
I hope you don't mind a bit of self-promotion. My process-streaminghttp://hackage.haskell.org/package/process-streaminglibrary provides helper functions for process http://hackage.haskell.org/package/process based on the pipeshttp://hackage.haskell.org/package/pipesstreaming library. The cat example would be written like this (taken verbatim from the tutorial): example6 = exitCode show $ execute3 (shell "cat") show (surely . useProducer $ yield "aaaaaa\naaaaa") (separate (encoding T.decodeIso8859_1 ignoreLeftovers $ surely $ T.toLazyM) nop ) Returns:
*Right ((),("aaaaaa\naaaaa",()))*
Writing stdin is done concurrently with the reading of stdout. When an exception is encountered, the library ensures that the handles are closed, the extant concurrent threads terminated, and the external process killed. Also stderr is drained even if you ignore it, to avoid deadlocks due to full buffers. http://hackage.haskell.org/package/process-streaming-0.0.1.1 http://hackage.haskell.org/package/process-streaming-0.0.1.1/docs/System-Pro... http://productivedetour.blogspot.com.es/2014/02/process-pipes-process-stream... On Monday, May 12, 2014 4:56:46 PM UTC+2, 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’.
-- Mateusz K. _______________________________________________ Haskell-Cafe mailing list Haskel...@haskell.org javascript: http://www.haskell.org/mailman/listinfo/haskell-cafe