transformers-0.2.0.0: Concrete functor and monad transformers

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Control.Monad.Trans.Error

Contents

Description

This monad transformer adds the ability to fail or throw exceptions to a monad.

A sequence of actions succeeds, producing a value, only if all the actions in the sequence are successful. If one fails with an error, the rest of the sequence is skipped and the composite action fails with that error.

Synopsis

The ErrorT monad transformer

class Error a whereSource

An exception to be thrown.

Minimal complete definition: noMsg or strMsg.

Methods

noMsg :: aSource

Creates an exception without a message. The default implementation is strMsg "".

strMsg :: String -> aSource

Creates an exception with a message. The default implementation of strMsg s is noMsg.

Instances

Error IOException 
ErrorList a => Error [a]

A string can be thrown as an error.

class ErrorList a whereSource

Workaround so that we can have a Haskell 98 instance Error String.

Methods

listMsg :: String -> [a]Source

Instances

newtype ErrorT e m a Source

The error monad transformer. It can be used to add error handling to other monads.

The ErrorT Monad structure is parameterized over two things:

  • e - The error type.
  • m - The inner monad.

Here are some examples of use:

 -- wraps IO action that can throw an error e
 type ErrorWithIO e a = ErrorT e IO a
 ==> ErrorT (IO (Either e a))

 -- IO monad wrapped in StateT inside of ErrorT
 type ErrorAndStateWithIO e s a = ErrorT e (StateT s IO) a
 ==> ErrorT (StateT s IO (Either e a))
 ==> ErrorT (StateT (s -> IO (Either e a,s)))

Constructors

ErrorT 

Fields

runErrorT :: m (Either e a)
 

Instances

Error e => MonadTrans (ErrorT e) 
(Monad m, Error e) => Monad (ErrorT e m) 
Functor m => Functor (ErrorT e m) 
(MonadFix m, Error e) => MonadFix (ErrorT e m) 
(Monad m, Error e) => MonadPlus (ErrorT e m) 
(Functor m, Monad m) => Applicative (ErrorT e m) 
(Functor m, Monad m, Error e) => Alternative (ErrorT e m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 

mapErrorT :: (m (Either e a) -> n (Either e' b)) -> ErrorT e m a -> ErrorT e' n bSource

throwError :: (Monad m, Error e) => e -> ErrorT e m aSource

Signal an error

catchError :: (Monad m, Error e) => ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m aSource

Handle an error

Lifting other operations

liftCallCC :: (((Either e a -> m (Either e b)) -> m (Either e a)) -> m (Either e a)) -> ((a -> ErrorT e m b) -> ErrorT e m a) -> ErrorT e m aSource

Lift a callCC operation to the new monad.

liftListen :: Monad m => (m (Either e a) -> m (Either e a, w)) -> ErrorT e m a -> ErrorT e m (a, w)Source

Lift a listen operation to the new monad.

liftPass :: Monad m => (m (Either e a, w -> w) -> m (Either e a)) -> ErrorT e m (a, w -> w) -> ErrorT e m aSource

Lift a pass operation to the new monad.