[Haskell-cafe] Re: process

Thomas Hartman tphyahoo at gmail.com
Fri Feb 23 07:55:58 EST 2007


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 at linodewhyou:~/learning/haskell/inter-process-communication$
cat /proc/version
Linux version 2.4.29-linode39-1um (root at 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 at 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 at 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 at linodewhyou:~/learning/haskell/inter-process-communication$
runghc inter-process-communication.hs
Running BC
*** Exception: waitForProcess: does not exist (No child processes)
thartman at linodewhyou:~/learning/haskell/inter-process-communication$


2007/2/23, Jules Bean <jules at jellybean.co.uk>:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list