An answer and a question to GHC implementors [was Re: How to make Claessen's Refs Ord-able?]

Simon Marlow simonmar@microsoft.com
Tue, 9 Apr 2002 11:06:14 +0100


> > However, it is possible to have global top-level references using
> > unsafePerformIO if you're very careful about it.  In GHC we=20
> do something
> > like this:
> >=20
> > {-# NOINLINE global_var #-}
> > global_var :: IORef Int
> > global_var =3D unsafePerformIO (newIORef 42)
> >=20
> > the NOINLINE pragma is used to ensure that there is=20
> precisely *one* copy
> > of the right hand side of global_var in the resulting=20
> program (NOTE: you
> > also need to compile the program with -fno-cse to ensure that the
> > compiler doesn't also common up the RHS of global_var with=20
> other similar
> > top-level definitions).
>=20
> this usage of unsafePerformIO is such a staple of real-world Haskell
> programming, it seems there should be some language (or experemental
> compiler *wink wink ghc nudge*) support for it. I am not sure=20
> what form
> it would take though.

<muse>
I did wonder once whether IO monad bindings should be allowed at the
top-level of a module, so you could say

     module M where
     ref <- newIORef 42

and the top-level IO would be executed as part of the module
initialization code.  This solves the problems with unsafePerformIO in a
cleanish way, but would add some extra complexity to implementations.
And I'm not sure what happens if one top-level IO action refers to other
top-level IO bindings (modules can be recursive, so you could get loops
too).
</muse>

> getGlobalVar :: IO (IORef Int)
> getGlobalVar =3D memoIO (newIORef 42)=20
>=20
> note that this is not exactly the same since getting the global var is
> in the io monad, but that really makes sense if you think=20
> about it. and
> chances are you are already in IO if you need an IORef.

This doesn't really solve the problem we were trying to solve, namely
that passing around the IORef everywhere is annoying.  If we were happy
to pass it around all the time, then we would just say

   main =3D do=20
      ref <- newIORef 42
      ... pass ref around for ever ...

We could use implicit parameters, but that means changing the types of
lots of functions, and that's just as annoying as actually passing the
arguments around explicitly.

Cheers,
	Simon