Donald:
Now, if you wanted to pass that ref to other functions, you'd have to
thread it explicitly -- unless you store it in a state monad :)

    i.e. do ref <- theGlobalVariable
            ...
            .. f ref
            ...

      f r = do
            ...
            .. g r
            ...

I kind of jumped ahead that step, and went straight to the implicitly
threaded version.

-- Don


Tested my code again and it doesn't work as expected. I don't
understand what "threading" means, but is that the reason I can't have
this:

----------------------------------------------------------
module StateTest where

import Data.IORef

theGlobalVariable = newIORef []

modify1 = do ref <- theGlobalVariable
            original <- readIORef ref
            print original
            writeIORef ref $ original ++ [1]
            new <- readIORef ref
            print new

modify2 = do ref <- theGlobalVariable
            original <- readIORef ref
            print original
            writeIORef ref $ original ++ [2]
            new <- readIORef ref
            print new

doIt = do modify1
         modify2
----------------------------------------------------------

TJ
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to