Cleaning up after the Close button is pressed

Hi everyone, I posted previously on haskell-beginners about an issue which would have been better directed to this list. Since then, I have revisited the issue and am now even less certain of its cause. I have to perform cleanup when my application terminates. GHC.ConsoleHandler handles cleanup from Ctrl-C and Ctrl-Break very nicely under Windows. My sample handler and main function are shown at [1]. When I press Ctrl-C and Ctrl-Break during threadDelay, messages are written to console_event.log as I expected. When I press the Close button during threadDelay, no message is written to console_event.log. Am I missing something fundamental about handling the Close button or installing handlers? In case it makes a difference, I'm using GHC 6.12.3 under Windows XP. Thanks, Colin [1] module Main where import Control.Concurrent (threadDelay) import GHC.ConsoleHandler import System.IO onConsoleEventReceived :: ConsoleEvent -> IO () onConsoleEventReceived event = withFile "console_event.log" AppendMode $ \ file -> do hPutStrLn file $ case event of ControlC -> "Received Ctrl-C event" Break -> "Received Ctrl-Break event" Close -> "Received X button event" _ -> "Received other console event" hFlush file main :: IO () main = installHandler (Catch onConsoleEventReceived) >> threadDelay (20*1000000)

On 20/01/2011 05:27, Colin Hume wrote:
Hi everyone,
I posted previously on haskell-beginners about an issue which would have been better directed to this list. Since then, I have revisited the issue and am now even less certain of its cause.
I have to perform cleanup when my application terminates. GHC.ConsoleHandler handles cleanup from Ctrl-C and Ctrl-Break very nicely under Windows. My sample handler and main function are shown at [1].
When I press Ctrl-C and Ctrl-Break during threadDelay, messages are written to console_event.log as I expected. When I press the Close button during threadDelay, no message is written to console_event.log. Am I missing something fundamental about handling the Close button or installing handlers?
In case it makes a difference, I'm using GHC 6.12.3 under Windows XP.
I don't know a great deal about this, but if you think it might be a bug please report it at http://hackage.haskell.org/trac/ghc/newticket?type=bug giving as much information as you can. Cheers, Simon
participants (2)
-
Colin Hume
-
Simon Marlow