[Haskell-cafe] Ctrl-C handling in Haskell with curl on Linux

Vasyl Pasternak vasyl.pasternak at gmail.com
Thu Sep 24 05:30:46 EDT 2009


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"
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090924/8f123702/attachment.html


More information about the Haskell-Cafe mailing list