Fast Mutable Variables for the IO and ST monads

Hello haskell-cafe, only for the souls interesting in writing efficient programs :) i included in this letter my own module used for fast variables - "DataVariables.hs". and "wc.hs" contains example of using these vars. DataVariables module contains many interesting beasts but for optimization purposes newVar/readVar/writeVar is especially interesting. these primitives mimics IORef interface, supports Int/Word/Bool variables, works in IO and ST monad and nevertheless they are compiled to the most-effective GHC primitives. moreover, they can be used outside GHC (of course, on other compilers just IORef/STRer are used to implement this) it was impossible to add Ptr's support with the same interface, so Ptrs supported by another functions - newPtr/readPtr/writePtr and don't work in ST monad. in other aspects fast Ptr variables are the same as fast general variables if you need to include these variables in data structures, use the types IntVar/WordVar/BoolVar/"MutPtr a" for the IO monad, and "MutInt s", "MutWord s", "MutBool s" for the ST monad another interesting beasts are unboxed Int and Bool values. although GHC can automatically unbox vars in some cases, using this module will guarantee unboxing. moreover, some operations such as bit shifts, are ineffective without explicit unboxing because their definitions don't use unboxed operations directly, but adds additional checks and conversions. using types FastInt and FastBool and associated operations guarantee unboxing on GHC and works on other compilers (where just boxed values are used to implement these types). one place from my lib where i used them to speed up program: putWord32be :: (Stream m h, Integral int, Bits int) => h -> int -> m () putWord32be h w = do let n = iUnbox (fromIntegral w) vPutByte h $! iBox ((n >># _ILIT 24) ) vPutByte h $! iBox ((n >># _ILIT 16) _ILIT 0xff) vPutByte h $! iBox ((n >># _ILIT 8) _ILIT 0xff) vPutByte h $! iBox ((n ) _ILIT 0xff) -- Best regards, Bulat mailto:bulatz@HotPOP.com

Bulat Ziganshin wrote:
only for the souls interesting in writing efficient programs :)
i included in this letter my own module used for fast variables - "DataVariables.hs". and "wc.hs" contains example of using these vars.
The Var class is interesting - basically the equivalent of the MArray class for mutable variables. Is there a reason you couldn't use the same pattern as the MArray class? MArray of Ptr works fine, but for some reason you couldn't do it with Var, why not? I suggest you follow the same scheme as the unboxed array types, and have IOURef/STURef types, parameterised over the element type. Of course, we should have instances for all of the primitive numeric types plus Ptr, ForeignPtr, StablePtr, Bool. Cheers, Simon

Hello Simon, Monday, February 06, 2006, 4:41:50 PM, you wrote: SM> The Var class is interesting - basically the equivalent of the MArray SM> class for mutable variables. Is there a reason you couldn't use the SM> same pattern as the MArray class? MArray of Ptr works fine, but for SM> some reason you couldn't do it with Var, why not? quick answer: because it don't use fundeps: class (HasBounds a, Monad m) => MArray a e m where vs class (Monad m) => Var m r a | r->a, m a->r where and fundeps used to avoid needing to specify type of created reference, as should be done with arrays: main = do arr <- newArray (1,10) 37 :: IO (IOArray Int Int) main = print $ runST (do arr <- newArray (1,10) 127 :: ST s (STArray s Int Int) while in my library one can write the following code: chars <- newVar (0::Int) inWord <- newVar False that will work in ANY monad (at least ST and IO with current Var instances). btw, Ptrs is not very useful outside of IO monad (although they can be very useful for extended-IO sort of monads) i will check this more thoroughly SM> I suggest you follow the same scheme as the unboxed array types, and SM> have IOURef/STURef types, parameterised over the element type. Of SM> course, we should have instances for all of the primitive numeric types SM> plus Ptr, ForeignPtr, StablePtr, Bool. i think that i should implement this and add my own Var class as the user of this more general library, that serves my own purpose of writing monad-independent code btw, i have the counter proposal - automatically convert IORefs of simple types to the fast internal variables like the Int automatically converted to the Int#. The same applies to automatic conversion of arrays to the unboxed arrays -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Mon, Feb 06, 2006 at 11:13:47PM +0300, Bulat Ziganshin wrote:
btw, i have the counter proposal - automatically convert IORefs of simple types to the fast internal variables like the Int automatically converted to the Int#. The same applies to automatic conversion of arrays to the unboxed arrays
Yeah, I have thought about doing this optimization for jhc. the only issue is that figuring out 'strictness' through an updatable variable is pretty darn tricky. It would be good if there were an IOSRef which is a strict IORef (this can be simulated with normal IORefs and seq) but with secret internal compiler support to automatically turn them into their unboxed equivalants. John -- John Meacham - ⑆repetae.net⑆john⑈

On Mon, Feb 06, 2006 at 04:19:03PM -0800, John Meacham wrote:
On Mon, Feb 06, 2006 at 11:13:47PM +0300, Bulat Ziganshin wrote:
btw, i have the counter proposal - automatically convert IORefs of simple types to the fast internal variables like the Int automatically converted to the Int#. The same applies to automatic conversion of arrays to the unboxed arrays
Yeah, I have thought about doing this optimization for jhc. the only issue is that figuring out 'strictness' through an updatable variable is pretty darn tricky. It would be good if there were an IOSRef which is a strict IORef (this can be simulated with normal IORefs and seq) but with secret internal compiler support to automatically turn them into their unboxed equivalants.
heh. After some more thought, I realized it is not only relativly easy for jhc to implement this optimization generally, but that it already does! the arity raising transformation is basically an unboxing style transformation, that will take arguments with a known heap layout and just pass its components to functions. since suspended functions and mutable variables are both just heap locations, the arity raising transformation of functions incidentally does the same for IORefs. meaning that if every update looks like this (which would be the case if you only stored strict integer values in it) update v1 (Prelude.Int (i::Int#)) then the arity raising will see that that heap location always has a boxed Int#, and just drop the box, turning it into update v1 (i::Int#) now an interesting thing is that this transformation applies even if the value isn't strict. take this function foo 0 = error "is zero" foo x = x now, imagine you want to store (foo x) in an IORef for various calls of foo, obviously using a strict IORef would be bad, as it might invoke the error prematurely. in grin, the writeIORefs will end up looking like update v1 (Ffoo (i::Int#)) Ffoo is the tag that means a suspended call to 'foo' since there is absolutely no differenc between data constructors and suspended functions, the same optimization applies, and you end up turning it into a mutable fast int in the heap, even though it is not strict... note there are some other complications, like you need to make sure you can identify all the use sites of said heap location so that you can transform them too, but in practice this can be done for the majority of heap locations I have found. John -- John Meacham - ⑆repetae.net⑆john⑈

Hello John, Tuesday, February 07, 2006, 3:19:03 AM, you wrote:
btw, i have the counter proposal - automatically convert IORefs of
JM> is pretty darn tricky. It would be good if there were an IOSRef which is JM> a strict IORef (this can be simulated with normal IORefs and seq) but JM> with secret internal compiler support to automatically turn them into JM> their unboxed equivalants. and what you now think about your proposal? anyway, IOURef should be made to speed up current GHC programs -- Best regards, Bulat mailto:bulatz@HotPOP.com

Bulat Ziganshin wrote:
Hello Simon,
Monday, February 06, 2006, 4:41:50 PM, you wrote:
SM> The Var class is interesting - basically the equivalent of the MArray SM> class for mutable variables. Is there a reason you couldn't use the SM> same pattern as the MArray class? MArray of Ptr works fine, but for SM> some reason you couldn't do it with Var, why not?
quick answer: because it don't use fundeps:
class (HasBounds a, Monad m) => MArray a e m where vs class (Monad m) => Var m r a | r->a, m a->r where
and fundeps used to avoid needing to specify type of created reference, as should be done with arrays:
main = do arr <- newArray (1,10) 37 :: IO (IOArray Int Int) main = print $ runST (do arr <- newArray (1,10) 127 :: ST s (STArray s Int Int)
while in my library one can write the following code:
chars <- newVar (0::Int) inWord <- newVar False
Sure, but you're restricted to one kind of Var per monad. With MArray, we have several array types per monad, and we could also have several monads per array type - if, say, you wanted to implement an instance of MArray for IOArray in your own IO-based monad, that's possible. Fewer fundeps = more flexibility but more type annotations. If we were to have overloaded references in the standard libraries, it would look strange if the interface wasn't consistent with overloaded arrays. I think you could mitigate the problem by providing non-overloaded newIORef/newSTRef operations. I'd support providing IOURef & STURef types, with overloading similar to MArray (MRef).
btw, i have the counter proposal - automatically convert IORefs of simple types to the fast internal variables like the Int automatically converted to the Int#. The same applies to automatic conversion of arrays to the unboxed arrays
The problem with doing this is you need a pretty beefy strictness analyser to be able to tell whether the reference is being used strictly, this is far beyond what GHC does (I'm impressed that jhc can do this, but I don't think there's much hope for us doing it in GHC). Better is for the user to request strict references, and have the implementation do the unboxing, which is exactly what happens with IOUArray. Furthermore, it's deterministic: if you ask for an IOUArray (or IOURef), you're guarnanteed to get unboxing, which is better than relying on some complex optimisation to work properly. Cheers, Simon

On Wed, Feb 08, 2006 at 11:13:20AM +0000, Simon Marlow wrote:
The problem with doing this is you need a pretty beefy strictness analyser to be able to tell whether the reference is being used strictly, this is far beyond what GHC does (I'm impressed that jhc can do this, but I don't think there's much hope for us doing it in GHC).
What jhc is doing is not quite strictness analysis here (though it does do ghc style strictness analysis at the jhc core phase). this is a sort of 'inverse strictness' where instead of determining whether a function will definitly evaluate a value, it determines when a value will definitly have already been evaluated when passed to a function. so instead of checking whether an IORef will definitly be read and evaluated, it just needs to check if it is always being filled in with already evaluated values. Since ghc (and jhc) core have no way to easily tell the difference between a thunk that we know has already been evaluated and one that might need to be (except in the few cases we can unbox it) this is hard to take advantage of at the core phase but easy in the grin phase where evaluations are explicit. it would be possible to add two types of case statements to core, one which does an 'evaluate then switch' and another that just does a 'switch' assuming the scrutinee has already been evaluated. the second form of case on ghc could just read the closure directly rather than jumping to its code. this would allow ghc to take advantage of this type of 'inverse' strictness analysis. however, it is less powerful when you have separate compilation, it might be useful for local functions or to express other optimizations. like for instance you know the 'switch' version of case will never need to do an update.
Better is for the user to request strict references, and have the implementation do the unboxing, which is exactly what happens with IOUArray. Furthermore, it's deterministic: if you ask for an IOUArray (or IOURef), you're guarnanteed to get unboxing, which is better than relying on some complex optimisation to work properly.
I was thinking just a provided strict reference type, which can be transformed internally into their unboxed forms when one is available, but just act as strict references otherwise. strict references would be generally useful independent of their unboxability and it wouldn't clutter up the API so much. It would be analogous to the (sometimes) automatic unboxing of strict fields in data constructors. such a transformation would need to be carried out always though and can't be considered just an optimization but that shouldn't be a problem as IORefs always have a known monomorphic type (or are never used) John -- John Meacham - ⑆repetae.net⑆john⑈

Simon Marlow wrote:
I suggest you follow the same scheme as the unboxed array types, and have IOURef/STURef types, parameterised over the element type. Of course, we should have instances for all of the primitive numeric types plus Ptr, ForeignPtr, StablePtr, Bool.
Perhaps it may be worth to introduce a class Unpackable as described at the end of http://www.haskell.org/pipermail/haskell-cafe/2004-July/006400.html so we may define STUArray as an instance of MArray, and other similar unpackable things easier?

Hello oleg, Wednesday, February 08, 2006, 8:37:55 AM, you wrote:
I suggest you follow the same scheme as the unboxed array types, and have IOURef/STURef types, parameterised over the element type. Of course, we should have instances for all of the primitive numeric types plus Ptr, ForeignPtr, StablePtr, Bool.
opc> Perhaps it may be worth to introduce a class Unpackable as described opc> at the end of opc> http://www.haskell.org/pipermail/haskell-cafe/2004-July/006400.html opc> so we may define STUArray as an instance of MArray, and other similar opc> unpackable things easier? btw, there is a class Storable. although it serves diffrent purposes, at least the members are the same -- Best regards, Bulat mailto:bulatz@HotPOP.com
participants (4)
-
Bulat Ziganshin
-
John Meacham
-
oleg@pobox.com
-
Simon Marlow