Can't establish subprocess communication

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

(hin, hout, _, p) <- runInteractiveProcess "copierer" [] Nothing
./twowaysubprocesscomm twowaysubprocesscomm: fd:7: hGetLine: end of file twowaysubprocesscomm: fd:6: hPutChar: resource vanished (Broken pipe)
Because you didn't give the right path to copierer. And you should hSetBuffering in copierer.hs. Because the handles returned by runInteractiveProcess are actually pipes that connect to copierer's stdin and stdout.

Hi mgampkay! Thank You, these were the problems with my programs. Greetings, Árpád On Sun, 2011-11-13 at 22:57 +0800, mgampkay wrote:
(hin, hout, _, p) <- runInteractiveProcess "copierer" [] Nothing
./twowaysubprocesscomm twowaysubprocesscomm: fd:7: hGetLine: end of file twowaysubprocesscomm: fd:6: hPutChar: resource vanished (Broken pipe)
Because you didn't give the right path to copierer. And you should hSetBuffering in copierer.hs. Because the handles returned by runInteractiveProcess are actually pipes that connect to copierer's stdin and stdout.

As mentioned by the first person to follow up, you need to set line buffering in the "copier" program. It's filling up its buffer while you write small lines to it - unlike the test run at the terminal prompt, where it's connected to a TTY device and therefore behaved differently. In a situation where you can confidently say your software will only ever be run in a POSIX environment, I like to use the Posix functions directly, because a buffered Handle on a pipe is nothing but extra trouble, and similarly the convenient wrapping of the POSIX API seems to cause more trouble than it's worth. Did your first attempt fail because the file name was not a complete path? Do that on purpose and see if runInteractiveProcess gives you a useful error message. Engineer some other kind of problem into your copier program, and see what happens to the error message ... oh, rats, it looks like runInteractiveProcess puts unit 2 on another pipe, when you might have worked better for you to leave it the way it was. (This kind of thing is what we call a "user friendly" API, which is why we say "with friends like that, who needs enemies!") Here's how the start process function could be written - import System.Posix.IO import System.Posix.Process startproc = do ip <- createPipe op <- createPipe pid <- forkProcess $ do forRead ip >>= onStdUnit 0 forWrite op >>= onStdUnit 1 executeFile "./copier" False [] Nothing to <- forWrite ip from <- forWrite op return (to, from, pid) where forRead (i, o) = closeFd o >> return i forWrite (i, o) = closeFd i >> return o onStdUnit i fd = do dupTo fd i closeFd fd -- and then for I/O to the file descriptors (remember to supply -- explicit newlines, if the other process is line buffered, e.g. "boo\n", -- But if the other process also uses Posix.readFd, it isn't buffered -- at all, so you don't need newlines. "cat" is in the latter category, -- but most command line applications are in the former, like, say, "awk".) sendrecv to from s = do forkIO $ fdWrite to s >> return () (v, _) <- fdRead from 1024 putStrLn ("recvd: " ++ show v) -- try it Donn
participants (3)
-
Donn Cave
-
mgampkay
-
Poprádi Árpád