<div dir="ltr"><div>Bear in mind that this program will also hang if you write enough data to it. There is an implicit buffer when piping data between processes. When it gets filled the process trying to write to it will simply wait forever. The "cat" you are spawning will wait too because you don't actually read any data. The solution is to perform writing and reading in concurrent fashion. Just try this program:<br>

<br>module Main where<br><br>import System.Process<br>import System.IO<br>import Control.Concurrent<br><br>r n = replicate n '.'<br><br>gs :: Int -> IO String<br>gs n = do<br>  print n<br>  let sp = (proc "cat" [])<br>

              { std_out = CreatePipe, std_in = CreatePipe }<br>  (Just hin, Just hout, _, _) <- createProcess sp<br>  let cb = do<br>             hPutStr hin (r n)<br>             hClose hin<br>  -- forkIO cb<br>  cb<br>

  c <- hGetContents hout<br>  length c `seq` hClose hout<br>  return c<br><br>main = do<br>  print "welcome"<br>  mapM_ gs [ 2 ^ x | x <- [0..20]]<br>  print "goodbye"<br><br></div>Without forkIO it hangs on my system with n = 2^18. If you replace "cb" with "forkIO cb" it will finish without hanging.<br>

<div><br></div><div>Best regards,<br></div><div><div></div></div><div class="gmail_extra">Krzysztof Skrzętnicki<br></div><div class="gmail_extra"><br><div class="gmail_quote">On Mon, May 12, 2014 at 5:00 PM, Mateusz Kowalczyk <span dir="ltr"><<a href="mailto:fuuzetsu@fuuzetsu.co.uk" target="_blank">fuuzetsu@fuuzetsu.co.uk</a>></span> wrote:<br>

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