control-monad-exception-0.11.4: Explicitly typed, checked exceptions with stack traces

Safe HaskellSafe
LanguageHaskell98

Control.Monad.Exception.Throws

Description

Defines the Throws binary relationship between types.

Synopsis

Documentation

class Exception e => Throws e l Source #

Throws is a type level binary relationship used to model a list of exceptions.

There is only one case in which the user must add further instances to Throws. If your sets of exceptions are hierarchical then you need to teach Throws about the hierarchy.

Subtyping
As there is no way to automatically infer the subcases of an exception, they have to be encoded manually mirroring the hierarchy defined in the defined Exception instances. For example, the following instance encodes that MyFileNotFoundException is a subexception of MyIOException :
instance Throws MyFileNotFoundException (Caught MyIOException l)

Throws is not a transitive relation and every ancestor relation must be explicitly encoded.

                                                           --   TopException
                                                           --         |
  instance Throws MidException   (Caught TopException l)   --         |
                                                           --   MidException
  instance Throws ChildException (Caught MidException l)   --         |
  instance Throws ChildException (Caught TopException l)   --         |
                                                           --  ChildException

Note that SomeException is automatically an ancestor of every other exception type.

Instances
UncaughtException e => Throws e NoExceptions Source # 
Instance details

Defined in Control.Monad.Exception.Base

Exception e => Throws e AnyException Source # 
Instance details

Defined in Control.Monad.Exception.Base

Exception e => Throws e (Caught SomeException l) Source #

SomeException is at the top of the exception hierarchy . Capturing SomeException captures every possible exception

Instance details

Defined in Control.Monad.Exception.Throws

Exception e => Throws e (Caught e l) Source # 
Instance details

Defined in Control.Monad.Exception.Throws

Throws e l => Throws e (Caught e' l) Source # 
Instance details

Defined in Control.Monad.Exception.Throws

Throws SomeException (Caught SomeException l) Source # 
Instance details

Defined in Control.Monad.Exception.Throws

data Caught e l Source #

A type level witness of a exception handler.

Instances
Exception e => Throws e (Caught SomeException l) Source #

SomeException is at the top of the exception hierarchy . Capturing SomeException captures every possible exception

Instance details

Defined in Control.Monad.Exception.Throws

Exception e => Throws e (Caught e l) Source # 
Instance details

Defined in Control.Monad.Exception.Throws

Throws e l => Throws e (Caught e' l) Source # 
Instance details

Defined in Control.Monad.Exception.Throws

Throws SomeException (Caught SomeException l) Source # 
Instance details

Defined in Control.Monad.Exception.Throws

(Exception e, Monad m) => MonadCatch e (EMT (Caught e l) m) (EMT l m) Source # 
Instance details

Defined in Control.Monad.Exception.Pure

Methods

catch :: EMT (Caught e l) m a -> (e -> EMT l m a) -> EMT l m a Source #

catchWithSrcLoc :: EMT (Caught e l) m a -> ([String] -> e -> EMT l m a) -> EMT l m a Source #

(Exception e, MonadBaseControl IO m) => MonadCatch e (EMT (Caught e l) m) (EMT l m) Source # 
Instance details

Defined in Control.Monad.Exception.IO

Methods

catch :: EMT (Caught e l) m a -> (e -> EMT l m a) -> EMT l m a Source #

catchWithSrcLoc :: EMT (Caught e l) m a -> ([String] -> e -> EMT l m a) -> EMT l m a Source #

newtype CheckedException l Source #

CheckedException adds a phantom type parameter l to SomeException