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

Levi Greenspan greenspan.levi at googlemail.com
Fri Aug 7 06:39:19 EDT 2009


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).

In addition to my last e-mail - would you say that blocking SIGVTALRM
in the thread that runs sleep (or poll etc.) is the right thing to do
in order to avoid the problem of getting EINTR? E.g. for the main
thread:

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import Foreign.C.Types
import Control.Concurrent
import System.Posix.Signals
import Control.Monad

blockSIGVTALRM :: IO ()
blockSIGVTALRM = addSignal virtualTimerExpired `liftM` getSignalMask >>=
    blockSignals >> return ()

sleep :: IO ()
sleep = blockSIGVTALRM >> c_sleep 3 >>= print

main :: IO ()
main = sleep

foreign import ccall safe "unistd.h sleep"
    c_sleep :: CUInt -> IO CUInt


How much would the thread scheduling be affected by this?

Many thanks,
Levi


More information about the Haskell-Cafe mailing list