isEmptyChan blocks?

Simon Peyton-Jones simonpj@microsoft.com
Thu, 19 Jun 2003 10:34:47 +0100


| > I noticed that isEmptyChan blocks if the channel is already
| > waited on by readChan, is this the intended behaviour?
| > At least I was a bit surprised by a blocking predicate..
|=20
| I agree this doesn't seem right.  Looking at the implementation
though,
| I can't see an easy way to fix it - any suggestions?

Just to clarify.   The offending module is Control.Concurrent.Chan, and
I reproduce the key code below.=20

The channel is represented by a pair of MVars, which point to head and
tail (respectively) of a list composed of MVars.  The difficulty is that
a blocked reader will own the read-end MVar, so isEmptyChan blocks. =20

That makes isEmptyChan essentially useless.  Either it should be
removed, or the implementation of Chan needs to be elaborated to support
isEmptyChan.

Volunteers?

Simon







-- A channel is represented by two @MVar@s keeping track of the two ends
-- of the channel contents,i.e.,  the read- and write ends. Empty
@MVar@s
-- are used to handle consumers trying to read from an empty channel.

-- |'Chan' is an abstract type representing an unbounded FIFO channel.
data Chan a =3D Chan (MVar (Stream a)) (MVar (Stream a))

type Stream a =3D MVar (ChItem a)

data ChItem a =3D ChItem a (Stream a)

-- See the Concurrent Haskell paper for a diagram explaining the
-- how the different channel operations proceed.

-- |Build and returns a new instance of 'Chan'.
newChan :: IO (Chan a)
newChan =3D do
   hole  <- newEmptyMVar
   read  <- newMVar hole
   write <- newMVar hole
   return (Chan read write)

-- To put an element on a channel, a new hole at the write end is
created.
-- What was previously the empty @MVar@ at the back of the channel is
then
-- filled in with a new stream element holding the entered value and the
-- new hole.

-- |Write a value to a 'Chan'.
writeChan :: Chan a -> a -> IO ()
writeChan (Chan _read write) val =3D do
  new_hole <- newEmptyMVar
  modifyMVar_ write $ \old_hole -> do
    putMVar old_hole (ChItem val new_hole)
    return new_hole

-- |Read the next value from the 'Chan'.
readChan :: Chan a -> IO a
readChan (Chan read _write) =3D do
  modifyMVar read $ \read_end -> do
    (ChItem val new_read_end) <- readMVar read_end
	-- Use readMVar here, not takeMVar,
	-- else dupChan doesn't work
    return (new_read_end, val)

-- |Returns 'True' if the supplied 'Chan' is empty.
isEmptyChan :: Chan a -> IO Bool
isEmptyChan (Chan read write) =3D do
   withMVar read $ \r -> do
     w <- readMVar write
     let eq =3D r =3D=3D w
     eq `seq` return eq