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

Judah Jacobson judah.jacobson at gmail.com
Wed Nov 10 11:39:42 EST 2004


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

The "Typeable" constraint forces the return value to be monomorphic,
which prevents the
following from happening (the first line doesn't type check under the
constraint):

> let ref = once (newIORef [])
> :t ref
ref :: forall a. IO (IORef [a])
> ref >>= flip writeIORef "foo"
> ref >>= readIORef >>= (\(x::[Bool]) -> print x)
[Illegal instruction

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!
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

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.  

Are there any applications of module initialization for which once
does not suffice?

-Judah


On Wed, 10 Nov 2004 17:11:31 +0000, Keean Schupke
<k.schupke at imperial.ac.uk> wrote:
> I have written a small library for supporting one-shot without using
> unsfePerformIO...
> The library uses SYSV semaphores under linux to make sure the functional
> argument of
> "once" is only ever run once. It uses the ProcessID as the key for the
> semaphore, so will
> even enforce the once-only property accross different Haskell threads.
> Some semaphore
> functions are also exported, allowing other constraints to be used (for
> example, once
> only over multiple processes by using a constant ID rather than the
> processID.
> 
> I have attached the source for the library incase anyone is interested.
> If people think
> it is useful I could put it up on a website (let me know). Also attached
> is an example,
> which can be compiled with:
> 
>     ghc -o test NamedSem.hs Test.hs -package posix
> 
>     Keean.
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> 
>


More information about the Haskell-Cafe mailing list