Bug in IO libraries when sending data through a pipe?

Jens Petersen juhp@01.246.ne.jp
20 Mar 2002 15:00:32 +0900


Jens Petersen <petersen@redhat.com> writes:

> > The problem is that the child process doesn't receive all the data which
> > the parent sends. It's as if "hPutStr vonh txt" sends the data lazily
> > somehow, and "hClose vonh" closes the pipe prematurely.
> > 
> > It varies from run to run exactly which data gets through. If I cause the
> > child process to read all its input immediately, the problem doesn't
> > seem to occur. Normally, it does so gradually, which takes a few seconds.
> > 
> > I'm using GHC 5.02.2
> 
> Quite possibly could be a bug.  Lazy IO is rather subtle I
> think, specially when done across pipes.  I faced some
> similar problem with in POpen recently.  You can see how I
> solved it (worked round it?) by comparing the latest release
> 1.00 with the previous one 0.00.1:
> 
>         http://www.01.246.ne.jp/~juhp/haskell/popenhs/
> 
> In comparison Posix.runProcess allows attaching file handles
> to the in, out and error pipes, which can be written to and
> read from eagerly I suppose.

Also I just rediscovered Manuel Chakravarty's HPL (Haskell
Ports Library), which provides a rather elegant,
sophisticated approach.

        http://www.cse.unsw.edu.au/~chak/haskell/ports/

It compiles fine under ghc-5.02.2, and using the BufferMode
patch included at the end output seems to be ok, but input
of more than 2048 bytes doesn't seem to be being handled
reliably.

Eg with the test program below:

        % test-processes ping localhost

works (with the aforementioned patch below to Processes.hs), but


        % cat 4096 | test-processes cat

[4096 is a file of 4096 chars]
mostly gives no output, but occasionally I see

        Warning: Ports.listenToPort: Attempted to listen to a closed port!

Needs some debugging I guess. :)

Jens


-- ghc -o test-processes `ports-config --cflags --libs` test-processes.hs
module Main
where
import Processes
import Ports
import IO (openFile, hGetContents, IOMode(..), hSetBuffering, BufferMode(..))
import Monad (unless)

main	:: IO()
main = do
     inpt <- getContents
     withPorts [] $ \ (cmd:args) ->
       do
       outpt <- newPort ' '
       errpt <- newPort ' '
       let p = proc cmd args
       p inpt outpt errpt
       putStrLn "output:"
       out <- listenToPort outpt
       mapM_ putStrLn $ lines out
       putStrLn "error:"
       errclosed <- isClosedPort errpt
       unless errclosed $
	 do
	 err <- listenToPort errpt
	 putStr err
       putStrLn "test finished"


Index: Processes.hs
===================================================================
RCS file: /home/chakcvs/cvs/ports/lib/Processes.hs,v
retrieving revision 1.7
diff -u -r1.7 Processes.hs
--- Processes.hs	2001/07/04 16:15:52	1.7
+++ Processes.hs	2002/03/20 05:28:33
@@ -145,6 +145,8 @@
   stdoutWriteHandle <- fdToHandle stdoutWriteFD
   stderrReadHandle  <- fdToHandle stderrReadFD
   stderrWriteHandle <- fdToHandle stderrWriteFD
+  hSetBuffering stdoutReadHandle  LineBuffering
+  hSetBuffering stderrReadHandle  LineBuffering
   --
   -- the child must close the pipe ends that it doesn't use (especially, the
   -- write end)