[Haskell-cafe] Re: process
Jules Bean
jules at jellybean.co.uk
Fri Feb 23 07:22:03 EST 2007
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
More information about the Haskell-Cafe
mailing list