[Haskell-cafe] control-c only caught once -- bug?

Brian Johnson brianjohnsonhaskellcafe at gmail.com
Fri Oct 28 21:47:16 CEST 2011


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111028/5d82a99b/attachment.htm>


More information about the Haskell-Cafe mailing list