exceptions-checked-0.0.1: Statically Checked Exceptions

Safe HaskellNone
LanguageHaskell2010

Control.Exception.Checked

Contents

Description

This module provides an API to statically check exceptions. The design is heavily derived from Pepe Iborra's control-monad-exception package and supporting paper Explicitly typed exceptions for Haskell.

One improvement is the delegation of exception handling to the safe-exceptions library (instead of Control.Exception) for improved handling of synchronous versus asynchronous exceptions.

Example Usage

If we have the following exceptions:

>>> :{
data FooE = FooE deriving (Show, Typeable)
data BarE = BarE deriving (Show, Typeable)
data BazE = BazE deriving (Show, Typeable)
instance Exception FooE
instance Exception BarE
instance Exception BazE
:}

We could define a function that throws one exception with Throws and throw:

>>> :{
throwsFoo :: Throws FooE e => CheckedIO e a
throwsFoo = throw FooE
:}

In cases throwing multiple exceptions, we can use ThrowsAll with GHC's DataKinds extension, for a compact syntax:

>>> :{
throwsFooBarBaz :: ThrowsAll '[FooE, BarE, BazE] e => CheckedIO e a
throwsFooBarBaz = throw FooE *> throw BarE *> throw BazE
:}

You can start checking a computation such as IO you already have in hand with throwsNone, throws, and throwsAll.

We can handle one of these exceptions with catch:

>>> :{
action :: ThrowsAll '[FooE, BazE] e => CheckedIO e ()
action = throwsFooBarBaz `catch` (\(_::BarE) -> pure ())
:}

We can handle more of these exceptions with catches and <::>:

>>> :{
action' :: ThrowsAll '[FooE, BazE] e => CheckedIO e ()
action' = throwsFooBarBaz
        `catches` (\(_::BarE) -> throw FooE)
             <::> (\(_::FooE) -> throw BazE)
:}

But the compiler prevents us from running it since our ThrowsAll constraint still indicates unhandled exceptions:

>>> runChecked action'
...
...prevents the constraint ...(Throws FooE ...)... from being solved...
...

But if we handle everything (note we can use <:> with a final <::> to chain as many handlers as required)

>>> :{
handled :: CheckedIO e ()
handled = throwsFooBarBaz
        `catches` (\(_::BazE) -> throwsNone $ print "handledBaz")
             <:>  (\(_::BarE) -> throwsNone $ print "handledBar")
             <::> (\(_::FooE) -> throwsNone $ print "handledFoo")
:}

then we can run it with runChecked:

>>> runChecked handled
"handledFoo"

If you like, you could chain on a finalizer on your action too with finally:

>>> :{
handled' :: CheckedIO e ()
handled' = throwsFooBarBaz
        `catches` (\(_::BazE) -> throwsNone $ print "handledBaz")
             <:>  (\(_::BarE) -> throwsNone $ print "handledBar")
             <::> (\(_::FooE) -> throwsNone $ print "handledFoo")
        `finally` (throwsNone $ print "finalized")
:}
>>> runChecked handled'
"handledFoo"
"finalized"

Hopefully that's enough to get you started and you can follow the types of the other exposed functions in this module to figure out the rest.

Regarding “Impure” Exceptions From Partial Functions

With Checked we can statically check exceptions, but that's still a long way from bridging that gap to totality. The provided Checked type is only useful with base monadic types with instances of MonadCatch or MonadMask. Note this excludes Identity, which means to statically check the kinds of exceptions we get with partial function (which Michael Snoyman has coined as “impure”), we must lift these computations into something like IO or STM.

Synopsis

Types and Type Classes

data Checked e m a Source #

Wrapper type that tracks exceptions.

Exceptions are tracked in the phantom parameter e. In practice, e will remain polymorphic with only Throws constraints on it.

Note that although m a may be a monad transformer stack, we don't want to be able to lift into Checked because we want to avoid casually lifting something that might throw an exception without tracking the possibility safely.

Instances
MonadWriter w m => MonadWriter w (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

writer :: (a, w) -> Checked e m a #

tell :: w -> Checked e m () #

listen :: Checked e m a -> Checked e m (a, w) #

pass :: Checked e m (a, w -> w) -> Checked e m a #

MonadState s m => MonadState s (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

get :: Checked e m s #

put :: s -> Checked e m () #

state :: (s -> (a, s)) -> Checked e m a #

MonadReader r m => MonadReader r (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

ask :: Checked e m r #

local :: (r -> r) -> Checked e m a -> Checked e m a #

reader :: (r -> a) -> Checked e m a #

MonadError e' m => MonadError e' (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

throwError :: e' -> Checked e m a #

catchError :: Checked e m a -> (e' -> Checked e m a) -> Checked e m a #

MFunctor (Checked e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

hoist :: Monad m => (forall a. m a -> n a) -> Checked e m b -> Checked e n b #

Monad m => Monad (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

(>>=) :: Checked e m a -> (a -> Checked e m b) -> Checked e m b #

(>>) :: Checked e m a -> Checked e m b -> Checked e m b #

return :: a -> Checked e m a #

fail :: String -> Checked e m a #

Functor m => Functor (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

fmap :: (a -> b) -> Checked e m a -> Checked e m b #

(<$) :: a -> Checked e m b -> Checked e m a #

MonadFix m => MonadFix (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

mfix :: (a -> Checked e m a) -> Checked e m a #

MonadFail m => MonadFail (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

fail :: String -> Checked e m a #

Applicative m => Applicative (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

pure :: a -> Checked e m a #

(<*>) :: Checked e m (a -> b) -> Checked e m a -> Checked e m b #

liftA2 :: (a -> b -> c) -> Checked e m a -> Checked e m b -> Checked e m c #

(*>) :: Checked e m a -> Checked e m b -> Checked e m b #

(<*) :: Checked e m a -> Checked e m b -> Checked e m a #

Foldable m => Foldable (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

fold :: Monoid m0 => Checked e m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> Checked e m a -> m0 #

foldr :: (a -> b -> b) -> b -> Checked e m a -> b #

foldr' :: (a -> b -> b) -> b -> Checked e m a -> b #

foldl :: (b -> a -> b) -> b -> Checked e m a -> b #

foldl' :: (b -> a -> b) -> b -> Checked e m a -> b #

foldr1 :: (a -> a -> a) -> Checked e m a -> a #

foldl1 :: (a -> a -> a) -> Checked e m a -> a #

toList :: Checked e m a -> [a] #

null :: Checked e m a -> Bool #

length :: Checked e m a -> Int #

elem :: Eq a => a -> Checked e m a -> Bool #

maximum :: Ord a => Checked e m a -> a #

minimum :: Ord a => Checked e m a -> a #

sum :: Num a => Checked e m a -> a #

product :: Num a => Checked e m a -> a #

Traversable m => Traversable (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

traverse :: Applicative f => (a -> f b) -> Checked e m a -> f (Checked e m b) #

sequenceA :: Applicative f => Checked e m (f a) -> f (Checked e m a) #

mapM :: Monad m0 => (a -> m0 b) -> Checked e m a -> m0 (Checked e m b) #

sequence :: Monad m0 => Checked e m (m0 a) -> m0 (Checked e m a) #

Eq1 m => Eq1 (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

liftEq :: (a -> b -> Bool) -> Checked e m a -> Checked e m b -> Bool #

Ord1 m => Ord1 (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

liftCompare :: (a -> b -> Ordering) -> Checked e m a -> Checked e m b -> Ordering #

Read1 m => Read1 (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Checked e m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Checked e m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Checked e m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Checked e m a] #

Show1 m => Show1 (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Checked e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Checked e m a] -> ShowS #

MonadZip m => MonadZip (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

mzip :: Checked e m a -> Checked e m b -> Checked e m (a, b) #

mzipWith :: (a -> b -> c) -> Checked e m a -> Checked e m b -> Checked e m c #

munzip :: Checked e m (a, b) -> (Checked e m a, Checked e m b) #

Alternative m => Alternative (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

empty :: Checked e m a #

(<|>) :: Checked e m a -> Checked e m a -> Checked e m a #

some :: Checked e m a -> Checked e m [a] #

many :: Checked e m a -> Checked e m [a] #

MonadPlus m => MonadPlus (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

mzero :: Checked e m a #

mplus :: Checked e m a -> Checked e m a -> Checked e m a #

MonadCont m => MonadCont (Checked e m) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

callCC :: ((a -> Checked e m b) -> Checked e m a) -> Checked e m a #

Eq (m a) => Eq (Checked e m a) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

(==) :: Checked e m a -> Checked e m a -> Bool #

(/=) :: Checked e m a -> Checked e m a -> Bool #

Ord (m a) => Ord (Checked e m a) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

compare :: Checked e m a -> Checked e m a -> Ordering #

(<) :: Checked e m a -> Checked e m a -> Bool #

(<=) :: Checked e m a -> Checked e m a -> Bool #

(>) :: Checked e m a -> Checked e m a -> Bool #

(>=) :: Checked e m a -> Checked e m a -> Bool #

max :: Checked e m a -> Checked e m a -> Checked e m a #

min :: Checked e m a -> Checked e m a -> Checked e m a #

Read (m a) => Read (Checked e m a) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

readsPrec :: Int -> ReadS (Checked e m a) #

readList :: ReadS [Checked e m a] #

readPrec :: ReadPrec (Checked e m a) #

readListPrec :: ReadPrec [Checked e m a] #

Show (m a) => Show (Checked e m a) Source # 
Instance details

Defined in Control.Exception.Checked

Methods

showsPrec :: Int -> Checked e m a -> ShowS #

show :: Checked e m a -> String #

showList :: [Checked e m a] -> ShowS #

type CheckedIO e a = Checked e IO a Source #

Convenience type alias for when working directly with IO.

class Allowed e => Throws exception e Source #

Declares an exception has been thrown.

In Throws exception e the exception parameter is the exception we're declaring has been thrown, and e is a type-level list that contains exception. This list will be solved for by the compiler, so in typical usage you will specify exception concretely leave e polymorphic.

See throws, throwsAll for examples of introducing this constraint, and see catch, handle, catches, and handles for example of removing this constraint.

Finally, note that Allowed is not exported, which prevent users from implementing more instances of Throws and bypassing safety.

Instances
Throws (exception :: k2) (Caught SomeException e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

Throws exception e => Throws (exception :: k3) (Caught exception' e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

Throws (exception :: k2) (Caught exception e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

type family ThrowsAll exceptions e where ... Source #

A syntactic convenience to expand to multiple Throws.

ThrowsAll '[ExceptionA, ExceptionB, ...] e => ...

expands to

(Throws ExceptionA e, Throws ExceptionB e, ...) => ...

Equations

ThrowsAll (exception ': rest) e = (Throws exception e, ThrowsAll rest e) 
ThrowsAll '[] e = (() :: Constraint) 

Running

runChecked :: Checked e m a -> m a Source #

Safely get your m a.

Most importantly, you won't be able to call this function if the phantom parameter l has any Throws constraints on it.

unsafeRunChecked :: Checked AnyException m a -> m a Source #

Ignore all type-level markers that an exception hasn't been handled.

This function is provided for completeness, but may you never find a reason to use this.

Constructors

throw :: (Throws exception e, Exception exception, MonadThrow m) => exception -> Checked e m a Source #

Throw an exception e.

Note, this delegates to safe-exception's throw.

impureThrow :: (Throws exception e, Exception exception, MonadThrow m) => exception -> Checked e m a Source #

Throw an exception e.

Note, this delegates to safe-exception's impureThrow.

throwsNone :: m a -> Checked e m a Source #

Start checking some monadic m a, declaring it as throwing nothing yet.

throws :: forall exception m e a. (Exception exception, Throws exception e, MonadThrow m) => m a -> Checked e m a Source #

Start checking a monadic m a, declaring it as throwing an exception.

This API is designed for GHC's TypeApplications extension. See throws' for an alternative.

>>> :{
checkedReadFile :: Throws IOException e => FilePath -> CheckedIO e String
checkedReadFile = throws @IOException . readFile
:}

Note that technically, you can use throwsNone and widen the constraints but this can lead to confusing code:

>>> :{
checkedReadFile :: Throws IOException e => FilePath -> CheckedIO e String
checkedReadFile = throwsNone . readFile
:}

See throwsAll if your m a throws more than one exception.

throwsAll :: forall exceptions m e a. (ThrowsAll exceptions e, MonadThrow m) => m a -> Checked e m a Source #

Start checking some monadic m a, declaring it as throwing exceptions. exceptions should be a type-level list.

This API is designed for GHC's TypeApplications extension. See throwsAll' for an alternative.

>>> import qualified Control.Exception as E
>>> :{
readFirst :: ThrowsAll '[IOException, E.ErrorCall] e
          => [FilePath] -> CheckedIO e String
readFirst = throwsAll @'[IOException, E.ErrorCall] . readFile . head
:}

Note that technically, you can use throwsNone and widen the constraints but this can lead to confusing code:

>>> :{
readFirst :: ThrowsAll '[IOException, E.ErrorCall] e
          => [FilePath] -> CheckedIO e String
readFirst = throwsNone . readFile . head
:}

See throwsAll if your m a throws more than one exception.

throws' :: (Exception exception, Throws exception e, MonadThrow m) => proxy exception -> m a -> Checked e m a Source #

Same a throws, but called with a proxy instead of a type application.

>>> import qualified Data.Proxy as P
>>> :{
checkedReadFile :: Throws IOException e => FilePath -> CheckedIO e String
checkedReadFile = throws' (P.Proxy :: P.Proxy IOException) . readFile
:}

throwsAll' :: (ThrowsAll exceptions e, MonadThrow m) => proxy exceptions -> m a -> Checked e m a Source #

Same a throwsAll, but called with a proxy instead of a type application.

>>> import qualified Data.Proxy as P
>>> import qualified Control.Exception as E
>>> :{
readFirst :: ThrowsAll '[IOException, E.ErrorCall] e
          => [FilePath] -> CheckedIO e String
readFirst = throwsAll' (P.Proxy :: P.Proxy '[IOException, E.ErrorCall])
    . readFile . head
:}

throwTo :: (Exception exception, MonadIO m) => ThreadId -> exception -> Checked e m () Source #

Throw an asynchronous exception to another thread.

Note, this delegates to safe-exception's throwTo.

throwString :: (Throws StringException e, MonadThrow m) => String -> Checked e m a Source #

Throw a semantically-neutral exception.

Note, this delegates to safe-exception's throwString.

Also, semantically, it's far better to make custom exception types. When everything thrown is a StringException, we can't handle/catch anything with any delicacy.

Handling Errors

Trying

try :: (Exception exception, MonadCatch m) => Checked (Caught exception e) m a -> Checked e m (Either exception a) infixl 8 Source #

Catch an exception and return it via an Either.

Note, this delegates to safe-exception's try.

tryIO :: MonadCatch m => Checked (Caught IOException e) m a -> Checked e m (Either IOException a) infixl 8 Source #

Catch an IOException and return it via an Either.

Note, this delegates to safe-exception's tryAny.

tryAny :: MonadCatch m => Checked (Caught SomeException e) m a -> Checked e m (Either SomeException a) infixl 8 Source #

Catch any exception and return it via an Either.

Note, this delegates to safe-exception's tryAny.

tryDeep :: (Exception exception, MonadCatch m, MonadIO m, NFData a) => Checked (Caught exception e) m a -> Checked e m (Either exception a) infixl 8 Source #

Force a computation, catch a exception and return it via an Either.

Note, this delegates to safe-exception's tryDeep.

tryAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => Checked (Caught SomeException e) m a -> Checked e m (Either SomeException a) infixl 8 Source #

Force a computation, catch any exception and return it via an Either.

Note, this delegates to safe-exception's tryAnyDeep.

tryJust :: (MonadCatch m, Exception exception) => (exception -> Maybe b) -> Checked e m a -> Checked e m (Either b a) Source #

A variant of try using a predicate to select which exceptions to catch.

Note, this delegates to safe-exception's tryJust.

tryAsync :: (Exception exception, MonadCatch m) => Checked (Caught exception e) m a -> Checked e m (Either exception a) infixl 8 Source #

Catch a possibly asynchronous exception and return it via an Either.

Note, this delegates to safe-exception's tryAsync. Also, catching asynchronous is discouraged, but this function is provided for completeness.

Catching

catch :: (Exception exception, MonadCatch m) => Checked (Caught exception e) m a -> (exception -> Checked e m a) -> Checked e m a infixl 8 Source #

Catch an exception with a provided handler.

Note, this delegates to safe-exception's catch.

catchIO :: MonadCatch m => Checked (Caught IOException e) m a -> (IOException -> Checked e m a) -> Checked e m a infixl 8 Source #

Catch an IOException with a provided handler.

Note, this delegates to safe-exception's catchIO.

catchAny :: MonadCatch m => Checked (Caught SomeException e) m a -> (SomeException -> Checked e m a) -> Checked e m a infixl 8 Source #

Catch any exception with a provided handler.

Note, this delegates to safe-exception's catchAny.

catchDeep :: (Exception exception, MonadCatch m, MonadIO m, NFData a) => Checked (Caught exception e) m a -> (exception -> Checked e m a) -> Checked e m a infixl 8 Source #

Force a computation, and catch an exception with a provided handler.

Note, this delegates to safe-exception's catchDeep.

catchAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => Checked (Caught SomeException e) m a -> (SomeException -> Checked e m a) -> Checked e m a infixl 8 Source #

Force a computation, and catch any exception with a provided handler.

Note, this delegates to safe-exception's catchAnyDeep.

catchJust :: (MonadCatch m, Exception exception) => (exception -> Maybe b) -> Checked (Caught exception e) m a -> (b -> Checked e m a) -> Checked e m a Source #

A variant of catch using a predicate to select which exceptions to catch.

Note, this delegates to safe-exception's catchJust.

catchAsync :: (Exception exception, MonadCatch m) => Checked (Caught exception e) m a -> (exception -> Checked e m a) -> Checked e m a infixl 8 Source #

Catch a possibly asynchronous exception with a provided handler.

Note, this delegates to safe-exception's catchAsync. Also, catching asynchronous is discouraged, but this function is provided for completeness.

Handling

handle :: (Exception exception, MonadCatch m) => (exception -> Checked e m a) -> Checked (Caught exception e) m a -> Checked e m a infixl 8 Source #

Flipped catch.

handleIO :: MonadCatch m => (IOException -> Checked e m a) -> Checked (Caught IOException e) m a -> Checked e m a infixl 8 Source #

Flipped catchIO.

handleAny :: MonadCatch m => (SomeException -> Checked e m a) -> Checked (Caught SomeException e) m a -> Checked e m a infixl 8 Source #

Flipped catchAny.

handleDeep :: (Exception exception, MonadCatch m, MonadIO m, NFData a) => (exception -> Checked e m a) -> Checked (Caught exception e) m a -> Checked e m a infixl 8 Source #

Flipped catchDeep.

handleAnyDeep :: (MonadCatch m, MonadIO m, NFData a) => (SomeException -> Checked e m a) -> Checked (Caught SomeException e) m a -> Checked e m a infixl 8 Source #

Flipped catchAnyDeep.

handleJust :: (MonadCatch m, Exception exception) => Checked (Caught exception e) m a -> (exception -> Maybe b) -> (b -> Checked e m a) -> Checked e m a Source #

Flipped catchJust.

handleAsync :: (Exception exception, MonadCatch m) => (exception -> Checked e m a) -> Checked (Caught exception e) m a -> Checked e m a infixl 8 Source #

Flipped catchAsync.

Note, catching asynchronous is discouraged, but this function is provided for completeness.

Handling Multiple Cases

data Handler m a handled e Source #

Used for catches and handles.

catches :: MonadCatch m => Checked (ToCaught handled e) m a -> Handler m a handled e -> Checked e m a infixl 8 Source #

Handle many exceptions at once.

Just as with catches, it's important to note that there's a difference between calling

  • catches with a single Handler built with many handler functions
  • catch multiple times, once for each handler function.

With catches, if one of the handlers throws an exception, that exception is guaranteed to surface. With catch, if a handler throws an exception, it may be handled by a successive call to catch. Fortunately, with exceptions checked at the type-level, the compiler helps makes this explicit.

Note, this delegates to safe-exception's catches.

catchesDeep :: (MonadCatch m, MonadIO m, NFData a) => Checked (ToCaught handled e) m a -> Handler m a handled e -> Checked e m a infixl 8 Source #

Same as catches, but forces computation first.

Note, this delegates to safe-exception's catchesDeep.

catchesAsync :: MonadCatch m => Checked (ToCaught handled e) m a -> Handler m a handled e -> Checked e m a infixl 8 Source #

Same as catches, but includes asynchronous exceptions as well.

Note, this delegates to safe-exception's catchesAsync. Also, catching asynchronous is discouraged, but this function is provided for completeness.

handles :: MonadCatch m => Handler m a handled e -> Checked (ToCaught handled e) m a -> Checked e m a infixl 8 Source #

Flipped catches.

handlesDeep :: (MonadCatch m, MonadIO m, NFData a) => Handler m a handled e -> Checked (ToCaught handled e) m a -> Checked e m a infixl 8 Source #

Flipped catchesDeep.

handlesAsync :: MonadCatch m => Handler m a handled e -> Checked (ToCaught handled e) m a -> Checked e m a infixl 8 Source #

Flipped catchesAsync.

Note, catching asynchronous is discouraged, but this function is provided for completeness.

handler :: Exception exception => (exception -> Checked e m a) -> Handler m a '[exception] e Source #

Builds a Handler to use with catches or handles.

You can put more handler functions into the returned Handler with appendHandler, <++>, or <:>.

(<:>) :: Exception exception => (exception -> Checked e m a) -> Handler m a handled e -> Handler m a (exception ': handled) e infixr 9 Source #

Chain a handler function into a Handler.

(<::>) :: (Exception exception, Exception exception') => (exception -> Checked e m a) -> (exception' -> Checked e m a) -> Handler m a '[exception, exception'] e infixr 9 Source #

Chain two handler functions together into a Handler.

This can start a right-associative chain of handlers, which you can add to with <:>:

>>> import qualified Control.Exception as E
>>> :{
completeHandler
    :: Handler IO ()
        '[E.IOException, E.ErrorCall, E.ArithException, E.SomeException] e
completeHandler =
         (\(_::E.IOException)    -> throwsNone $ print "handledIO")
    <:>  (\(_::E.ErrorCall)      -> throwsNone $ print "handledError")
    <:>  (\(_::E.ArithException) -> throwsNone $ print "handledArith")
    <::> (\(_::E.SomeException)  -> throwsNone $ print "handledSome")
:}

(<++>) :: Handler m a handled e -> Handler m a handled' e -> Handler m a (Append handled handled') e infixr 9 Source #

Infix operator alias for appendHandler

appendHandler :: Handler m a handled e -> Handler m a handled' e -> Handler m a (Append handled handled') e infixr 9 Source #

Appends two Handlers.

emptyHandler :: Handler m a '[] e Source #

A trivial empty Handler.

This may not be useful in the common case, but is here for as a convenience.

Cleanup

finally infixl 8 Source #

Arguments

:: MonadMask m 
=> Checked e m a

action

-> Checked e' m b

finalizer

-> Checked e m a 

A specialised variant of bracket with just a computation to run afterward.

Delegates to finally.

onException infixl 8 Source #

Arguments

:: MonadMask m 
=> Checked e m a

action

-> Checked e' m b

run if action throws an exception

-> Checked e m a 

Like finally, but finalizes only if an exception has been raised.

Delegates to onException.

withException infixl 8 Source #

Arguments

:: (MonadMask m, Exception exception) 
=> Checked e m a

action

-> (exception -> Checked e' m b)

run if action throws a specified exception

-> Checked e m a 

Like onException, but provides the handler the thrown exception.

Delegates to withException.

bracket Source #

Arguments

:: MonadMask m 
=> Checked e m a

acquire resource

-> (a -> Checked e' m b)

action

-> (a -> Checked e m c)

release resource

-> Checked e m c 

Acquire a resource, run an action with it, and release the resource.

Delegates to bracket.

bracket_ Source #

Arguments

:: MonadMask m 
=> Checked e m a

run before action

-> Checked e' m b

run after action

-> Checked e m c

action

-> Checked e m c 

Bracket an action with one before and after.

Delegates to bracket.

bracketOnError Source #

Arguments

:: MonadMask m 
=> Checked e m a

setup before action

-> (a -> Checked e' m b)

run if action throws an exception

-> (a -> Checked e m c)

action

-> Checked e m c 

Setup some context, run an action, and run another action upon an error.

Delegates to bracketOnError.

bracketOnError_ Source #

Arguments

:: MonadMask m 
=> Checked e m a

setup before action

-> Checked e' m b

run if action throws an exception

-> Checked e m c

action

-> Checked e m c 

run some setup, run an action, and run another action upon an error.

Delegates to bracketOnError_.

bracketWithError Source #

Arguments

:: MonadMask m 
=> Checked e m a

acquire resource

-> (Maybe SomeException -> a -> Checked e' m b)

cleanup, possibly handling an exception from action

-> (a -> Checked e m c)

action

-> Checked e m c 

General bracketing.

Delegates to bracketWithError.

Re-exported for convenience

isAsyncException :: Exception e => e -> Bool #

Check if the given exception is asynchronous

Since: safe-exceptions-0.1.0.0

isSyncException :: Exception e => e -> Bool #

Check if the given exception is synchronous

Since: safe-exceptions-0.1.0.0

toAsyncException :: Exception e => e -> SomeException #

Convert an exception into an asynchronous exception

For asynchronous exceptions, this is the same as toException. For synchronous exceptions, this will wrap up the exception with AsyncExceptionWrapper

Since: safe-exceptions-0.1.0.0

toSyncException :: Exception e => e -> SomeException #

Convert an exception into a synchronous exception

For synchronous exceptions, this is the same as toException. For asynchronous exceptions, this will wrap up the exception with SyncExceptionWrapper

Since: safe-exceptions-0.1.0.0

data AsyncExceptionWrapper where #

Wrap up a synchronous exception to be treated as an asynchronous exception

This is intended to be created via toAsyncException

Since: safe-exceptions-0.1.0.0

Constructors

AsyncExceptionWrapper :: forall e. Exception e => e -> AsyncExceptionWrapper 

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 MyException

The 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 = frontendExceptionFromException

We 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
Exception BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception AllocationLimitExceeded

Since: base-4.8.0.0

Instance details

Defined in GHC.IO.Exception

Exception CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Exception AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception AsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Exception StringException 
Instance details

Defined in Control.Exception.Safe

Exception SyncExceptionWrapper 
Instance details

Defined in Control.Exception.Safe

Exception AsyncExceptionWrapper 
Instance details

Defined in Control.Exception.Safe

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

Instance details

Defined in GHC.IO.Exception

Show IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Error IOException 
Instance details

Defined in Control.Monad.Trans.Error

MonadError IOException IO 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: IOException -> IO a #

catchError :: IO a -> (IOException -> IO a) -> IO a #

class MonadThrow m => MonadCatch (m :: Type -> Type) #

A class for monads which allow exceptions to be caught, in particular exceptions which were thrown by throwM.

Instances should obey the following law:

catch (throwM e) f = f e

Note that the ability to catch an exception does not guarantee that we can deal with all possible exit points from a computation. Some monads, such as continuation-based stacks, allow for more than just a success/failure strategy, and therefore catch cannot be used by those monads to properly implement a function such as finally. For more information, see MonadMask.

Minimal complete definition

catch

Instances
MonadCatch IO 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a #

MonadCatch STM 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => STM a -> (e -> STM a) -> STM a #

e ~ SomeException => MonadCatch (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => Either e a -> (e0 -> Either e a) -> Either e a #

MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

MonadCatch m => MonadCatch (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ExceptT e m a -> (e0 -> ExceptT e m a) -> ExceptT e m a #

MonadCatch m => MonadCatch (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a #

(Error e, MonadCatch m) => MonadCatch (ErrorT e m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ErrorT e m a -> (e0 -> ErrorT e m a) -> ErrorT e m a #

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

MonadCatch m => MonadCatch (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

class MonadCatch m => MonadMask (m :: Type -> Type) #

A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.

Instances should ensure that, in the following code:

fg = f `finally` g

The action g is called regardless of what occurs within f, including async exceptions. Some monads allow f to abort the computation via other effects than throwing an exception. For simplicity, we will consider aborting and throwing an exception to be two forms of "throwing an error".

If f and g both throw an error, the error thrown by fg depends on which errors we're talking about. In a monad transformer stack, the deeper layers override the effects of the inner layers; for example, ExceptT e1 (Except e2) a represents a value of type Either e2 (Either e1 a), so throwing both an e1 and an e2 will result in Left e2. If f and g both throw an error from the same layer, instances should ensure that the error from g wins.

Effects other than throwing an error are also overriden by the deeper layers. For example, StateT s Maybe a represents a value of type s -> Maybe (a, s), so if an error thrown from f causes this function to return Nothing, any changes to the state which f also performed will be erased. As a result, g will see the state as it was before f. Once g completes, f's error will be rethrown, so g' state changes will be erased as well. This is the normal interaction between effects in a monad transformer stack.

By contrast, lifted-base's version of finally always discards all of g's non-IO effects, and g never sees any of f's non-IO effects, regardless of the layer ordering and regardless of whether f throws an error. This is not the result of interacting effects, but a consequence of MonadBaseControl's approach.

Minimal complete definition

mask, uninterruptibleMask, generalBracket

Instances
MonadMask IO 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

generalBracket :: IO a -> (a -> ExitCase b -> IO c) -> (a -> IO b) -> IO (b, c) #

e ~ SomeException => MonadMask (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

generalBracket :: Either e a -> (a -> ExitCase b -> Either e c) -> (a -> Either e b) -> Either e (b, c) #

MonadMask m => MonadMask (MaybeT m)

Since: exceptions-0.10.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

uninterruptibleMask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

generalBracket :: MaybeT m a -> (a -> ExitCase b -> MaybeT m c) -> (a -> MaybeT m b) -> MaybeT m (b, c) #

MonadMask m => MonadMask (ExceptT e m)

Since: exceptions-0.9.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

generalBracket :: ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) #

MonadMask m => MonadMask (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

uninterruptibleMask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

generalBracket :: IdentityT m a -> (a -> ExitCase b -> IdentityT m c) -> (a -> IdentityT m b) -> IdentityT m (b, c) #

(Error e, MonadMask m) => MonadMask (ErrorT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

uninterruptibleMask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

generalBracket :: ErrorT e m a -> (a -> ExitCase b -> ErrorT e m c) -> (a -> ErrorT e m b) -> ErrorT e m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

MonadMask m => MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

generalBracket :: ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

class Monad m => MonadThrow (m :: Type -> Type) #

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

throwM

Instances
MonadThrow [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> STM a #

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> Either e a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a #

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IdentityT m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ErrorT e m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

data SomeAsyncException where #

Superclass for asynchronous exceptions.

Since: base-4.7.0.0

Constructors

SomeAsyncException :: forall e. Exception e => e -> SomeAsyncException 

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 :: forall e. Exception e => e -> SomeException 
Instances
Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Throws (exception :: k2) (Caught SomeException e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

data SyncExceptionWrapper where #

Wrap up an asynchronous exception to be treated as a synchronous exception

This is intended to be created via toSyncException

Since: safe-exceptions-0.1.0.0

Constructors

SyncExceptionWrapper :: forall e. Exception e => e -> SyncExceptionWrapper 

class Typeable (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

Implementation details

These abstractions tie everything together at the type-level, but are not something a user is expected to need directly.

data Caught exception e Source #

Inferred instance of Throws.

Instances
Throws (exception :: k2) (Caught SomeException e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

Throws exception e => Throws (exception :: k3) (Caught exception' e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

Throws (exception :: k2) (Caught exception e :: Type) Source # 
Instance details

Defined in Control.Exception.Checked

type family ToCaught asList asCaught where ... Source #

Implementation detail enabling catches and handles.

Equations

ToCaught (exception ': rest) e = Caught exception (ToCaught rest e) 
ToCaught '[] e = e 

type family Append exceptions exceptions' where ... Source #

Implementation detail enabling appendHandler and <++>.

Equations

Append (exception ': rest) e = exception ': Append rest e 
Append '[] e = e