[Haskell-cafe] readMVar and the devils

Simon Marlow simonmar at microsoft.com
Wed Jul 7 06:04:09 EDT 2004


On 06 July 2004 11:29, Conor T McBride wrote:

> OK, here's what I want, what I do with it, and my attempt to deliver
> it. But I'm not an expert, so please let me know if there's some
> disastrous flaw...
> 
> The signature/spec:
> 
> type Hole x
> 
> hole :: IO (Hole x)
>    -- returns a fresh empty hole for an x
> askHole :: Hole x -> IO (Maybe x)
>    -- inspects the current contents (or none) of the hole; mustn't
>    -- block
> tellHole :: Hole x -> x -> IO (Maybe x)
>    -- tries to write the hole, returns what was previously there;
>    -- if the hole was empty, the value supplied is installed
>    -- if the hole was full, it's unchanged (too late, pal!);
>    -- mustn't block
> readHole :: Hole x -> IO x
>    -- blocks until the hole has been filled, then returns its
>    -- value
> instance Eq (Hole x)
>    -- a kind of higher-level `pointer equality'

The following should do the trick (but I wouldn't rule out any lurking
race conditions, and perhaps there's an even simpler way to achieve
this):

data Hole x = Hole
   (MVar ())          -- wait on this for readHole
   (MVar (Maybe x))   -- always full, Just x <=> hole contains x

instance Eq (Hole x) where
  (Hole m1 _) == (Hole m2 _) = m1 == m2

hole = do
  wait <- newEmptyMVar
  val  <- newMVar Nothing
  return (Hole wait val)

askHole (Hole wait val) = readMVar val

tellHole (Hole wait val) x = do
  modifyMVar val $ \mb ->
    case mb of
      Nothing -> do putMVar wait (); return (Just x, Nothing)
      Just y  -> return (Just y, Just y)

readHole (Hole wait val) = do
  readMVar wait
  mb <- readMVar val
  return (fromJust mb)

Cheers,
	Simon


More information about the Haskell-Cafe mailing list