Control.Concurrent.Chan: how do i close a channel?

David Menendez zednenem at psualum.com
Tue Jul 17 15:33:31 EDT 2007


On 7/16/07, Claus Reinke <claus.reinke at talk21.com> wrote:
> > I often use Chan (Maybe a), with Nothing to tell the reader thread that
> > EOF is reached -- perhaps something like that is what you're looking
> > for?
>
> yes. but that would add another slight indirection, and it still doesn't
> make getChanContents itself any more useable. if you "often" have to
> modify/expand the API when you use it, perhaps there is something
> missing in that API? the "much like hGetContents" comment does
> seem to suggest that as well.

If STM is available, you could use a TChan for content and a TVar for
signalling.

Here's a quick sketch:

import Control.Concurrent.STM
import Control.Monad
import System.IO.Unsafe (unsafeInterleaveIO)
import qualified Control.Exception as X

data ClosableChan a = CC { open :: TVar Bool, chan :: TChan a }

newCChan :: STM (ClosableChan a)
newCChan = liftM2 CC (newTVar True) newTChan

writeCChan :: ClosableChan a -> a -> STM ()
writeCChan c a = writeTChan (chan c) a

closeCChan :: ClosableChan a -> STM ()
closeCChan c = writeTVar (open c) False

readCChan :: ClosableChan a -> STM a
readCChan c = readTChan (chan c) `orElse`
	(readTVar (open c) >>= \b -> if b then retry else error "Closed")


getCChanContents :: ClosableChan a -> IO [a]
getCChanContents c = unsafeInterleaveIO $ (do
	hd <- atomically (readCChan c)
	tl <- getCChanContents c
	return (hd:tl)
	) `X.catch` \_ -> return []


More information about the Libraries mailing list