| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Utils.Panic
Description
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.
Synopsis
- data GhcException
- showGhcException :: SDocContext -> GhcException -> ShowS
- showGhcExceptionUnsafe :: GhcException -> ShowS
- throwGhcException :: GhcException -> a
- throwGhcExceptionIO :: GhcException -> IO a
- handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a
- progName :: String
- pgmError :: String -> a
- panic :: String -> a
- pprPanic :: HasCallStack => String -> SDoc -> a
- assertPanic :: String -> Int -> a
- assertPprPanic :: HasCallStack => String -> Int -> SDoc -> a
- sorry :: String -> a
- trace :: String -> a -> a
- panicDoc :: String -> SDoc -> a
- sorryDoc :: String -> SDoc -> a
- pgmErrorDoc :: String -> SDoc -> a
- cmdLineError :: String -> a
- cmdLineErrorIO :: String -> IO a
- callStackDoc :: HasCallStack => SDoc
- class (Typeable e, Show e) => Exception e where- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
 
- showException :: Exception e => e -> String
- safeShowException :: Exception e => e -> IO String
- try :: Exception e => IO a -> IO (Either e a)
- tryMost :: IO a -> IO (Either SomeException a)
- throwTo :: Exception e => ThreadId -> e -> IO ()
- withSignalHandlers :: ExceptionMonad m => m a -> m a
Documentation
data GhcException Source #
GHC's own exception type error messages all take the form:
<location>: <error>
If the location is on the command line, or in GHC itself, then <location>="ghc". All of the error types below correspond to a <location> of "ghc", except for ProgramError (where the string is assumed to contain a location already, so we don't print one).
Constructors
| Signal Int | Some other fatal signal (SIGHUP,SIGTERM) | 
| UsageError String | Prints the short usage msg after the error | 
| CmdLineError String | A problem with the command line arguments, but don't print usage. | 
| Panic String | The  | 
| PprPanic String SDoc | |
| Sorry String | The user tickled something that's known not to work yet, but we're not counting it as a bug. | 
| PprSorry String SDoc | |
| InstallationError String | An installation problem. | 
| ProgramError String | An error in the user's code, probably. | 
| PprProgramError String SDoc | 
Instances
| Show GhcException Source # | |
| Defined in GHC.Utils.Panic Methods showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # | |
| Exception GhcException Source # | |
| Defined in GHC.Utils.Panic Methods toException :: GhcException -> SomeException # fromException :: SomeException -> Maybe GhcException # displayException :: GhcException -> String # | |
showGhcException :: SDocContext -> GhcException -> ShowS Source #
Append a description of the given exception to this string.
showGhcExceptionUnsafe :: GhcException -> ShowS Source #
Append a description of the given exception to this string.
Note that this uses defaultSDocContext, which doesn't use the options
 set by the user via DynFlags.
throwGhcException :: GhcException -> a Source #
throwGhcExceptionIO :: GhcException -> IO a Source #
handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a Source #
pprPanic :: HasCallStack => String -> SDoc -> a Source #
Throw an exception saying "bug in GHC" with a callstack
assertPanic :: String -> Int -> a Source #
Throw a failed assertion exception for a given filename and line number.
assertPprPanic :: HasCallStack => String -> Int -> SDoc -> a Source #
Panic with an assertion failure, recording the given file and line number. Should typically be accessed with the ASSERT family of macros
The trace function outputs the trace message given as its first argument,
before returning the second argument as its result.
For example, this returns the value of f x but first outputs the message.
>>>let x = 123; f = show>>>trace ("calling f with x = " ++ show x) (f x)"calling f with x = 123 123"
The trace function should only be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.
pgmErrorDoc :: String -> SDoc -> a Source #
Throw an exception saying "bug in pgm being compiled" (used for unusual program errors)
cmdLineError :: String -> a Source #
cmdLineErrorIO :: String -> IO a Source #
callStackDoc :: HasCallStack => SDoc Source #
class (Typeable e, Show e) => Exception e where #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException
    deriving Show
instance Exception MyExceptionThe default method definitions in the Exception class do what we need
in this case. You can now throw and catch ThisException and
ThatException as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler
data SomeCompilerException = forall e . Exception e => SomeCompilerException e
instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e
instance Exception SomeCompilerException
compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException
compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a
---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler
data SomeFrontendException = forall e . Exception e => SomeFrontendException e
instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e
instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException
frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException
frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a
---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception
data MismatchedParentheses = MismatchedParentheses
    deriving Show
instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromExceptionWe can now catch a MismatchedParentheses exception as
MismatchedParentheses, SomeFrontendException or
SomeCompilerException, but not other types, e.g. IOException:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses
Minimal complete definition
Nothing
Methods
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
Render this exception value in a human-friendly manner.
Default implementation: show
Since: base-4.8.0.0
Instances
showException :: Exception e => e -> String Source #
Show an exception as a string.
safeShowException :: Exception e => e -> IO String Source #
Show an exception which can possibly throw other exceptions. Used when displaying exception thrown within TH code.
try :: Exception e => IO a -> IO (Either e a) #
Similar to catch, but returns an Either result which is
 ( if no exception of type Right a)e was raised, or (
 if an exception of type Left ex)e was raised and its value is ex.
 If any other type of exception is raised than it will be propogated
 up to the next enclosing exception handler.
try a = catch (Right `liftM` a) (return . Left)
tryMost :: IO a -> IO (Either SomeException a) Source #
Like try, but pass through UserInterrupt and Panic exceptions. Used when we want soft failures when reading interface files, for example. TODO: I'm not entirely sure if this is catching what we really want to catch
throwTo :: Exception e => ThreadId -> e -> IO () #
throwTo raises an arbitrary exception in the target thread (GHC only).
Exception delivery synchronizes between the source and target thread:
throwTo does not return until the exception has been raised in the
target thread. The calling thread can thus be certain that the target
thread has received the exception.  Exception delivery is also atomic
with respect to other exceptions. Atomicity is a useful property to have
when dealing with race conditions: e.g. if there are two threads that
can kill each other, it is guaranteed that only one of the threads
will get to kill the other.
Whatever work the target thread was doing when the exception was raised is not lost: the computation is suspended until required by another thread.
If the target thread is currently making a foreign call, then the
exception will not be raised (and hence throwTo will not return)
until the call has completed.  This is the case regardless of whether
the call is inside a mask or not.  However, in GHC a foreign call
can be annotated as interruptible, in which case a throwTo will
cause the RTS to attempt to cause the call to return; see the GHC
documentation for more details.
Important note: the behaviour of throwTo differs from that described in
the paper "Asynchronous exceptions in Haskell"
(http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm).
In the paper, throwTo is non-blocking; but the library implementation adopts
a more synchronous design in which throwTo does not return until the exception
is received by the target thread.  The trade-off is discussed in Section 9 of the paper.
Like any blocking operation, throwTo is therefore interruptible (see Section 5.3 of
the paper).  Unlike other interruptible operations, however, throwTo
is always interruptible, even if it does not actually block.
There is no guarantee that the exception will be delivered promptly,
although the runtime will endeavour to ensure that arbitrary
delays don't occur.  In GHC, an exception can only be raised when a
thread reaches a safe point, where a safe point is where memory
allocation occurs.  Some loops do not perform any memory allocation
inside the loop and therefore cannot be interrupted by a throwTo.
If the target of throwTo is the calling thread, then the behaviour
is the same as throwIO, except that the exception
is thrown as an asynchronous exception.  This means that if there is
an enclosing pure computation, which would be the case if the current
IO operation is inside unsafePerformIO or unsafeInterleaveIO, that
computation is not permanently replaced by the exception, but is
suspended as if it had received an asynchronous exception.
Note that if throwTo is called with the current thread as the
target, the exception will be thrown even if the thread is currently
inside mask or uninterruptibleMask.
withSignalHandlers :: ExceptionMonad m => m a -> m a Source #
Temporarily install standard signal handlers for catching ^C, which just throw an exception in the current thread.