Control.Concurrent.Chan: how do i close a channel?
Claus Reinke
claus.reinke at talk21.com
Mon Jul 16 10:21:16 EDT 2007
> 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
More information about the Libraries
mailing list