| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Utils.Panic.Plain
Description
Defines a simple exception type and utilities to throw it. The
 PlainGhcException type is a subset of the GhcException
 type.  It omits the exception constructors that involve
 pretty-printing via SDoc.
There are two reasons for this:
- To avoid import cycles / use of boot files. GHC.Utils.Outputable has many transitive dependencies. To throw exceptions from these modules, the functions here can be used without introducing import cycles.
 - To reduce the number of modules that need to be compiled to object code when loading GHC into GHCi. See #13101
 
Synopsis
- data PlainGhcException
 - showPlainGhcException :: PlainGhcException -> ShowS
 - panic :: HasCallStack => String -> a
 - sorry :: HasCallStack => String -> a
 - pgmError :: HasCallStack => String -> a
 - cmdLineError :: String -> a
 - cmdLineErrorIO :: String -> IO a
 - assertPanic :: String -> Int -> a
 - assert :: HasCallStack => Bool -> a -> a
 - assertM :: (HasCallStack, Monad m) => m Bool -> m ()
 - massert :: (HasCallStack, Applicative m) => Bool -> m ()
 
Documentation
data PlainGhcException Source #
This type is very similar to GhcException, but it omits
 the constructors that involve pretty-printing via
 SDoc.  Due to the implementation of fromException
 for GhcException, this type can be caught as a
 GhcException.
Note that this should only be used for throwing exceptions, not for
 catching, as GhcException will not be converted to this
 type when catching.
Constructors
| PlainSignal Int | Some other fatal signal (SIGHUP,SIGTERM)  | 
| PlainUsageError String | Prints the short usage msg after the error  | 
| PlainCmdLineError String | A problem with the command line arguments, but don't print usage.  | 
| PlainPanic String | The   | 
| PlainSorry String | The user tickled something that's known not to work yet, but we're not counting it as a bug.  | 
| PlainInstallationError String | An installation problem.  | 
| PlainProgramError String | An error in the user's code, probably.  | 
Instances
| Exception PlainGhcException Source # | |
Defined in GHC.Utils.Panic.Plain Methods toException :: PlainGhcException -> SomeException Source # fromException :: SomeException -> Maybe PlainGhcException Source #  | |
| Show PlainGhcException Source # | |
Defined in GHC.Utils.Panic.Plain  | |
showPlainGhcException :: PlainGhcException -> ShowS Source #
Append a description of the given exception to this string.
panic :: HasCallStack => String -> a Source #
Panics and asserts.
sorry :: HasCallStack => String -> a Source #
Panics and asserts.
pgmError :: HasCallStack => String -> a Source #
Panics and asserts.
cmdLineError :: String -> a Source #
cmdLineErrorIO :: String -> IO a Source #
assertPanic :: String -> Int -> a Source #
Throw a failed assertion exception for a given filename and line number.
assert :: HasCallStack => Bool -> a -> a Source #
massert :: (HasCallStack, Applicative m) => Bool -> m () Source #