[Haskell-cafe] Emulating bash pipe/ process lib

Marc Weber Marc Weber marco-oweber at gmx.de
Thu Feb 9 03:25:24 EST 2006


Hi. I want to write a little haskell program executing about 4 programs
passing data via pipes. As my python script seems to be slower than a
bash script I want to try a ghc executable now.
It should invoke different parts of a text to speech chain. This way I
have one interface then.

Talar und #haskell told me that I might use runProcess and pass handles
for stdin and out created by createPipe and fdToHandle.

So my simple test looks like this:


module Main where
import System.IO
import System.Posix.IO

main = do
  (fdIn,fdOut) <- createPipe
  let (iohIn, iohOut) = (fdToHandle fdIn, fdToHandle fdOut)
  hIn <- iohIn
  hOut <- iohOut
  hPutStr hIn "test"
  line <- hGetLine hOut
  print line -- should now print test having been piped through my pipe

but I get the error:
pipe2: <file descriptor: 3>: hPutStr: illegal operation (handle is not
open for writing)

And in current CVS docs in base.System.Process.hs it is said that
createPipe is no longer exported ?

I've also found this library:
http://www.haskell.org/communities/11-2005/html/report.html#processlib
which seems to do something similar but is meant to pipe haskell types
between different threads (? I haven't understood what's going on there
because I can't understand Russian ;-)
Is this of any help for me?

Greetings Marc


More information about the Haskell-Cafe mailing list