| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Exception
Contents
Synopsis
- throwIO :: (MonadIO m, Exception e) => e -> m a
 - class Monad m => MonadThrow (m :: * -> *) where
 - ioError :: IOError -> IO a
 - userError :: String -> IOError
 - exitWith :: ExitCode -> IO a
 - exitFailure :: IO a
 - exitSuccess :: IO a
 - die :: String -> IO a
 - catch :: (MonadUnliftIO m, Exception e) => m a -> (e -> m a) -> m a
 - catchAny :: MonadUnliftIO m => m a -> (SomeException -> m a) -> m a
 - catches :: MonadUnliftIO m => m a -> [Handler m a] -> m a
 - data Handler (m :: * -> *) a where
 - catchJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a
 - handle :: (MonadUnliftIO m, Exception e) => (e -> m a) -> m a -> m a
 - handleJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a
 - try :: (MonadUnliftIO m, Exception e) => m a -> m (Either e a)
 - tryAny :: MonadUnliftIO m => m a -> m (Either SomeException a)
 - tryJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a)
 - tryIO :: MonadUnliftIO m => m a -> m (Either IOException a)
 - bracket :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c
 - bracket_ :: MonadUnliftIO m => m a -> m b -> m c -> m c
 - bracketOnError :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c
 - finally :: MonadUnliftIO m => m a -> m b -> m a
 - onException :: MonadUnliftIO m => m a -> m b -> m a
 - data MaskingState
 - mask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
 - mask_ :: MonadUnliftIO m => m a -> m a
 - uninterruptibleMask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
 - uninterruptibleMask_ :: MonadUnliftIO m => m a -> m a
 - getMaskingState :: IO MaskingState
 - interruptible :: IO a -> IO a
 - allowInterrupt :: IO ()
 - data SomeException where
 - class (Typeable e, Show e) => Exception e where
 - mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a
 - data ExitCode
 - data IOException
 - data SomeAsyncException where
 - data AsyncException
 - asyncExceptionToException :: Exception e => e -> SomeException
 - asyncExceptionFromException :: Exception e => SomeException -> Maybe e
 
Throwing exceptions
throwIO :: (MonadIO m, Exception e) => e -> m a #
Synchronously throw the given exception.
Since: unliftio-0.1.0.0
class Monad m => MonadThrow (m :: * -> *) where #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Minimal complete definition
Methods
throwM :: Exception e => e -> m a #
Throw an exception. Note that this throws when this action is run in
 the monad m, not when it is applied. It is a generalization of
 Control.Exception's throwIO.
Should satisfy the law:
throwM e >> f = throwM e
Instances
Throwing specific exceptions
exitWith :: ExitCode -> IO a #
Computation exitWith code throws ExitCode code.
 Normally this terminates the program, returning code to the
 program's caller.
On program termination, the standard Handles stdout and
 stderr are flushed automatically; any other buffered Handles
 need to be flushed manually, otherwise the buffered data will be
 discarded.
A program that fails in any other way is treated as if it had
 called exitFailure.
 A program that terminates successfully without calling exitWith
 explicitly is treated as if it had called exitWith ExitSuccess.
As an ExitCode is not an IOError, exitWith bypasses
 the error handling in the IO monad and cannot be intercepted by
 catch from the Prelude.  However it is a SomeException, and can
 be caught using the functions of Control.Exception.  This means
 that cleanup computations added with bracket
 (from Control.Exception) are also executed properly on exitWith.
Note: in GHC, exitWith should be called from the main program
 thread in order to exit the process.  When called from another
 thread, exitWith will throw an ExitException as normal, but the
 exception will not cause the process itself to exit.
exitFailure :: IO a #
The computation exitFailure is equivalent to
 exitWith (ExitFailure exitfail),
 where exitfail is implementation-dependent.
exitSuccess :: IO a #
The computation exitSuccess is equivalent to
 exitWith ExitSuccess, It terminates the program
 successfully.
Write given error message to stderr and terminate with exitFailure.
Since: base-4.8.0.0
Catching exceptions
catch :: (MonadUnliftIO m, Exception e) => m a -> (e -> m a) -> m a #
Unlifted catch, but will not catch asynchronous exceptions.
Since: unliftio-0.1.0.0
catchAny :: MonadUnliftIO m => m a -> (SomeException -> m a) -> m a #
catch specialized to catch all synchronous exception.
Since: unliftio-0.1.0.0
catches :: MonadUnliftIO m => m a -> [Handler m a] -> m a #
Same as upstream catches, but will not catch
 asynchronous exceptions.
Since: unliftio-0.1.0.0
catchJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a #
handle :: (MonadUnliftIO m, Exception e) => (e -> m a) -> m a -> m a #
Flipped version of catch.
Since: unliftio-0.1.0.0
handleJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a #
Flipped catchJust.
Since: unliftio-0.1.0.0
try :: (MonadUnliftIO m, Exception e) => m a -> m (Either e a) #
Unlifted try, but will not catch asynchronous exceptions.
Since: unliftio-0.1.0.0
tryAny :: MonadUnliftIO m => m a -> m (Either SomeException a) #
try specialized to catch all synchronous exceptions.
Since: unliftio-0.1.0.0
tryJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a) #
A variant of try that takes an exception predicate to select
 which exceptions are caught.
Since: unliftio-0.1.0.0
tryIO :: MonadUnliftIO m => m a -> m (Either IOException a) #
try specialized to only catching IOExceptions.
Since: unliftio-0.1.0.0
Cleanup
bracket :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c #
Async safe version of bracket.
Since: unliftio-0.1.0.0
bracket_ :: MonadUnliftIO m => m a -> m b -> m c -> m c #
Async safe version of bracket_.
Since: unliftio-0.1.0.0
bracketOnError :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c #
Async safe version of bracketOnError.
Since: unliftio-0.1.0.0
finally :: MonadUnliftIO m => m a -> m b -> m a #
Async safe version of finally.
Since: unliftio-0.1.0.0
onException :: MonadUnliftIO m => m a -> m b -> m a #
Async safe version of onException.
Since: unliftio-0.1.0.0
Masking exceptions
data MaskingState #
Describes the behaviour of a thread when an asynchronous exception is received.
Constructors
| Unmasked | asynchronous exceptions are unmasked (the normal state)  | 
| MaskedInterruptible | the state during   | 
| MaskedUninterruptible | the state during   | 
Instances
| Eq MaskingState | |
Defined in GHC.IO  | |
| Show MaskingState | |
Defined in GHC.IO Methods showsPrec :: Int -> MaskingState -> ShowS # show :: MaskingState -> String # showList :: [MaskingState] -> ShowS #  | |
mask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b #
Unlifted version of mask.
Since: unliftio-0.1.0.0
mask_ :: MonadUnliftIO m => m a -> m a #
Unlifted version of mask_.
Since: unliftio-0.1.0.0
uninterruptibleMask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b #
Unlifted version of uninterruptibleMask.
Since: unliftio-0.1.0.0
uninterruptibleMask_ :: MonadUnliftIO m => m a -> m a #
Unlifted version of uninterruptibleMask_.
Since: unliftio-0.1.0.0
getMaskingState :: IO MaskingState #
Returns the MaskingState for the current thread.
interruptible :: IO a -> IO a #
Allow asynchronous exceptions to be raised even inside mask, making
 the operation interruptible (see the discussion of "Interruptible operations"
 in Exception).
When called outside mask, or inside uninterruptibleMask, this
 function has no effect.
Since: base-4.9.0.0
allowInterrupt :: IO () #
When invoked inside mask, this function allows a masked
 asynchronous exception to be raised, if one exists.  It is
 equivalent to performing an interruptible operation (see
 #interruptible), but does not involve any actual blocking.
When called outside mask, or inside uninterruptibleMask, this
 function has no effect.
Since: base-4.4.0.0
Exception types
data SomeException where #
The SomeException type is the root of the exception type hierarchy.
When an exception of type e is thrown, behind the scenes it is
encapsulated in a SomeException.
Constructors
| SomeException :: SomeException | 
Instances
| Show SomeException | Since: base-3.0  | 
Defined in GHC.Exception Methods showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS #  | |
| Exception SomeException | Since: base-3.0  | 
Defined in GHC.Exception Methods toException :: SomeException -> SomeException # fromException :: SomeException -> Maybe SomeException # displayException :: SomeException -> String #  | |
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
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
mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a #
This function maps one exception into another as proposed in the paper "A semantics for imprecise exceptions".
Defines the exit codes that a program can return.
Constructors
| ExitSuccess | indicates successful termination;  | 
| ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system).  | 
Instances
| Eq ExitCode | |
| Ord ExitCode | |
Defined in GHC.IO.Exception  | |
| Read ExitCode | |
| Show ExitCode | |
| Generic ExitCode | |
| Exception ExitCode | Since: base-4.1.0.0  | 
Defined in GHC.IO.Exception Methods toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String #  | |
| NFData ExitCode | Since: deepseq-1.4.2.0  | 
Defined in Control.DeepSeq  | |
| Serialise ExitCode | Since: serialise-0.2.0.0  | 
| type Rep ExitCode | |
Defined in GHC.IO.Exception  | |
data IOException #
Exceptions that occur in the IO monad.
 An IOException records a more specific error type, a descriptive
 string and maybe the handle that was used when the error was
 flagged.
Instances
| Eq IOException | Since: base-4.1.0.0  | 
Defined in GHC.IO.Exception  | |
| Show IOException | Since: base-4.1.0.0  | 
Defined in GHC.IO.Exception Methods showsPrec :: Int -> IOException -> ShowS # show :: IOException -> String # showList :: [IOException] -> ShowS #  | |
| Exception IOException | Since: base-4.1.0.0  | 
Defined in GHC.IO.Exception Methods toException :: IOException -> SomeException # fromException :: SomeException -> Maybe IOException # displayException :: IOException -> String #  | |
| Error IOException | |
Defined in Control.Monad.Trans.Error  | |
| MonadError IOException IO | |
Defined in Control.Monad.Error.Class  | |
Asynchronous exceptions
data SomeAsyncException where #
Superclass for asynchronous exceptions.
Since: base-4.7.0.0
Constructors
| SomeAsyncException :: SomeAsyncException | 
Instances
| Show SomeAsyncException | Since: base-4.7.0.0  | 
Defined in GHC.IO.Exception Methods showsPrec :: Int -> SomeAsyncException -> ShowS # show :: SomeAsyncException -> String # showList :: [SomeAsyncException] -> ShowS #  | |
| Exception SomeAsyncException | Since: base-4.7.0.0  | 
Defined in GHC.IO.Exception Methods toException :: SomeAsyncException -> SomeException # fromException :: SomeException -> Maybe SomeAsyncException #  | |
data AsyncException #
Asynchronous exceptions.
Constructors
| StackOverflow | The current thread's stack exceeded its limit. Since an exception has been raised, the thread's stack will certainly be below its limit again, but the programmer should take remedial action immediately.  | 
| HeapOverflow | The program's heap is reaching its limit, and the program should take action to reduce the amount of live data it has. Notes: 
  | 
| ThreadKilled | This exception is raised by another thread
 calling   | 
| UserInterrupt | This exception is raised by default in the main thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console).  | 
Instances
| Eq AsyncException | |
Defined in GHC.IO.Exception Methods (==) :: AsyncException -> AsyncException -> Bool # (/=) :: AsyncException -> AsyncException -> Bool #  | |
| Ord AsyncException | |
Defined in GHC.IO.Exception Methods compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # max :: AsyncException -> AsyncException -> AsyncException # min :: AsyncException -> AsyncException -> AsyncException #  | |
| Show AsyncException | Since: base-4.1.0.0  | 
Defined in GHC.IO.Exception Methods showsPrec :: Int -> AsyncException -> ShowS # show :: AsyncException -> String # showList :: [AsyncException] -> ShowS #  | |
| Exception AsyncException | Since: base-4.7.0.0  | 
Defined in GHC.IO.Exception Methods toException :: AsyncException -> SomeException #  | |
asyncExceptionToException :: Exception e => e -> SomeException #
Since: base-4.7.0.0
asyncExceptionFromException :: Exception e => SomeException -> Maybe e #
Since: base-4.7.0.0