[Haskell-cafe] FFI: Problem with Signal Handler Interruptions
Levi Greenspan
greenspan.levi at googlemail.com
Tue Aug 4 04:06:16 EDT 2009
Dear list members,
In February this year there was a posting "Why does sleep not work?"
(http://www.haskell.org/pipermail/haskell-cafe/2009-February/055400.html).
The problem was apparently caused by signal handler interruptions. I
noticed the same (not with sleep though) when doing some FFI work and
compiled the following test program:
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Foreign.C.Types
import Control.Concurrent
sleep :: IO ()
sleep = c_sleep 3 >>= print
fails :: IO ()
fails = sleep
works :: IO ()
works = forkIO sleep >> return ()
main :: IO ()
main = fails >> works >> threadDelay 3000000
foreign import ccall unsafe "unistd.h sleep"
c_sleep :: CUInt -> IO CUInt
When compiled with GHC (using --make -threaded), it will print 3
immediately (from the "fails" function) and after 3 seconds 0 (from
"works"), before it finally exits. man sleep(3) tells me that sleep
returns 0 on success and if interrupted by a signal the number of
seconds left to sleep. Clearly "fails" is interrupted by a signal
(which seems to be SIGVTALRM). This was mentioned in the discussion
from February.
I would like to know why "fails" fails and "works" works, i.e. why is
"sleep" not interrupted when run in a separate thread? And what can be
done to make "sleep" work in the main thread? It wouldn't be wise to
block SIGVTALRM, wouldn't it?
Many thanks,
Levi
More information about the Haskell-Cafe
mailing list