[Haskell-cafe] class Ref...

Gracjan Polak gracjan at acchsh.com
Tue Jun 7 08:52:50 EDT 2005


Bulat Ziganshin wrote:
> Hello Gracjan,
> 
> Tuesday, June 07, 2005, 2:25:50 PM, you wrote:
> class Monad m =>> Ref m r | m -> r where
> GP>      newRef :: a -> m (r a)
> GP>      readRef :: r a -> m a
> GP>      writeRef :: r a -> a -> m ()
> 
> may be the following will be even more interesting:
>

I like it very much!

> import Control.Monad
> import Data.IORef
> 
> infixl 0 =:, +=, -=, =::, <<=
> ref = newIORef
> val = readIORef
> a=:b = writeIORef a b

Pretty shame := is already reserver :(. There is something alike 
Graphics.Rendering.OpenGL.GL.StateVar. The use $= for assignment. 
Generalizing "variables" (in respect to some monad) seems to be often 
reinvented idea :)

As I see this could be generalized to all Ref-like constructs 
(IO,ST,others?)

> a+=b = modifyIORef a (\a-> a+b)
> a-=b = modifyIORef a (\a-> a-b)
> a=::b = ((a=:).b) =<< val a
Is this convoluted modify? Why doesn't it use modifyIORef? Or am I wrong?

> for :: [a] -> (a -> IO b) -> IO ()
> for = flip mapM_

I like:

foreach = flip mapM
foreach_ = flip mapM_

> 
> newList = ref []
> list <<= x   =  list =:: (++[x])
Is this append?

> push list x  =  list =:: (x:)
> pop list     =  do x:xs<-val list; list=:xs; return x
> 
> main = do
>   sum <- ref 0
>   lasti <- ref undefined
>   for [1..5] $ \i -> do
>     sum += i
>     lasti =: i
>   sum =:: (\sum-> 2*sum+1)
>   print =<< val sum
>   print =<< val lasti
> 
>   xs <- newList
>   for [1..3] (push xs)
>   xs <<= 10
>   xs <<= 20
>   print =<< val xs
>

Haskell as ultimate imperative language :)

> 
> 
> I use this module to simplify working with references in my program.
> The first inteface can be used for IORef/STRef/MVar/TVar and second
> for lists and Chan
> 

Then we should create classes for those interfaces.

-- 
Gracjan



More information about the Haskell-Cafe mailing list