[Haskell-cafe] Re: FFI: Problem with Signal Handler Interruptions

Levi Greenspan greenspan.levi at googlemail.com
Thu Aug 6 07:10:09 EDT 2009


Hi Simon,

Many thanks for your reply. I am not actually using sleep in my code.
I only used it for here for highlighting the problem. It will be the
same when using poll(2) for instance. Does this mean that because of
SIGVTALRM I can always get an EINTR when calling a foreign function
that blocks on a system call?

Cheers,
Levi

On Thu, Aug 6, 2009 at 12:17 PM, Simon Marlow<marlowsd at gmail.com> wrote:
> The SIGVTALRM signal is delivered to one (random) thread in the program, so
> I imagine it just isn't being delivered to the thread that runs your second
> call to sleep.  (the main Haskell thread is a "bound thread" and hence gets
> an OS thread to itself).
>
> Is there some reason you can't use threadDelay?  threadDelay is much more
> friendly: it doesn't require another OS thread for each sleeping Haskell
> thread.
>
> Cheers,
>        Simon
>
> On 05/08/2009 17:01, Levi Greenspan wrote:
>>
>> Nobody?
>>
>> On Tue, Aug 4, 2009 at 10:06 AM, Levi
>> Greenspan<greenspan.levi at googlemail.com>  wrote:
>>>
>>> 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