System.Posix.Signals weirdness

Simon Marlow marlowsd at gmail.com
Tue Feb 8 12:11:28 CET 2011


 > I'd expect the following program (compiled with ghc and without any
 > specieal flags) to produce
 >
 > 	Just (Exited ExitSuccess)
 > 	True
 >
 > but it produces
 >
 > 	Just (Exited ExitSuccess)
 > 	False
 >
 > on Debian Lenny (ghc-6.8), OpenBSD-current (ghc-6.12.3), OpenBSD-current
 > (ghc=7.0 from the 7.0 branch).
 >
 > 	module Main where
 >
 > 	import Data.IORef
 > 	import System.Posix.Process
 > 	import System.Posix.Signals
 > 	import System.Posix.Unistd
 >
 > 	main = do
 > 		caughtCHLD <- newIORef False
 > 		installHandler sigCHLD (Catch $ writeIORef caughtCHLD True) Nothing
 > 		pid <- forkProcess $ sleep 2 >> return ()
 > 		s <- sleep 8
 > 		getProcessStatus False False pid >>= print
 > 		readIORef caughtCHLD >>= print
 >
 > The sigCHLD handler is never called in this program. Is this expected
 > behaviour? If so, why?

If you change the "sleep" to "threadDelay", you get the expected answer. 
  The reason is that sleep is a foreign call, and in the unthreaded RTS 
no other threads can run while the foreign call is in progress, and that 
includes threads created to handle signals.  When sleep returns, there 
isn't enough time before the main thread exits for the sigCHLD handler 
thread to run.

threadDelay is more friendly and lets the RTS run other threads.

You could also use -threaded, but then the sleep call will be 
interrupted by SIGVTALRM, so using threadDelay is better.

Cheers,
	Simon




More information about the Glasgow-haskell-users mailing list