signal handling and optimisation
Simon Marlow
simonmar@microsoft.com
Mon, 23 Jun 2003 10:53:38 +0100
=20
> I'm trying to write some code that catches unix signals and turns them
> into GHC exceptions, GHC version 6.0, debian linux
>=20
> Heres my code:
>=20
> ------
> module Main where
> =20
> import Control.Concurrent
> import Control.Exception
> import System.Posix
> import IO=20
> =20
> catchCtrlC :: IO Handler
> catchCtrlC
> =3D do main_thread <- myThreadId
> installHandler sigINT (Catch (handler main_thread)) Nothing
> where
> handler :: ThreadId -> IO ()
> handler main_thread =3D throwTo main_thread=20
> (ErrorCall "Kaboom")
> =20
> main :: IO ()
> main =3D do catchCtrlC=20
> print (f 1)
> =20
> f :: Int -> Int
> f x =3D f (x + 1)
> ------ =20
>=20
> The function "f" is intentionally bogus, I want it to loop so=20
> I have enough time to hit cntrl-C.
You've hit a known bug with concurrency, described in the
Control.Concurrent documentation.
The problem is that context switches only happen when some allocation is
going on: in your f function above, the optimiser turns it into a loop
that does no allocation, so no context switches can happen and the
exception is never delivered.
You probably won't run into this bug in a real program ;-)
Cheers,
Simon