
Hi all, I'm playing with signal handlers on Win32. I found a good post on signal handlers but it works with System.Posix.Signals which on Win32 is empty. Blog is here: http://therning.org/magnus/archives/285 I tried to adapt this code to GHC.ConsoleHandler, the Win32 counterpart of System.Posix.Signals. The code: ===================================== module Main where --import System.Posix.Signals import GHC.ConsoleHandler import Control.Concurrent import Control.Concurrent.MVar import System -- ControlC increments counter handler :: MVar (Int, Bool) -> ConsoleEvent -> IO () handler mi ControlC = do (i, exit) <- takeMVar mi putStrLn "In ControlC handler" putMVar mi ((i + 1), False) -- Break sets Bool to True to stop application handler mi Break = do (i, exit) <- takeMVar mi putStrLn "In Break handler" putMVar mi (i, True) -- Ignore other signals handler _ _ = do return () doNothing :: MVar (Int, Bool) -> IO () doNothing mi = do threadDelay 1000000 (i, exit) <- takeMVar mi if exit then do putStrLn "Good bye!" exitWith ExitSuccess else do putStrLn $ "Repeating " ++ (show i) main :: IO () main = do mi <- newMVar (0, False) installHandler (Catch $ handler mi) sequence_ $ repeat $ doNothing mi ===================================== It compiles but when run I receive this: Repeating 0 SignalsText.exe: <<loop>> First iteration is executed but then it gets trapped in what looks like a dead lock. If I remove the installation of the signal handler to just have an infinite loop (comment out installHandler ...) I get this: Repeating 0 SignalsText.exe: thread blocked indefinitely Without the signal handler the code uses only the main and doNothing function and I can't figure out what causes this to block? Something to do with my use of MVar, but what??? Lazy evaluation? Thanks for any advice, Olivier.