exceptions-0.6: Extensible optionally-pure exceptions

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Monad.Catch.Pure

Contents

Description

This module supplies a 'pure' monad transformer that can be used for mock-testing code that throws exceptions, so long as those exceptions are always thrown with throwM.

Do not mix CatchT with IO. Choose one or the other for the bottom of your transformer stack!

Synopsis

Transformer

The transformers-style monad transfomer

newtype CatchT m a Source

Add Exception handling abilities to a Monad.

This should never be used in combination with IO. Think of CatchT as an alternative base monad for use with mocking code that solely throws exceptions via throwM.

Note: that IO monad has these abilities already, so stacking CatchT on top of it does not add any value and can possibly be confusing:

>>> (error "Hello!" :: IO ()) `catch` (\(e :: ErrorCall) -> liftIO $ print e)
Hello!
>>> runCatchT $ (error "Hello!" :: CatchT IO ()) `catch` (\(e :: ErrorCall) -> liftIO $ print e)
*** Exception: Hello!
>>> runCatchT $ (throwM (ErrorCall "Hello!") :: CatchT IO ()) `catch` (\(e :: ErrorCall) -> liftIO $ print e)
Hello!

Constructors

CatchT 

Fields

runCatchT :: m (Either SomeException a)
 

Instances

MonadTrans CatchT 
MonadRWS r w s m => MonadRWS r w s (CatchT m) 
MonadReader e m => MonadReader e (CatchT m) 
MonadState s m => MonadState s (CatchT m) 
MonadWriter w m => MonadWriter w (CatchT m) 
Monad m => Monad (CatchT m) 
Monad m => Functor (CatchT m) 
MonadFix m => MonadFix (CatchT m) 
Monad m => MonadPlus (CatchT m) 
Monad m => Applicative (CatchT m) 
Foldable m => Foldable (CatchT m) 
(Monad m, Traversable m) => Traversable (CatchT m) 
Monad m => Alternative (CatchT m) 
MonadIO m => MonadIO (CatchT m) 
Monad m => MonadMask (CatchT m)

Note: This instance is only valid if the underlying monad has a single exit point!

Monad m => MonadCatch (CatchT m) 
Monad m => MonadThrow (CatchT m) 

mapCatchT :: (m (Either SomeException a) -> n (Either SomeException b)) -> CatchT m a -> CatchT n bSource

Map the unwrapped computation using the given function.

runCatchT (mapCatchT f m) = f (runCatchT m)

Typeclass

The mtl style typeclass