Safe Haskell | None |
---|---|
Language | GHC2021 |
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
- pprPanic :: HasCallStack => String -> SDoc -> a
- panicDoc :: String -> SDoc -> a
- sorryDoc :: String -> SDoc -> a
- pgmErrorDoc :: String -> SDoc -> a
- assertPprPanic :: HasCallStack => SDoc -> a
- assertPpr :: HasCallStack => Bool -> SDoc -> a -> a
- assertPprMaybe :: HasCallStack => Maybe SDoc -> a -> a
- assertPprM :: (HasCallStack, Monad m) => m Bool -> SDoc -> m ()
- massertPpr :: (HasCallStack, Applicative m) => Bool -> SDoc -> m ()
- callStackDoc :: HasCallStack => SDoc
- prettyCallStackDoc :: CallStack -> SDoc
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- backtraceDesired :: e -> Bool
- 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
- module GHC.Utils.Panic.Plain
GHC exception type
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).
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
Exception GhcException Source # | |
Defined in GHC.Utils.Panic | |
Show GhcException Source # | |
Defined in GHC.Utils.Panic showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # |
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 #
Command error throwing patterns
pprPanic :: HasCallStack => String -> SDoc -> a Source #
Throw an exception saying "bug in GHC" with a callstack
pgmErrorDoc :: String -> SDoc -> a Source #
Throw an exception saying "bug in pgm being compiled" (used for unusual program errors)
Assertions
assertPprPanic :: HasCallStack => 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
assertPprMaybe :: HasCallStack => Maybe SDoc -> a -> a Source #
assertPprM :: (HasCallStack, Monad m) => m Bool -> SDoc -> m () Source #
massertPpr :: (HasCallStack, Applicative m) => Bool -> SDoc -> m () Source #
Call stacks
callStackDoc :: HasCallStack => SDoc Source #
prettyCallStackDoc :: CallStack -> SDoc Source #
Exception utilities
class (Typeable e, Show e) => Exception e where #
Nothing
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
backtraceDesired :: e -> Bool #
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.
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
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.
module GHC.Utils.Panic.Plain