This is related but somewhat tangential -- 

  Why isn't there a tryReadChan?  It looks like it would be implementable with the current Chan representation in terms of tryTakeMVar.  Especially since isEmptyChan is deprecated this would be nice to have.

Because of missing tryReadChan there is no non-blocking way to read data resident in a Chan (i.e. flush it -- in this case because I was in an exception handler and wanted to flush out what was left in memory in a Chan).  I found myself rolling my own in the form of the following data structure to get around this:


-- Chan's don't quite do the trick.  Here's something simpler.  It
-- keeps a buffer of elemnts and an MVar to signal "end of stream".
-- This it separates blocking behavior from data access.
data Buffer a = Buf (MVar ()) (IORef [a])

newBuffer :: IO (Buffer a)
newBuffer = do
  mv  <- newEmptyMVar
  ref <- newIORef []
  return (Buf mv ref)

writeBuffer :: Buffer a -> a -> IO ()
writeBuffer (Buf mv ref) x = do
  b <- isEmptyMVar mv
  if b
     then atomicModifyIORef ref (\ ls -> (x:ls,()))
   else error "writeBuffer: cannot write to closed Buffer"

-- | Signal completion. 
closeBuffer :: Buffer a -> IO ()
closeBuffer (Buf mv _) = putMVar mv ()

peekBuffer :: Buffer a -> IO [a]
peekBuffer (Buf _ ref) = liftM reverse $ readIORef ref 

-- Returns a lazy list, just like getChanContents:
getBufferContents :: Buffer a -> IO [a]
getBufferContents buf@(Buf mv ref) = do
  chan <- newChan 
  let loop = do 
grabbed <- atomicModifyIORef ref (\ ls -> ([], reverse ls))
mapM_ (writeChan chan . Just) grabbed
mayb <- tryTakeMVar mv -- Check if we're done.
case mayb of 
  Nothing -> threadDelay 10000 >> loop
  Just () -> writeChan chan Nothing
  forkIO loop
  ls <- getChanContents chan
  return (map fromJust $ 
 takeWhile isJust ls)