After using forkProcess the child cannot read from stdin (except for data
already in the buffer). Using forkProcessAll or foreign importing C's fork
makes the problem go away. This applies to Solaris and GHC 6.0, I have not
tested other platforms.

Example program:

> module Main where

> import Monad
> import IO
> import System.Posix

> main = do
>   mPid <- forkProcess
>   case mPid of
>     Nothing ->  -- Child.
>       forwardStdin
>     Just pid -> do  -- Parent.
>       getProcessStatus True False pid
>       return ()

> forwardStdin = do
>   eof <- isEOF
>   when (not eof) $ do
>     c <- getChar
>     putChar c
>     forwardStdin

Test output:

$ echo "apa" | ./Test
apa
$ ./Test
asdfasdf
^CTest: interrupted
$

/NAD
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to