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

John Meacham john@repetae.net
Thu, 11 Apr 2002 13:21:22 -0700


On Tue, Apr 09, 2002 at 11:06:14AM +0100, Simon Marlow wrote:
> > 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 
> > 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


wow. i really like this, I was thinking about something similar, but did
not want to have to introduce new syntax. using <- seems to make sense
here.

> 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 = memoIO (newIORef 42) 
> > 
> > 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 
> > 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 = do 
>       ref <- newIORef 42
>       ... pass ref around for ever ...

we wouldnt have to pass it around all the time with this scheme, you
would do something like

getGlobalVar :: IO (IORef Int)
getGlobalVar = memoIO (newIORef 42)

now you can use it anywhere as..

inc = do
	v <- getGlobalVar
	modifyIORef v (+ 1)


here is my simple implementation of memoIO which seems to do the right
thing. (at least under ghc)

memoIO :: IO a -> IO a
memoIO ioa = do
    v <- readIORef var
    case v of 
	Just x -> return x
	Nothing -> do
	    x <- ioa
	    writeIORef var (Just x) 
	    return x 
     where
	var = unsafePerformIO $ newIORef Nothing

-- 
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john@repetae.net
---------------------------------------------------------------------------