%
% (c) The University of Glasgow 2006
% (c) The GRASP Project, Glasgow University, 1992-2000
%
Defines basic functions for printing error messages.
It's hard to put these functions anywhere else without causing
some unnecessary loops in the module dependency graph.
\begin{code}
module Panic (
GhcException(..), showGhcException,
throwGhcException, throwGhcExceptionIO,
handleGhcException,
progName,
pgmError,
panic, sorry, panicFastInt, assertPanic, trace,
panicDoc, sorryDoc, panicDocFastInt, pgmErrorDoc,
Exception.Exception(..), showException, safeShowException, try, tryMost, throwTo,
installSignalHandlers,
pushInterruptTargetThread, popInterruptTargetThread
) where
#include "HsVersions.h"
import Outputable (SDoc)
import Config
import FastTypes
import Exception
import Control.Concurrent
import Data.Dynamic
#if __GLASGOW_HASKELL__ < 705
import Data.Maybe
#endif
import Debug.Trace ( trace )
import System.IO.Unsafe
import System.Exit
import System.Environment
#ifndef mingw32_HOST_OS
import System.Posix.Signals
#endif
#if defined(mingw32_HOST_OS)
import GHC.ConsoleHandler
#endif
import GHC.Stack
#if __GLASGOW_HASKELL__ >= 705
import System.Mem.Weak ( Weak, deRefWeak )
#endif
data GhcException
= PhaseFailed String
ExitCode
| Signal Int
| UsageError String
| CmdLineError String
| Panic String
| PprPanic String SDoc
| Sorry String
| PprSorry String SDoc
| InstallationError String
| ProgramError String
| PprProgramError String SDoc
deriving (Typeable)
instance Exception GhcException
instance Show GhcException where
showsPrec _ e@(ProgramError _) = showGhcException e
showsPrec _ e@(CmdLineError _) = showString "<command line>: " . showGhcException e
showsPrec _ e = showString progName . showString ": " . showGhcException e
progName :: String
progName = unsafePerformIO (getProgName)
short_usage :: String
short_usage = "Usage: For basic information, try the `--help' option."
showException :: Exception e => e -> String
showException = show
safeShowException :: Exception e => e -> IO String
safeShowException e = do
r <- try (return $! forceList (showException e))
case r of
Right msg -> return msg
Left e' -> safeShowException (e' :: SomeException)
where
forceList [] = []
forceList xs@(x : xt) = x `seq` forceList xt `seq` xs
showGhcException :: GhcException -> String -> String
showGhcException exception
= case exception of
UsageError str
-> showString str . showChar '\n' . showString short_usage
PhaseFailed phase code
-> showString "phase `" . showString phase .
showString "' failed (exitcode = " . shows (int_code code) .
showString ")"
CmdLineError str -> showString str
PprProgramError str _ ->
showGhcException (ProgramError (str ++ "\n<<details unavailable>>"))
ProgramError str -> showString str
InstallationError str -> showString str
Signal n -> showString "signal: " . shows n
PprPanic s _ ->
showGhcException (Panic (s ++ "\n<<details unavailable>>"))
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"
PprSorry s _ ->
showGhcException (Sorry (s ++ "\n<<details unavailable>>"))
Sorry s
-> showString $
"sorry! (unimplemented feature or known bug)\n"
++ " (GHC version " ++ cProjectVersion ++ " for " ++ TargetPlatform_NAME ++ "):\n\t"
++ s ++ "\n"
where int_code code =
case code of
ExitSuccess -> (0::Int)
ExitFailure x -> x
throwGhcException :: GhcException -> a
throwGhcException = Exception.throw
throwGhcExceptionIO :: GhcException -> IO a
throwGhcExceptionIO = Exception.throwIO
handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a
handleGhcException = ghandle
panic, sorry, pgmError :: String -> a
panic x = unsafeDupablePerformIO $ do
stack <- ccsToStrings =<< getCurrentCCS x
if null stack
then throwGhcException (Panic x)
else throwGhcException (Panic (x ++ '\n' : renderStack stack))
sorry x = throwGhcException (Sorry x)
pgmError x = throwGhcException (ProgramError x)
panicDoc, sorryDoc, pgmErrorDoc :: String -> SDoc -> a
panicDoc x doc = throwGhcException (PprPanic x doc)
sorryDoc x doc = throwGhcException (PprSorry x doc)
pgmErrorDoc x doc = throwGhcException (PprProgramError x doc)
panicFastInt :: String -> FastInt
panicFastInt s = case (panic s) of () -> _ILIT(0)
panicDocFastInt :: String -> SDoc -> FastInt
panicDocFastInt s d = case (panicDoc s d) of () -> _ILIT(0)
assertPanic :: String -> Int -> a
assertPanic file line =
Exception.throw (Exception.AssertionFailed
("ASSERT failed! file " ++ file ++ ", line " ++ show line))
tryMost :: IO a -> IO (Either SomeException a)
tryMost action = do r <- try action
case r of
Left se ->
case fromException se of
Just (Signal _) -> throwIO se
Just (Panic _) -> throwIO se
Just _ -> return (Left se)
Nothing ->
case fromException se of
Just (_ :: IOException) ->
return (Left se)
Nothing -> throwIO se
Right v -> return (Right v)
installSignalHandlers :: IO ()
installSignalHandlers = do
main_thread <- myThreadId
pushInterruptTargetThread main_thread
let
interrupt_exn = (toException UserInterrupt)
interrupt = do
mt <- peekInterruptTargetThread
case mt of
Nothing -> return ()
Just t -> throwTo t interrupt_exn
#if !defined(mingw32_HOST_OS)
_ <- installHandler sigQUIT (Catch interrupt) Nothing
_ <- installHandler sigINT (Catch interrupt) Nothing
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
let sig_handler ControlC = interrupt
sig_handler Break = interrupt
sig_handler _ = return ()
_ <- installHandler (Catch sig_handler)
return ()
#endif
#if __GLASGOW_HASKELL__ >= 705
interruptTargetThread :: MVar [Weak ThreadId]
interruptTargetThread = unsafePerformIO (newMVar [])
pushInterruptTargetThread :: ThreadId -> IO ()
pushInterruptTargetThread tid = do
wtid <- mkWeakThreadId tid
modifyMVar_ interruptTargetThread $ return . (wtid :)
peekInterruptTargetThread :: IO (Maybe ThreadId)
peekInterruptTargetThread =
withMVar interruptTargetThread $ loop
where
loop [] = return Nothing
loop (t:ts) = do
r <- deRefWeak t
case r of
Nothing -> loop ts
Just t -> return (Just t)
#else
interruptTargetThread :: MVar [ThreadId]
interruptTargetThread = unsafePerformIO (newMVar [])
pushInterruptTargetThread :: ThreadId -> IO ()
pushInterruptTargetThread tid = do
modifyMVar_ interruptTargetThread $ return . (tid :)
peekInterruptTargetThread :: IO (Maybe ThreadId)
peekInterruptTargetThread =
withMVar interruptTargetThread $ return . listToMaybe
#endif
popInterruptTargetThread :: IO ()
popInterruptTargetThread =
modifyMVar_ interruptTargetThread $
\tids -> return $! case tids of [] -> []
(_:ts) -> ts
\end{code}