[Haskell-cafe] One-shot? (was: Global variables and stuff)

Adrian Hey ahey at iee.org
Wed Nov 10 14:15:02 EST 2004


OK, I'll play again..

On Wednesday 10 Nov 2004 4:39 pm, Judah Jacobson wrote:
> What about the following?  It does use unsafePerformIO, but only to
> wrap newMVar in this
> specific case.
>
> once :: Typeable a => IO a -> IO a
> once m = let {-# NOINLINE r #-}
>              r = unsafePerformIO (newMVar Nothing)
>          in do
>                y <- takeMVar r
>                x <- case y of
>                      Nothing -> m
>                      Just x -> return x
>                putMVar r (Just x)
>                return x
>

My initial feeling is that this kind of swizzles the problem around a bit
and leaves us right back where we started. Pretty much any use of
unsafePerformIO is unsound, though whether or not this has any bad
consequences probably depends a lot on the context it's used what
transformations and optimisations the compiler implements. But I'd
really like to avoid using it at all if possible. Unless I'm
missing something, once is still unsafe (see below..)

> Additionally, I'd like to repeat the point that "once" (whether
> defined my way or Keean's) is
> not just a consequence of module initialization; it can actually
> replace it in most cases!

Hmm, must of missed that..

> For example:
>
> myRef :: IO (IORef Char)
> myRef = once (newIORef 'a')
>
> readMyRef :: IO Char
> readMyRef = myRef >>= readIORef
>
> writeMyRef :: Char -> IO ()
> writeMyRef c = myRef >>= flip writeIORef c

Suppose I had..

myOtherRef :: IO (IORef Char)
myOtherRef = once (newIORef 'a')

There's nothing to stop the compiler doing CSE and producing, in effect..

commonRef :: IO (IORef Char)
commonRef = once (newIORef 'a')

.. followed by substitution of all occurrences of myRef and myOtherRef
with commonRef. I think this would break your programs.

> A library interface might consist of readMyRef and writeMyRef, while hiding
> myRef itself from the user.  However, what happens in IO stays in the
> IO monad; myRef is an action, so the IORef is not initialized until
> the first time
> that one of read/writeMyRef is called.  Indeed, any action wrapped by once
> will only be run in the context of the IO monad.  IMO, this is the primary
> advantage of a function like once over the proposal for top-level
> x <- someAction
> where the exact time someAction is evaluated is unspecified.

AFAICS this is only true if the argument to once is something like
(newIORef 'a), in which case the same is also true of the x <- newIORef 'a'
solution. Also my own pet solution (SafeIO monad) and Koen's CIO monad
are intended to make it impossible to use constructions whose initial
value depends on when construction occurs.

The intention of the (x <- constructor) proposal is more than just
syntactic sugar for (x = unsafePerformIO constructor). I think something
like this really is necessary for a proper solution, though not everybody
agrees what that should be at the moment (and some don't seem agree that
there's a problem in the first place :-)

Hope I haven't missed anything. (I'm sure you'll let me know if you think
I'm being stupid :-)

Regards
--
Adrian Hey



More information about the Haskell-Cafe mailing list