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

in principle, Chan looks like a nice way to do pipes within haskell code, or to avoid unsafeInterleaveIO, in combination with getChanContents (which explicitly mentions hGetContents in its API doc). however, i seem to be missing a way to close a channel? am i misinterpreting this library? claus

claus.reinke:
in principle, Chan looks like a nice way to do pipes within haskell code, or to avoid unsafeInterleaveIO, in combination with getChanContents (which explicitly mentions hGetContents in its API doc).
however, i seem to be missing a way to close a channel? am i misinterpreting this library?
They're not attached to Handles -- that's the IO loop that does the writing to the Chan's job -- so they dont' really have a 'close'. When you're done writing, just stop writing. 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? -- Don

however, i seem to be missing a way to close a channel? am i misinterpreting this library?
They're not attached to Handles -- that's the IO loop that does the writing to the Chan's job -- so they dont' really have a 'close'.
i was indeed looking for a haskell-internal replacement for Handles, being somewhat surprised that i can't seem to create unattached Handles with the uls (usual library suspects;-). think pipes: if an external process takes input via a handle and provides output via a handle, the haskell equivalent could do the same via a Chan, so it'd be easy to write mixed pipes.
When you're done writing, just stop writing.
yes, but any user of getChanContents will be left hanging! that kind of function doesn't really work well without a way to tell it that it has nothing more to wait for.
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. claus

think pipes: if an external process takes input via a handle and provides output via a handle, the haskell equivalent could do the same via a Chan, so it'd be easy to write mixed pipes.
for illustration, here is the kind of utility that i find missing in System.Process, using the Maybe lifting of Chan contents. this doesn't do any error handling, but allows for simple-minded pipes like: $ ghc -e 'cmd "cat" >|> fun (map Data.Char.toUpper) >|> cmd "grep WO" >>= \(i,o)->i "hello\nWORLD\n">>o >>= putStr' ProcUtils.hs WORLD $ ghc -e 'cmd "ls" >|> fun (map Data.Char.toUpper) >|> cmd "grep .HS" >>= \(i,o)->o >>= putStr' ProcUtils.hs PROCUTILS.HS X.HS Y.HS Z.HS lifting contents to Maybe is easy enough, i just find it hard to see the use-case for getChanContents without such lifting or any way to close Chans? claus ---------------------------------------------------pipe utitlities import System.Process import Control.Concurrent import System.IO import Data.Maybe cmd c = runInteractiveCommand c >>= \(i,o,e,p)->return (hPutStr i,hGetContents o) fun f = do i <- newChan o <- newChan forkIO $ fromChan i >>= toChan o . f return (toChan i,fromChan o) infixr >|> c1 >|> c2 = do (i1,o1) <- c1 (i2,o2) <- c2 forkIO $ o1 >>= i2 return (i1,o2) toChan c str = writeList2Chan c $ map Just str ++ [Nothing] fromChan c = getChanContents c >>= return . map fromJust . takeWhile isJust

On 2007-07-16, Claus Reinke
When you're done writing, just stop writing.
yes, but any user of getChanContents will be left hanging! that kind of function doesn't really work well without a way to tell it that it has nothing more to wait for.
Yeah, getChanContents is not suitable for streams that may end. A note in the documentation to this effect may be useful. Some sort of unfold-like combinator to lazily read from a Chan (Maybe a) into a list may be useful instead. -- Aaron Denney -><-

On 7/16/07, Claus Reinke
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 []

On 2007-07-17, David Menendez
On 7/16/07, Claus Reinke
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 -><-

Aaron Denney wrote:
On 2007-07-17, David Menendez
wrote: On 7/16/07, Claus Reinke
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"?
The above costs the construction of the Maybe data for each item going through the channel. Using an MVar instead of a TVar costs taking the MVar on each read. Using STM is optimistic, it performs the read on the channel and then a check that nothing was committed in the mean time (unlikely given the short atomic block). Benchmarking the three idioms would be a useful service, but I don't have time. -- Chris
participants (5)
-
Aaron Denney
-
Claus Reinke
-
David Menendez
-
dons@cse.unsw.edu.au
-
haskell@list.mightyreason.com