[Haskell-cafe] Reading and writing to handles made with System.Process far too slow
Mateusz Kowalczyk
fuuzetsu at fuuzetsu.co.uk
Mon May 12 15:00:43 UTC 2014
On 05/12/2014 04:56 PM, Mateusz Kowalczyk wrote:
> Hi,
>
> I'm have some business in piping some data and reading some data back
> out of a socket so I thought that I'd just use the ‘socat’ tool. I went
> off to System.Process just to find out that reading and writing are
> taking far too long.
>
> I put together a small example which only requires that you have ‘cat’
> on your system:
>
>
> {-# LANGUAGE UnicodeSyntax #-}
> module Uzbl.WithSource where
>
> import GHC.IO.Handle ( hPutStr, hGetContents, hSetBuffering
> , BufferMode(..))
> import System.Process ( createProcess, proc
> , StdStream(CreatePipe), std_out, std_in)
>
> gs ∷ IO String
> gs = do
> let sp = (proc "cat" [])
> { std_out = CreatePipe, std_in = CreatePipe }
> (Just hin, Just hout, _, _) ← createProcess sp
> -- hSetBuffering hin NoBuffering
> -- hSetBuffering hout NoBuffering
> hPutStr hin "Test data"
> hGetContents hout
>
>
> All this should effectively do is to give you back "Test data". While it
> *does* do that, it takes far too long. When I run ‘gs’, it will start to
> (lazily) print the result, printing nothing but opening ‘"’ and then
> after about 2-3 seconds printing the rest and finishing.
>
> If we set buffering on the in-handle (hin) to NoBuffering, we get a
> slightly different behaviour: pretty much straight away we'll have
> ‘"Test data’ but then it will wait for the same amount of time to
> conclude that it's the end of the response. Changing buffering mode on
> ‘hout’ seems to make no difference. Setting precise number in a
> BlockBuffering seems to be no improvement and in the actual application
> I will not know how long the data I'm piping in and out will be.
>
> GHC 7.8.2, process-1.2.2.0; I'm running ‘gs’ in GHCi. It seems that if I
> change the module name to Main, make ‘main = gs >>= putStrLn’, compile
> the file and run it, it just hangs there! If I add a newline at the end,
> it will print but the program will not finish. This makes me think that
> perhaps I should be closing handles somewhere (but if I try inside the
> function, I get no output, thanks lazy I/O).
>
> What I would expect this program to do is to produce same result as
> ‘print "Test data" | cat’.
>
As it often happens, I solved it straight away after posting to the
list. Here's the program that behaves how I wanted it to from the start:
gs ∷ IO String
gs = do
let sp = (proc "cat" [])
{ std_out = CreatePipe, std_in = CreatePipe }
(Just hin, Just hout, _, _) ← createProcess sp
hPutStr hin "Test data"
hClose hin
c ← hGetContents hout
length c `seq` hClose hout
return c
--
Mateusz K.
More information about the Haskell-Cafe
mailing list