signal handling and optimisation

Bernard James POPE bjpop@cs.mu.OZ.AU
Sat, 21 Jun 2003 00:00:08 +1000 (EST)


Hi All,

I'm trying to write some code that catches unix signals and turns them
into GHC exceptions, GHC version 6.0, debian linux

Heres my code:

------
   module Main where
   
   import Control.Concurrent
   import Control.Exception
   import System.Posix
   import IO 
   
   catchCtrlC :: IO Handler
   catchCtrlC
      = do main_thread <- myThreadId
           installHandler sigINT (Catch (handler main_thread)) Nothing
           where
           handler :: ThreadId -> IO ()
           handler main_thread = throwTo main_thread (ErrorCall "Kaboom")
   
   main :: IO ()
   main = do catchCtrlC 
             print (f 1)
   
   f :: Int -> Int
   f x = f (x + 1)
------   

The function "f" is intentionally bogus, I want it to loop so I have enough
time to hit cntrl-C.

When I compile this with no optimisations:

   ghc --make Sig.hs

I get the desired behaviour, that is soon after I hit cntrl-C I get:

   Fail: Kaboom

However, when I compile with -O:

   touch Sig.hs && ghc --make -O Sig.hs

Now the exception does not appear to be caught. Indeed the program just keeps
on looping.

If a give the program a lot of cntrl-Cs then eventually I get this message:

   a.out: too many pending signals

And the program dies.

Commenting out the call to "catchCtrlC" from within "main" seems to
let GHC's default signal handling mechanism work properly, that is
after (strangley 2) cntrl-Cs the program dies (no message). 

Cheers,
Bernie.