ghci and ghc -threaded broken with pipes & forking

Simon Marlow simonmarhaskell at gmail.com
Thu Mar 1 10:06:22 EST 2007


Ok, what happens here is that in the forked process there is only a single 
thread, the runtime kills all the other threads (as advertised).  Unfortunately 
this includes the I/O manager thread, so as soon as you do some I/O in the 
forked process, you block.

It might be possible to fix this, but not easily I'm afraid, because the I/O 
manager doesn't currently have a way to restart after it's been killed.  We 
could implement that, though.  I'll create a bug report.

On a more general note, forkProcess is known to be hairy - simply the fact that 
it kills all the other threads in the system in the forked process means that 
there's a good supply of means to shoot yourself in the foot, even accidentally. 
  John - perhaps there's another way to achieve what you want?

Cheers,
	Simon

Jeremy Shaw wrote:
> Hello,
> 
> Here is a simplified example that seems to exhibit the same behaviour,
> unless I screwed up:
> 
> --->
> 
> module Main where
> 
> import System.Posix
> import System.IO
> import System.Exit
> 
> main =
>     do putStrLn "running..."
>        (stdinr, stdinw) <- createPipe
>        (stdoutr, stdoutw) <- createPipe
>        pid <- forkProcess $ do hw <- fdToHandle stdoutw
>                                hr <- fdToHandle stdinr
>                                closeFd stdinw
>                                hGetContents hr >>= hPutStr hw
>                                hClose hr
>                                hClose hw
>                                exitImmediately ExitSuccess
>        closeFd stdoutw
>        closeFd stdinw
>        hr2 <- fdToHandle stdoutr
>        hGetContents hr2 >>= putStr
>        getProcessStatus True False pid >>= print
> 
> <---
> 
> Compiling with:
> 
> ghc --make -no-recomp test3.hs -o test3 && ./test3
> 
> works. But compiling with:
> 
> ghc --make -no-recomp -threaded test3.hs -o test3 && ./test3
> 
> results in a hang. If you comment out the "hGetContents hr >>=" and
> change 'hPutStr hw' to 'hPutStr hw "hi"', then it seems to work ok.
> 
> As you suggested, it seems that hGetContents is not ever seeing the
> EOF when -threaded is enabled. I think it gets 'Resource temporarily
> unavailable' instead. So, it keeps retrying.
> 
> Assuming I have recreated the same bug, we at least have a simpiler
> test case now...
> 
> j.
> 
> At Wed, 28 Feb 2007 11:15:04 -0600,
> John Goerzen wrote:
>> Hi,
>>
>> I've been hitting my head against a wall for the past couple of days
>> trying to figure out why my shell-like pipeline code kept hanging.  I
>> found fd leakage (file descriptors not being closed), which disrupts EOF
>> detection and can lead to deadlocks.  I just couldn't find the problem.
>>
>> I finally tried compiling my test with ghc instead of running it in
>> ghci.
>>
>> And poof, it worked fine the first time.
>>
>> I tried asking on #haskell, and got the suggestion that ghci uses
>> -threaded.  I tried compiling my test program with ghc -threaded, and
>> again, same deadlock.  My program never calls forkIO or forkOS or any
>> other threading code.
>>
>> You can see my test case with:
>>
>> darcs get '--tag=glasgow ml' http://darcs.complete.org/hsh
>> ghc -fglasgow-exts --make -o test2 test2.hs
>>
>> That'll run fine.  If you add -threaded, it will hang.
>>
>> Ideas?
>>
>> Thanks,
>>
>> -- John
>>
>>
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users at haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 



More information about the Glasgow-haskell-users mailing list