
First of all, sorry if this is a really silly question, but I couldn't figure it out from experimenting in GHCi and from the GHC libraries documentation (or Google). Is there an IORef consturctor? Or is it just internal to the Data.IORef module? I want a "global variable", so I did the following: ------ module VirtualWorld where import Data.IORef theWorld = IORef [] -- This will be writeIORef'ed with a populated list as the user modifies the world. ----- It doesn't work. GHCi says that the IORef constructor is not in scope. I did a ":module Data.IORef" and then "IORef []" and it still gives me the same error. I'm using GHC 6.6 on Windows.

On 01/12/2006, at 6:08 PM, TJ wrote:
First of all, sorry if this is a really silly question, but I couldn't figure it out from experimenting in GHCi and from the GHC libraries documentation (or Google).
Is there an IORef consturctor? Or is it just internal to the Data.IORef module?
I want a "global variable", so I did the following:
------ module VirtualWorld where import Data.IORef theWorld = IORef [] -- This will be writeIORef'ed with a populated list as the user modifies the world. -----
It doesn't work. GHCi says that the IORef constructor is not in scope. I did a ":module Data.IORef" and then "IORef []" and it still gives me the same error.
I'm using GHC 6.6 on Windows.
Hi TJ, IORef is an abstract data type, so you cannot refer to its constructors directly. Instead you must use: newIORef :: a -> IO (IORef a) which will create an IORef on your behalf. Note that the result is in the IO type, which limits what you can do with it. If you want a global variable then you can use something like: import System.IO.Unsafe (unsafePerformIO) global = unsafePerformIO (newIORef []) But this is often regarded as bad programming style (depends who you talk to). So you should probably avoid this unless it is really necessary (perhaps you could use a state monad instead?) Read the comments about unsafePerformIO on this page: http://www.haskell.org/ghc/docs/latest/html/libraries/base/System- IO-Unsafe.html especially the notes about NOINLINE and -fno-cse Cheers, Bernie.

Thanks. I've been reading the docs and examples on State (in
Control.Monad.State), but I can't understand it at all. ticks and
plusOnes... All they seem to do is return their argument plus 1...
On 12/1/06, Bernie Pope
On 01/12/2006, at 6:08 PM, TJ wrote:
First of all, sorry if this is a really silly question, but I couldn't figure it out from experimenting in GHCi and from the GHC libraries documentation (or Google).
Is there an IORef consturctor? Or is it just internal to the Data.IORef module?
I want a "global variable", so I did the following:
------ module VirtualWorld where import Data.IORef theWorld = IORef [] -- This will be writeIORef'ed with a populated list as the user modifies the world. -----
It doesn't work. GHCi says that the IORef constructor is not in scope. I did a ":module Data.IORef" and then "IORef []" and it still gives me the same error.
I'm using GHC 6.6 on Windows.
Hi TJ,
IORef is an abstract data type, so you cannot refer to its constructors directly.
Instead you must use:
newIORef :: a -> IO (IORef a)
which will create an IORef on your behalf. Note that the result is in the IO type, which limits what you can do with it.
If you want a global variable then you can use something like:
import System.IO.Unsafe (unsafePerformIO)
global = unsafePerformIO (newIORef [])
But this is often regarded as bad programming style (depends who you talk to). So you should probably avoid this unless it is really necessary (perhaps you could use a state monad instead?)
Read the comments about unsafePerformIO on this page:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/System- IO-Unsafe.html
especially the notes about NOINLINE and -fno-cse
Cheers, Bernie.

tjay.dreaming:
Thanks. I've been reading the docs and examples on State (in Control.Monad.State), but I can't understand it at all. ticks and plusOnes... All they seem to do is return their argument plus 1...
Here's a little demo. (I agree, the State docs could have nicer demos) Play around with the code, read the haddocks, and it should make sense eventually :)_ -- Don import Control.Monad.State -- -- the type for a 'global' 'variable' -- data T = T { ref :: Int } -- Run code with a single global 'ref', initialised to 0 main = evalStateT g $ T { ref = 0 } -- set it to 10 g = do printio "g" putRef 10 printio "modified state" f -- read that ref, print it f = do r <- getRef printio r return () getRef = gets ref putRef x = modify $ \_ -> T { ref = x } printio :: Show a => a -> StateT T IO () printio = liftIO . print

Thanks for the demo. I don't actually understand what's going on yet,
but your code doesn't really use a global variable, does it? From
what I can understand, the main function is passing the State to the
other functions.
I think I was careless about mixing "IO functions" and normal
functions. Now that I think about it, my "global variable" really
should only be available to IO functions, so the following should be
just fine:
----------------------------------------------------------
module Global where
import Data.IORef
theGlobalVariable = newIORef []
testIt = do ref <- theGlobalVariable
original <- readIORef ref
print original
writeIORef ref [1,2,3]
new <- readIORef ref
print new
----------------------------------------------------------
I've got a lot to learn about Haskell...
On 12/1/06, Donald Bruce Stewart
tjay.dreaming:
Thanks. I've been reading the docs and examples on State (in Control.Monad.State), but I can't understand it at all. ticks and plusOnes... All they seem to do is return their argument plus 1...
Here's a little demo. (I agree, the State docs could have nicer demos)
Play around with the code, read the haddocks, and it should make sense eventually :)_
-- Don
import Control.Monad.State
-- -- the type for a 'global' 'variable' -- data T = T { ref :: Int }
-- Run code with a single global 'ref', initialised to 0 main = evalStateT g $ T { ref = 0 }
-- set it to 10 g = do printio "g" putRef 10 printio "modified state" f
-- read that ref, print it f = do r <- getRef printio r return ()
getRef = gets ref
putRef x = modify $ \_ -> T { ref = x }
printio :: Show a => a -> StateT T IO () printio = liftIO . print

tjay.dreaming:
Thanks for the demo. I don't actually understand what's going on yet, but your code doesn't really use a global variable, does it? From what I can understand, the main function is passing the State to the other functions.
Right, via the monad. The monad does all the threading.
I think I was careless about mixing "IO functions" and normal functions. Now that I think about it, my "global variable" really should only be available to IO functions, so the following should be just fine:
---------------------------------------------------------- module Global where
import Data.IORef
theGlobalVariable = newIORef []
testIt = do ref <- theGlobalVariable original <- readIORef ref print original writeIORef ref [1,2,3] new <- readIORef ref print new ----------------------------------------------------------
I've got a lot to learn about Haskell...
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

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

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

TJ wrote:
---------------------------------------------------------- module Global where
import Data.IORef
theGlobalVariable = newIORef []
testIt = do ref <- theGlobalVariable original <- readIORef ref print original writeIORef ref [1,2,3] new <- readIORef ref print new ----------------------------------------------------------
Wrong. You get a fresh new "variable" everytime you access 'theGlobalVariable'.
I've got a lot to learn about Haskell...
Well, for starters: - there are no variables in ordinary Haskell, - there are variables in the ST and IO monads, but dragging IO everywhere is burdensome and you don't want to do that, - you can probably fake global variables using 'unsafePerformIO', and you definitely don't want to mess with that (yet), - you need to understand monads in general, the State monad, the ST monad and the IO monad, and in exactly this order. Whatever you're trying to do right now, just forget that there are variables in BASIC and do it without mutable state. -Udo -- They laughed at Einstein. They laughed at the Wright Brothers. But they also laughed at Bozo the Clown. -- attributed to Carl Sagan

Donald:
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.
Indeed, it's not what I thought it was at all! Bulat:
you may be interested in looking at http://haskell.org/haskellwiki/IO_inside
Thanks for the link. Udo:
Whatever you're trying to do right now, just forget that there are variables in BASIC and do it without mutable state.
Alrighty. But I'd like to set the record straight that it was C++ which screwed up my mind forever ;) Donald:
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?
Yes I've come to the same conclusion. Thanks for the help, it really helps :) TJ

Bernie Pope wrote:
If you want a global variable then you can use something like:
import System.IO.Unsafe (unsafePerformIO)
global = unsafePerformIO (newIORef [])
But this is often regarded as bad programming style (depends who you talk to).
Besides, isn't this example /really/ unsafe? I thought, at least the IORef has to be monomorphic or else type safety is lost? Cheers Ben

On 05/12/2006, at 1:00 PM, Benjamin Franksen wrote:
Bernie Pope wrote:
If you want a global variable then you can use something like:
import System.IO.Unsafe (unsafePerformIO)
global = unsafePerformIO (newIORef [])
But this is often regarded as bad programming style (depends who you talk to).
Besides, isn't this example /really/ unsafe? I thought, at least the IORef has to be monomorphic or else type safety is lost?
Perhaps your question is rhetorical, but in case it is not, then yes, we ought to make it a monomorphic type. This little example seg-faults on my mac, and no doubt on other machines as well: import System.IO.Unsafe (unsafePerformIO) import Data.IORef global = unsafePerformIO (newIORef []) main = do modifyIORef global (id :) x <- readIORef global print ((head x + 1) :: Int) It writes the identity function onto the front of the global variable, and then reads it back as an int, and tries to do addition on it. Cheers, Bernie.

On Wednesday 06 December 2006 07:40, Bernie Pope wrote:
On 05/12/2006, at 1:00 PM, Benjamin Franksen wrote:
Bernie Pope wrote:
If you want a global variable then you can use something like:
import System.IO.Unsafe (unsafePerformIO)
global = unsafePerformIO (newIORef [])
But this is often regarded as bad programming style (depends who you talk to).
Besides, isn't this example /really/ unsafe? I thought, at least the IORef has to be monomorphic or else type safety is lost?
Perhaps your question is rhetorical,
Half-way ;-) I was pretty sure but not 100%. Thanks for the nice example. Cheers, Ben
participants (5)
-
Benjamin Franksen
-
Bernie Pope
-
dons@cse.unsw.edu.au
-
TJ
-
Udo Stenzel