Marc Weber Marc Weber wrote:
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 ?
If you want to communicate with external programs via pipes, then
System.Process should provide everything you need. Take a look at
runInteractiveProcess in particular.
Cheers,
Simon
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe