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

Aaron Denney wnoise at ofb.net
Tue Jul 17 16:19:31 EDT 2007


On 2007-07-17, David Menendez <zednenem at psualum.com> wrote:
> 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.

That seems excessive.  STM has nice composable properties but if you're
not composing it with other STM usages, there's not much reason to
buy those properties.

> getClosableChanContents :: Chan (Maybe a) -> IO [a]
> getClosableChanContents ch = unsafeInterleaveIO $ do
>       x <- readChan ch
>       case x of Nothing -> return []
>                 Just y  -> do ys <- getClosableChanContents ch
>                               return (y : ys)

Untested of course.  With the corresponding

> writeList2CChan :: Chan (Maybe a) -> [a] -> IO ()
> writeList2CChan ch ls = do sequence_ (map (writeChan ch) . (Just)) ls)
>                            writeChan ch Nothing

Am I missing something that makes this "not lazy enough"?

-- 
Aaron Denney
-><-



More information about the Libraries mailing list