Ctrl-C handling in Haskell with curl on Linux

Hi, Yesterday I tried to implement simple tool to download pages, and wanted catch Ctrl-C (and other 'killing' messages) from haskell to handle state saving. Without curl (when I perform some long operation) haskell throws UserInterrupt exception immediately, but if I put long operation, which downloads page from the WEB (from the far-far-away server :) ) than I noticed following issues: - to break my program I have to press Ctrl-C twice - haskell doesn't throw an exception - when I rewrite this code to use signals, haskell, after I press Ctrl-C several times exits with error "too many pending signals" I put the test code in the end of the letter. Shortly the longTask doesn't handle Ctrl-C and longTask' handles it. I couldn't find any solutions to this problem, I am afraid that this problem could occur in other non-native haskell modules (bindings to C libraries) Many thanks in advance, Vasyl pasternak ------------------------------------------ Test code: module Main where import Prelude hiding (catch) import Network.Curl import Control.Exception import Control.Monad import System.IO errorHandler defVal e = do putStrLn $ "Error: " ++ (show (e :: ErrorCall)) return defVal link = "far-far-away-site.com.net" getSite curl l = do r <- do_curl_ curl l method_GET :: IO (CurlResponse) if respCurlCode r /= CurlOK then error "get page failed" else return $ respBody r -- this long task doesn't throw user interrupts longTask = do putStrLn "Long task started" curl <- initialize setopts curl [CurlCookieJar "cookies"] handle (errorHandler ()) $ mapM_ (\_ -> getSite curl link >> return ()) [0..100] return () -- this trows longTask' = do putStrLn "long task started" let fib n = foldr (*) 1 [1..n] h <- openFile "/dev/null" WriteMode -- never ends mapM_ (hPutStr h . show . fib) [1..] return () onAbort e = do let x = show (e :: AsyncException) putStrLn $ "Aborted: " ++ x return () main :: IO () main = do handle onAbort longTask putStrLn "Exiting"

Hello Vasyl, Thursday, September 24, 2009, 1:30:46 PM, you wrote:
I couldn't find any solutions to this problem, I am afraid that this problem could occur in other non-native haskell modules (bindings to C libraries)
look at GHC.ConsoleHandler module -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Sep 24, 2009, at 05:30 , Vasyl Pasternak wrote:
Yesterday I tried to implement simple tool to download pages, and wanted catch Ctrl-C (and other 'killing' messages) from haskell to handle state saving. Without curl (when I perform some long operation) haskell throws UserInterrupt exception immediately, but if I put long operation, which downloads page from the WEB (from the far-far-away server :) ) than I noticed following issues:
You're going to have problems any time a C library installs its own signal handler, which I would expect libcurl to do so it can clean up after itself. This is true even in C-to-C calling; you need a way to hook the signal handler, which some libraries provide in their API and others you just lose. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sep 24, 2009, at 06:20 , Brandon S. Allbery KF8NH wrote:
On Sep 24, 2009, at 05:30 , Vasyl Pasternak wrote:
Yesterday I tried to implement simple tool to download pages, and wanted catch Ctrl-C (and other 'killing' messages) from haskell to handle state saving. Without curl (when I perform some long operation) haskell throws UserInterrupt exception immediately, but if I put long operation, which downloads page from the WEB (from the far-far-away server :) ) than I noticed following issues:
You're going to have problems any time a C library installs its own signal handler, which I would expect libcurl to do so it can clean up after itself. This is true even in C-to-C calling; you need a way to hook the signal handler, which some libraries provide in their API and others you just lose.
Just occurred to me I should clarify: while most exception handling mechanisms support the concept of re-throwing exceptions to outer exception handlers, POSIX signals do not. The best you could hope for in a library routine which handles signals itself is an API hook into the signal handler; next best is the API returning a signal-occurred error/exception value. Note that I have no idea how the equivalent signaling mechanism works on Win32. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Thank you,
You give me and idea, and I fixed this annoying bug - we should only wrap
all
curl code into withCurlDo function, so the longTask function should be
following:
longTask = do
putStrLn "Long task started (curl)"
withCurlDo $ do
curl <- initialize
setopts curl [CurlCookieJar "cookies"]
handle (errorHandler ()) $
mapM_ (\_ -> getSite curl link >> return ()) [0..100]
return ()
Now it works fine and handles interrupts correctly.
Best regards,
Vasyl Pasternak
2009/9/24 Brandon S. Allbery KF8NH
On Sep 24, 2009, at 06:20 , Brandon S. Allbery KF8NH wrote:
On Sep 24, 2009, at 05:30 , Vasyl Pasternak wrote:
Yesterday I tried to implement simple tool to download pages, and wanted catch Ctrl-C (and other 'killing' messages) from haskell to handle state saving. Without curl (when I perform some long operation) haskell throws UserInterrupt exception immediately, but if I put long operation, which downloads page from the WEB (from the far-far-away server :) ) than I noticed following issues:
You're going to have problems any time a C library installs its own signal handler, which I would expect libcurl to do so it can clean up after itself. This is true even in C-to-C calling; you need a way to hook the signal handler, which some libraries provide in their API and others you just lose.
Just occurred to me I should clarify: while most exception handling mechanisms support the concept of re-throwing exceptions to outer exception handlers, POSIX signals do not. The best you could hope for in a library routine which handles signals itself is an API hook into the signal handler; next best is the API returning a signal-occurred error/exception value.
Note that I have no idea how the equivalent signaling mechanism works on Win32.
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (3)
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Vasyl Pasternak