control-c only caught once -- bug?

Hi, The second time I press control-c, it isn't caught -- the program exits instead. Why? (The context is, I'm writing an interactive program where calculations may take a long time. Control-c during a calculation should return the user to a prompt. As things stand, this can only be done once -- the second calculation so interrupted causes the whole program to exit.) $ ./ctrlctest ^Cuser interrupt ^C -- program exits! $ cat ctrlctest.hs module Main where import Control.Concurrent (threadDelay) import qualified Control.Exception as C main :: IO () main = do (threadDelay 1000000 >> return ()) `C.catch` (\e -> print (e::C.AsyncException)) main $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.0.3 $ uname -mrsv Darwin 11.2.0 Darwin Kernel Version 11.2.0: Tue Aug 9 20:54:00 PDT 2011; root:xnu-1699.24.8~1/RELEASE_X86_64 x86_64 $ file ctrlctest ctrlctest: Mach-O executable i386

On Fri, Oct 28, 2011 at 12:47 PM, Brian Johnson
Hi, The second time I press control-c, it isn't caught -- the program exits instead. Why?
Interesting -- this works as you want with runghc, but it works as you describe when compiled with ghc --make. (under ghc 7.0.3 here as well.) --Rogan
(The context is, I'm writing an interactive program where calculations may take a long time. Control-c during a calculation should return the user to a prompt. As things stand, this can only be done once -- the second calculation so interrupted causes the whole program to exit.) $ ./ctrlctest ^Cuser interrupt ^C -- program exits! $ cat ctrlctest.hs module Main where import Control.Concurrent (threadDelay) import qualified Control.Exception as C main :: IO () main = do (threadDelay 1000000 >> return ()) `C.catch` (\e -> print (e::C.AsyncException)) main $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.0.3 $ uname -mrsv Darwin 11.2.0 Darwin Kernel Version 11.2.0: Tue Aug 9 20:54:00 PDT 2011; root:xnu-1699.24.8~1/RELEASE_X86_64 x86_64 $ file ctrlctest ctrlctest: Mach-O executable i386
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Oct 28, 2011 at 6:07 PM, Rogan Creswick
On Fri, Oct 28, 2011 at 12:47 PM, Brian Johnson
wrote: Hi, The second time I press control-c, it isn't caught -- the program exits instead. Why?
Interesting -- this works as you want with runghc, but it works as you describe when compiled with ghc --make. (under ghc 7.0.3 here as well.)
It works fine with runghc / ghc (7.0.3) on WinXP 32-bit. Perhaps it's related to this: http://blogs.embarcadero.com/eboling/2009/11/10/5628

The second time I press control-c, it isn't caught -- the program exits instead. Why?
I don't know why. Same behavior on my platform (Haiku.) While I imagine someone intimately acquainted with RTS signal handling might be able to explain it, I think the real problem is that Control.Exception.Catch isn't a real signal handler. For example, your program doesn't catch SIGHUP, or SIGALRM, or probably anything but SIGINT. The SIGINT handler looks like more of a quirk of the RTS, than a feature whose behavior you should depend on in great detail. I can use System.Posix.Signals.installHandler to catch <ctrl>C (SIGINT) in a repeatable way, on MacOS X, so that's working as it should. If you want it to return control to the user interface, that's going to take some work - for all I know, there may be some way to hook a signal handler up with Control.Exception.catch. Donn

On Sat, Oct 29, 2011 at 9:36 AM, Donn Cave
The SIGINT handler looks like more of a quirk of the RTS, than a feature whose behavior you should depend on in great detail.
I looked into this some more, and found that it is indeed a quirk of the RTS -- an apparently /intentional/ one. From http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Signals: "When the interrupt signal is received, the default behaviour of the runtime is to attempt to shut down the Haskell program gracefully. It does this by calling interruptStgRts() in rts/Schedule.chttp://hackage.haskell.org/trac/ghc/browser/rts/Schedule.c (see Commentary/Rts/Scheduler#ShuttingDownhttp://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Scheduler#ShuttingDo...). If a second interrupt signal is received, then we terminate the process immediately; this is just in case the normal shutdown procedure failed or hung for some reason, the user is always able to stop the process with two control-C keystrokes" While I'm sure someone or ones meant well when designing the RTS to work in this way, I do not agree that this is sensible. It's fine for calculation or utility programs that perform one task and exit, but not for interactive programs such as shells, editors, or anything with a command line interface. IMO, handholding behavior such as this is exactly the sort of thing that risks new Haskell users coming to the conclusion that "Haskell is not intended for real programming projects" -- I know, because I nearly came to this exact conclusion while pulling my hair out trying to figure out what was going on here. Further complicating the matter is that this feature only exists in POSIX environments, i.e. not on Windows. I can use System.Posix.Signals.installHandler to catch <ctrl>C (SIGINT)
in a repeatable way, on MacOS X, so that's working as it should. If you want it to return control to the user interface, that's going to take some work - for all I know, there may be some way to hook a signal handler up with Control.Exception.catch.
Indeed, it's easy to hook up your own signal handler so that ALL keyboard interrupts have the expected behavior of throwing a UserInterrupt exception -- although I would not have thought to do this before learning that the RTS is "broken" in this regard: import Control.Exception as C import Control.Concurrent import System.Posix.Signals main = do tid <- myThreadId installHandler keyboardSignal (Catch (throwTo tid UserInterrupt)) Nothing ... -- rest of program Brian

On Sat, Oct 29, 2011 at 12:18 PM, Brian Johnson < brianjohnsonhaskellcafe@gmail.com> wrote:
From http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Signals:
"When the interrupt signal is received, the default behaviour of the runtime is to attempt to shut down the Haskell program gracefully. It does this by calling interruptStgRts() in rts/Schedule.chttp://hackage.haskell.org/trac/ghc/browser/rts/Schedule.c (see Commentary/Rts/Scheduler#ShuttingDownhttp://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Scheduler#ShuttingDo...). If a second interrupt signal is received, then we terminate the process immediately; this is just in case the normal shutdown procedure failed or hung for some reason, the user is always able to stop the process with two control-C keystrokes"
On further thought, there is something sensible here: the RTS might crash while trying to exit. I propose, for POSIX environments, the following change to SIGINT handling: * SIGINT is transformed into UserInterrupt during normal program execution * Once the RTS is committed to exiting, it resets the signal handler for SIGINT so that any additional control-c causes an immediate exit Makes sense? Brian

An interactive program that wants to handle interrupt itself should not rely on default signal behavior, because that has no idea where to stop (and I would argue that attempting to coerce interactive signals into exceptions within the program is not the right way to do things, because they're only superficially similar and oddities like this are the result). If you want to handle signals, handle signals; don't rely on exceptions to do it for you. Using the POSIX model, signals are blocked until the handler either returns or modifies the signal mask explicitly; this prevents a race condition which in this case could happen when a program is running slowly due to some other process slowing the machine down, which could lead to a second SIGINT aborting the program before the program could handle it. (This used to be common on AT&T/v7-derived Unixes which didn't have signal blocking, and is why POSIX adopted the BSD-derived signal model.) If you try to map signals to exceptions, you can't make them behave like an exception (where a second one, received while in the exception handler, is thrown immediately to the outer scope) without losing the ability to handle that signal inside the exception handler (due to the race condition above). (I have a feeling I'm not describing this clearly enough; I'm a bit fuzzy due to not having caught up on sleep fully yet.) Possibly the way to do a higher level signal handler is something similar to "catch": computation `withSignal` $ \sig -> handler where, unlike "catch", the signal is blocked until "handler" finishes unless explicitly unblocked (thus behaving like POSIX signal handlers and avoiding the race condition). (And then comes the question of how, if at all, any of this applies to Windows, which I'm unqualified to answer.) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Quoth Brian Johnson
On further thought, there is something sensible here: the RTS might crash while trying to exit. I propose, for POSIX environments, the following change to SIGINT handling:
* SIGINT is transformed into UserInterrupt during normal program execution * Once the RTS is committed to exiting, it resets the signal handler for SIGINT so that any additional control-c causes an immediate exit
The picture I get from the commentary (below) is that we're talking about shutting down, one way or another - either "gracefully", or if that isn't making satisfactory progress, abruptly on the second ^C. Because the user entered a keyboard interrupt, and the program hasn't installed a signal handler for it. If you have your own shutdown procedure that you want to have happen at that time, then it would make sense to me to catch this exception for that purpose. If you want to handle keyboard interrupts, throughout the lifetime of the program process, then you should handle the signals. If the SIGINT handler described below is too confusing, then I would solve that problem by simply removing it. Programs written in other languages simply abort on unhandled signals, and I'm a little skeptical that there's any reliable way to improve on that. We're just teaching people to press <ctrl>C twice if it's a Haskell program. Donn
From http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Signals:
"When the interrupt signal is received, the default behaviour of the runtime is to attempt to shut down the Haskell program gracefully. It does this by calling interruptStgRts() in rts/Schedule.chttp://hackage.haskell.org/trac/ghc/browser/rts/Schedule.c (see Commentary/Rts/Scheduler#ShuttingDownhttp://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Scheduler#ShuttingDo...). If a second interrupt signal is received, then we terminate the process immediately; this is just in case the normal shutdown procedure failed or hung for some reason, the user is always able to stop the process with two control-C keystrokes"
participants (5)
-
Brandon Allbery
-
Brian Johnson
-
Donn Cave
-
Giovanni Tirloni
-
Rogan Creswick