
tjay.dreaming:
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
This doesn't mean what you think it means :) In particular, theGlobalVariable isn't a global variable, its a function that creates a new IORef, initialised to []. So you create two new iorefs, once in modify1, and again in modify2. For this kind of problem, I'd use a State transformer monad, layered over IO, as follows: import Control.Monad.State main = evalStateT doIt [] doIt = do modify1 modify2 modify1 = do orig <- get printio orig put (1 : orig) new <- get printio new modify2 = do orig <- get printio orig put (2 : orig) new <- get printio new printio :: Show a => a -> StateT a IO () printio = liftIO . print Running this: $ runhaskell A.hs [] [1] [1] [2,1] Note that there's no need for any mutable variables here. If this isn't suitable, perhaps you could elaborate a bit on what effect you're trying to achieve? -- Don