Bug in IO libraries when sending data through a pipe?
Manuel M. T. Chakravarty
chak@cse.unsw.edu.au
Thu, 04 Apr 2002 23:45:03 +1000
Jens Petersen <juhp@01.246.ne.jp> wrote,
> Jens Petersen <petersen@redhat.com> writes:
>
> 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,
Why LineBuffering? Doesn't really change anything for me
(same GHC version).
> but input
> of more than 2048 bytes doesn't seem to be being handled
> reliably.
[..]
> mostly gives no output, but occasionally I see
>
> Warning: Ports.listenToPort: Attempted to listen to a closed port!
>
> Needs some debugging I guess. :)
I guess, it needs more documentation. Your test program is
wrong in two places.
The function `listenToPort' starts to listens at the given
port exactly when `listenToPort' is executed; ie, any data
that goes over the port earlier will not be received in the
stream that this call to `listenToPort' returns.
You wrote
> outpt <- newPort ' '
> errpt <- newPort ' '
> let p = proc cmd args
> p inpt outpt errpt
> putStrLn "output:"
> out <- listenToPort outpt
As the processes `cmd' is fork()ed in a separate thread, it
may already have finshed its business until you get to
`listenToPort outpt', which means you have missed all the
data. For similar reasons
> errclosed <- isClosedPort errpt
> unless errclosed $
> do
> err <- listenToPort errpt
isn't recommended.
I changed your program to what I have appended. It then
works for me for the
% cat 4096 | test-processes cat
test...except that I sometimes get a "Broken Pipe". So, I
guess, I have to do some debugging after all (plus improve
the documentation).
Cheers,
Manuel
PS: I'll add your program to the ports/tests/ directory if
you don't mind.
-=-
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 ' '
out <- listenToPort outpt
err <- listenToPort errpt
let p = proc cmd args
p inpt outpt errpt
putStrLn "output:"
mapM_ putStrLn $ lines out
putStrLn "error:"
putStr err
putStrLn "test finished"