fix warning on Windows
[ghc-hetmet.git] / compiler / utils / Panic.lhs
index b8ab86a..ee06777 100644 (file)
@@ -11,13 +11,13 @@ some unnecessary loops in the module dependency graph.
 \begin{code}
 module Panic  
    ( 
-     GhcException(..), showGhcException, ghcError, progName, 
+     GhcException(..), showGhcException, throwGhcException, handleGhcException,
+     ghcError, progName,
      pgmError,
 
      panic, panicFastInt, assertPanic, trace,
      
-     Exception.Exception(..), showException, try, tryJust, tryMost, tryUser,
-     catchJust, ioErrors, throwTo,
+     Exception.Exception(..), showException, try, tryMost, throwTo,
 
      installSignalHandlers, interruptTargetThread
    ) where
@@ -35,13 +35,12 @@ import System.Posix.Signals
 import GHC.ConsoleHandler
 #endif
 
-import Control.Exception
-import Control.Concurrent ( MVar, ThreadId, withMVar, newMVar )
+import Exception
+import Control.Concurrent ( MVar, ThreadId, withMVar, newMVar, modifyMVar_,
+                            myThreadId )
 import Data.Dynamic
-import qualified Control.Exception as Exception
 import Debug.Trace     ( trace )
 import System.IO.Unsafe        ( unsafePerformIO )
-import System.IO.Error ( isUserError )
 import System.Exit
 import System.Environment
 \end{code}
@@ -50,7 +49,7 @@ GHC's own exception type.
 
 \begin{code}
 ghcError :: GhcException -> a
-ghcError e = Exception.throwDyn e
+ghcError e = Exception.throw e
 
 -- error messages all take the form
 --
@@ -65,6 +64,7 @@ data GhcException
   = PhaseFailed String         -- name of phase 
                ExitCode        -- an external phase (eg. cpp) failed
   | Interrupted                        -- someone pressed ^C
+  | Signal Int                  -- some other fatal signal (SIGHUP,SIGTERM)
   | UsageError String          -- prints the short usage msg after the error
   | CmdLineError String                -- cmdline prob, but doesn't print usage
   | Panic String               -- the `impossible' happened
@@ -72,18 +72,17 @@ data GhcException
   | ProgramError String                -- error in the user's code, probably
   deriving Eq
 
+instance Exception GhcException
+
 progName :: String
 progName = unsafePerformIO (getProgName)
 {-# NOINLINE progName #-}
 
 short_usage :: String
 short_usage = "Usage: For basic information, try the `--help' option."
-   
-showException :: Exception.Exception -> String
--- Show expected dynamic exceptions specially
-showException (Exception.DynException d) | Just e <- fromDynamic d 
-                                        = show (e::GhcException)
-showException other_exn                         = show other_exn
+
+showException :: Exception e => e -> String
+showException = show
 
 instance Show GhcException where
   showsPrec _ e@(ProgramError _) = showGhcException e
@@ -110,12 +109,20 @@ showGhcException (InstallationError str)
    = showString str
 showGhcException (Interrupted)
    = showString "interrupted"
+showGhcException (Signal n)
+   = showString "signal: " . shows n
 showGhcException (Panic s)
    = showString ("panic! (the 'impossible' happened)\n"
                 ++ "  (GHC version " ++ cProjectVersion ++ " for " ++ TargetPlatform_NAME ++ "):\n\t"
                 ++ s ++ "\n\n"
                 ++ "Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug\n")
 
+throwGhcException :: GhcException -> a
+throwGhcException = Exception.throw
+
+handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a
+handleGhcException = ghandle
+
 ghcExceptionTc :: TyCon
 ghcExceptionTc = mkTyCon "GhcException"
 {-# NOINLINE ghcExceptionTc #-}
@@ -127,8 +134,8 @@ Panics and asserts.
 
 \begin{code}
 panic, pgmError :: String -> a
-panic    x = Exception.throwDyn (Panic x)
-pgmError x = Exception.throwDyn (ProgramError x)
+panic    x = throwGhcException (Panic x)
+pgmError x = throwGhcException (ProgramError x)
 
 --  #-versions because panic can't return an unboxed int, and that's
 -- what TAG_ is with GHC at the moment.  Ugh. (Simon)
@@ -148,27 +155,27 @@ assertPanic file line =
 -- exceptions.  Used when we want soft failures when reading interface
 -- files, for example.
 
-tryMost :: IO a -> IO (Either Exception.Exception a)
-tryMost action = do r <- try action; filter r
-  where
-   filter (Left e@(Exception.DynException d))
-           | Just ghc_ex <- fromDynamic d
-               = case ghc_ex of
-                   Interrupted -> Exception.throw e
-                   Panic _     -> Exception.throw e
-                   _other      -> return (Left e)
-   filter other 
-     = return other
-
--- | tryUser is like try, but catches only UserErrors.
--- These are the ones that are thrown by the TcRn monad 
--- to signal an error in the program being compiled
-tryUser :: IO a -> IO (Either Exception.Exception a)
-tryUser action = tryJust tc_errors action
-  where 
-       tc_errors e@(Exception.IOException ioe) | isUserError ioe = Just e
-       tc_errors _other = Nothing
-\end{code}     
+-- XXX I'm not entirely sure if this is catching what we really want to catch
+tryMost :: IO a -> IO (Either SomeException a)
+tryMost action = do r <- try action
+                    case r of
+                        Left se ->
+                            case fromException se of
+                                -- Some GhcException's we rethrow,
+                                Just Interrupted -> throwIO se
+                                Just (Signal _)  -> throwIO se
+                                Just (Panic _)   -> throwIO se
+                                -- others we return
+                                Just _           -> return (Left se)
+                                Nothing ->
+                                    case fromException se of
+                                        -- All IOExceptions are returned
+                                        Just (_ :: IOException) ->
+                                            return (Left se)
+                                        -- Anything else is rethrown
+                                        Nothing -> throwIO se
+                        Right v -> return (Right v)
+\end{code}
 
 Standard signal handlers for catching ^C, which just throw an
 exception in the target thread.  The current target thread is
@@ -178,18 +185,27 @@ installSignalHandlers.
 \begin{code}
 installSignalHandlers :: IO ()
 installSignalHandlers = do
+  main_thread <- myThreadId
+  modifyMVar_ interruptTargetThread (return . (main_thread :))
+
   let
-      interrupt_exn = Exception.DynException (toDyn Interrupted)
+      interrupt_exn = (toException Interrupted)
 
       interrupt = do
        withMVar interruptTargetThread $ \targets ->
          case targets of
           [] -> return ()
           (thread:_) -> throwTo thread interrupt_exn
+
   --
 #if !defined(mingw32_HOST_OS)
-  installHandler sigQUIT (Catch interrupt) Nothing 
-  installHandler sigINT  (Catch interrupt) Nothing
+  _ <- installHandler sigQUIT  (Catch interrupt) Nothing 
+  _ <- installHandler sigINT   (Catch interrupt) Nothing
+  -- see #3656; in the future we should install these automatically for
+  -- all Haskell programs in the same way that we install a ^C handler.
+  let fatal_signal n = throwTo main_thread (Signal (fromIntegral n))
+  _ <- installHandler sigHUP   (Catch (fatal_signal sigHUP))  Nothing
+  _ <- installHandler sigTERM  (Catch (fatal_signal sigTERM)) Nothing
   return ()
 #else
   -- GHC 6.3+ has support for console events on Windows
@@ -201,7 +217,7 @@ installSignalHandlers = do
       sig_handler Break    = interrupt
       sig_handler _        = return ()
 
-  installHandler (Catch sig_handler)
+  _ <- installHandler (Catch sig_handler)
   return ()
 #endif