[Haskell-cafe] Can't establish subprocess communication

Poprádi Árpád popradi_arpad at freemail.hu
Sun Nov 13 09:53:21 CET 2011


Hi all!

I have found a simple program on the web:

--code begin: copierer.hs
module Main (main)
where

main = interact id
--code end

I compiled it with
ghc -threaded --make copierer.hs

If i start it from a terminal,it behaves like the "cat" program without
arguments: simply copies the stdin to stdout line by line.

I wanted it to use from another Haskell program as subprocess:

--code begin: twowaysubprocesscomm.hs
module Main
where

import System.IO
import System.Process
import Control.Concurrent

main :: IO ()
main = do
    (hin,hout,p) <- start_subprocess
    send_and_receive (hin,hout) "boo"
    send_and_receive (hin,hout) "foo"
    terminateProcess p

start_subprocess :: IO (Handle,Handle,ProcessHandle)
start_subprocess = do
--    (hin, hout, _, p) <- runInteractiveProcess "cat" [] Nothing
Nothing -- This line works as expected
    (hin, hout, _, p) <- runInteractiveProcess "copierer" [] Nothing
Nothing -- This line doesn't work
    hSetBuffering hin  LineBuffering
    hSetBuffering hout LineBuffering
    return (hin, hout, p)

send_and_receive :: (Handle,Handle) -> String -> IO ()
send_and_receive (hin,hout) indata = do
    forkIO $ hPutStrLn hin indata
    outdata <- hGetLine hout
    putStrLn $ "outdata: " ++ outdata
--code end

I compiled it with:
ghc -threaded --make twowaysubprocesscomm.hs

then ran:
./twowaysubprocesscomm 
twowaysubprocesscomm: fd:7: hGetLine: end of file
twowaysubprocesscomm: fd:6: hPutChar: resource vanished (Broken pipe)

Copierer doesn't work as subprocess!
If i compile twowaysubprocesscomm.hs using the original "cat", it works
as expected:

./twowaysubprocesscomm 
outdata: boo
outdata: foo


What is wrong here?
The "copierer.hs", its usage in "twowaysubprocesscomm.hs" or both?

I use GHC 6.12.3 on a 64 bit linux.

Thanks,
Árpád








More information about the Haskell-Cafe mailing list