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 <[EMAIL PROTECTED]> wrote:

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.

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

Reply via email to