
Hello, I need to interact with some other program, and wrote the following code: module Main where import System.Process import System.IO main :: IO () main = do putStrLn "Running proc9..." (inp,out,err,pid) <- runInteractiveProcess "prog1" [] Nothing Nothing hSetBuffering inp LineBuffering hSetBuffering out LineBuffering hSetBuffering err LineBuffering hPutStrLn inp "1" a <- hGetLine out hPutStrLn inp a a <- hGetLine out waitForProcess pid putStrLn a But it does not work as I expected. As long as there is no need to put some input after having received some output it is no problem, but real interaction seems not possible. Is there a solution to work with the Handles as with stdin,... ? using ghc 6.6 on Windows Thanks in advance for your help.

h. wrote:
But it does not work as I expected. As long as there is no need to put some input after having received some output it is no problem, but real interaction seems not possible.
Right, this particular program works just for a particular interaction. What real interaction do you have in mind? I assure you all interactions are possible, but first you have to settle on one.

I have in mind something as connections via pipes to the chils's stdin, stdout and stderr, but the stream library just supports internal pipes, and posix require Unix. By this means it's not possible to request, receive and than respond,... with the process. Does there exist an alternative way?

h._h._h._:
I have in mind something as connections via pipes to the chils's stdin, stdout and stderr, but the stream library just supports internal pipes, and posix require Unix. By this means it's not possible to request, receive and than respond,... with the process. Does there exist an alternative way?
I usually use System.Process for this kind of thing. http://haskell.org/ghc/docs/latest/html/libraries/base/System-Process.html -- Don

Donald Bruce Stewart
I usually use System.Process for this kind of thing.
http://haskell.org/ghc/docs/latest/html/libraries/base/System-Process.html
As I wrote in "process": [...] As long as there is no need to put some input after having received some output it is no problem [...] module Main where import System.Process import System.IO main :: IO () main = do putStrLn "Running proc9..." (inp,out,err,pid) <- runInteractiveProcess "prog1" [] Nothing Nothing hSetBuffering inp LineBuffering hSetBuffering out LineBuffering hSetBuffering err LineBuffering hPutStrLn inp "1" a <- hGetLine out hPutStrLn inp a a <- hGetLine out waitForProcess pid putStrLn a [...] If it basically works, what goes wrong in my programm?

Quoth h., nevermore,
If it basically works, what goes wrong in my programm?
Maybe something to do with compiler flags? I have tried doing inter-process stuff like that and it's the principal place where laziness really trips me up. I haven't yet been able to predict what would happen in any particular situation. D. -- Dougal Stanton

Dougal Stanton wrote:
If it basically works, what goes wrong in my programm?
Maybe something to do with compiler flags?
No. This isn't even a Haskell-related problem, in all likelihood. Bidirectional interaction with another process over a pipe, particularly when the other process is using stdio or an equivalent (i.e. most programs), is a classic and fruitful source of deadlocks. Just because *your* end of each pipe is a line-buffered file handle has no bearing on the *other* process's management of its pair of endpoints. For example, on a Unix-like system, the other process's stdio will block-buffer stdin and stdout by default if it finds that they're not attached to tty-like file descriptors. There are really only two ways to deal with this. The first is to read from the subprocess in a separate thread, but this only works effectively if what you're sending to the other process doesn't depend on what you read back from it (because there's no way of forcing it to send you anything). The second is Unix-specific, and involves talking to the other process via a pseudotty instead of a pair of pipes. This convinces the other process's stdio that you're a terminal, and you get the line-buffering you desire. It's *still* highly deadlock-prone, and not something to do casually. So what you're trying to do looks easy if you've never tried it, but it's actually very fiddly in all but the most trivial of circumstances. The third, and best, way to deal with this problem is to completely avoid it unless you want to spend several hours or days scratching your head.

Bryan O'Sullivan wrote:
Just because *your* end of each pipe is a line-buffered file handle has no bearing on the *other* process's management of its pair of endpoints. For example, on a Unix-like system, the other process's stdio will block-buffer stdin and stdout by default if it finds that they're not attached to tty-like file descriptors.
In case the implications of this aren't clear, let me expand a little. You've got a line-buffered stdout. You write "1+1\n", which sends 4 bytes to the other process. It's got a block-buffered stdin, so it's going to sit in its first read until it receives 512 bytes (or whatever the buffer size is) from you. And an oversized violin, you have a deadlock! The converse bites you, too. You want to read a line from the other process. It writes "1+1\n" to you, but its stdio buffers up the 4 bytes because it hasn't reached the 512-byte watermark. It then tries to read from you, but you're still blocked trying to read the first line (that it hasn't actually sent) from it. Deadlock.

h. wrote:
If it basically works, what goes wrong in my programm?
Well that depends entirely what your program is supposed to do. Your email doesn't tell us (a) what your program was supposed to do or (b) what goes wrong. Therefore we are forced to guess! The following slight variation of your program works fine for me. I don't have anything called 'prog1' on my system, so I used 'bc' which is a calculator program standard on unixes, which works by line-by-line interaction. I varied your program just a tiny bit to get some interesting output: module Main where import System.Process import System.IO main :: IO () main = do putStrLn "Running BC" (inp,out,err,pid) <- runInteractiveProcess "bc" [] Nothing Nothing hSetBuffering inp LineBuffering hSetBuffering out LineBuffering hSetBuffering err LineBuffering hPutStrLn inp "1+3" a <- hGetLine out hPutStrLn inp a a <- hGetLine out hPutStrLn inp "quit" waitForProcess pid putStrLn a This program asks 'bc' to calculate "1+3". The reply is stored in 'a'. Then the program sends 'a' back to bc, effectively asking bc to calculate "4". Since the "4" evaluates just to "4", 'a' gets the value "4" once more. Then I have to send "quit" to bc. That is the command that "bc" interprets as an instruction to quit; without that command, 'waitForProcess pid' will wait forever (it's waiting for bc to quit). Finally my program outputs "4" the result of the last calculation. Is this close to what you're trying to do? Jules

This seemed like a handy thing to have an example of, so I added it to
my growing repo of sample haskell programs and tried running it. But I
was unsuccessful.
Can anyone see what I'm doing wrong?
In case it matters, I'm on a virtualized user-mode-linux shell.
**********************************************
thartman@linodewhyou:~/learning/haskell/inter-process-communication$
cat /proc/version
Linux version 2.4.29-linode39-1um (root@nova1.theshore.net) (gcc
version 3.3.3 20040412 (Red Hat Linux 3.3.3-7)) #1 Wed Jan 19 12:22:14
EST 2005
thartman@linodewhyou:~/learning/haskell/inter-process-communication$
ghc -v 2>&1 | head -n1
Glasgow Haskell Compiler, Version 6.6, for Haskell 98, compiled by GHC
version 6.6
thartman@linodewhyou:~/learning/haskell/inter-process-communication$
cat inter-process-communication.hs
module Main where
import System.Process
import System.IO
main :: IO ()
main = do
putStrLn "Running BC"
(inp,out,err,pid) <- runInteractiveProcess "bc" [] Nothing Nothing
hSetBuffering inp LineBuffering
hSetBuffering out LineBuffering
hSetBuffering err LineBuffering
hPutStrLn inp "1+3"
a <- hGetLine out
hPutStrLn inp a
a <- hGetLine out
hPutStrLn inp "quit"
waitForProcess pid
putStrLn a
thartman@linodewhyou:~/learning/haskell/inter-process-communication$
runghc inter-process-communication.hs
Running BC
*** Exception: waitForProcess: does not exist (No child processes)
thartman@linodewhyou:~/learning/haskell/inter-process-communication$
2007/2/23, Jules Bean
h. wrote:
If it basically works, what goes wrong in my programm?
Well that depends entirely what your program is supposed to do.
Your email doesn't tell us (a) what your program was supposed to do or (b) what goes wrong. Therefore we are forced to guess!
The following slight variation of your program works fine for me. I don't have anything called 'prog1' on my system, so I used 'bc' which is a calculator program standard on unixes, which works by line-by-line interaction. I varied your program just a tiny bit to get some interesting output:
module Main where import System.Process import System.IO
main :: IO () main = do putStrLn "Running BC" (inp,out,err,pid) <- runInteractiveProcess "bc" [] Nothing Nothing hSetBuffering inp LineBuffering hSetBuffering out LineBuffering hSetBuffering err LineBuffering hPutStrLn inp "1+3" a <- hGetLine out hPutStrLn inp a a <- hGetLine out hPutStrLn inp "quit" waitForProcess pid putStrLn a
This program asks 'bc' to calculate "1+3". The reply is stored in 'a'. Then the program sends 'a' back to bc, effectively asking bc to calculate "4". Since the "4" evaluates just to "4", 'a' gets the value "4" once more.
Then I have to send "quit" to bc. That is the command that "bc" interprets as an instruction to quit; without that command, 'waitForProcess pid' will wait forever (it's waiting for bc to quit).
Finally my program outputs "4" the result of the last calculation.
Is this close to what you're trying to do?
Jules _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 23/02/07, Thomas Hartman
This seemed like a handy thing to have an example of, so I added it to my growing repo of sample haskell programs and tried running it. But I was unsuccessful.
Your program works for me both compiled or using runghc: Linux lonlsd62 2.6.9-11.ELsmp #1 SMP Fri May 20 18:26:27 EDT 2005 i686 i686 i386 GNU/Linux Glasgow Haskell Compiler, Version 6.6, for Haskell 98, compiled by GHC version 6.6

Jules Bean
Well that depends entirely what your program is supposed to do.
Your email doesn't tell us (a) what your program was supposed to do or (b) what goes wrong. Therefore we are forced to guess!
The following slight variation of your program works fine for me. I don't have anything called 'prog1' on my system, so I used 'bc' which is a calculator program standard on unixes, which works by line-by-line interaction. I varied your program just a tiny bit to get some interesting output:
module Main where import System.Process import System.IO
main :: IO () main = do putStrLn "Running BC" (inp,out,err,pid) <- runInteractiveProcess "bc" [] Nothing Nothing hSetBuffering inp LineBuffering hSetBuffering out LineBuffering hSetBuffering err LineBuffering hPutStrLn inp "1+3" a <- hGetLine out hPutStrLn inp a a <- hGetLine out hPutStrLn inp "quit" waitForProcess pid putStrLn a
This program asks 'bc' to calculate "1+3". The reply is stored in 'a'. Then the program sends 'a' back to bc, effectively asking bc to calculate "4". Since the "4" evaluates just to "4", 'a' gets the value "4" once more.
Then I have to send "quit" to bc. That is the command that "bc" interprets as an instruction to quit; without that command, 'waitForProcess pid' will wait forever (it's waiting for bc to quit).
Finally my program outputs "4" the result of the last calculation.
Is this close to what you're trying to do?
Jules
Thanks, but I still puzzle over the same problem. I wrote the following lines to test exactely your code: module Main where main :: IO () main = f where f = do a <- getLine if a == "quit" then return () else putStrLn a >> f running the program in the console works without any problems ("1+3" is the result :) ), but with runInteractiveProcess I do not get any output except "Running BC", and every IO action after the first hPutStrLn inp "1+3" is never reached (the program hang-up there - no error is thrown) - thats my problem...

h. wrote:
module Main where main :: IO () main = f where f = do a <- getLine if a == "quit" then return () else putStrLn a >> f
This one also needs to switch to line buffering. Add/Change: import System.IO(stdout, hSetBuffering, BufferMode(LineBuffering)) main = hSetBuffering stdout LineBuffering >> f

Albert Y. C. Lai
h. wrote:
module Main where main :: IO () main = f where f = do a <- getLine if a == "quit" then return () else putStrLn a >> f
This one also needs to switch to line buffering. Add/Change:
import System.IO(stdout, hSetBuffering, BufferMode(LineBuffering)) main = hSetBuffering stdout LineBuffering >> f
Thanks a lot, now it does work! This means just the proc1 program has to be changed and everything will work properly (hopefully - at least the haskell part works :) ).
participants (8)
-
Albert Y. C. Lai
-
Bryan O'Sullivan
-
dons@cse.unsw.edu.au
-
Dougal Stanton
-
h.
-
Joe Thornber
-
Jules Bean
-
Thomas Hartman