transformers-0.0.0.0: Concrete monad transformers

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Control.Monad.Trans.Error

Contents

Description

Computation type:
Computations which may fail or throw exceptions.
Binding strategy:
Failure records information about the cause/location of the failure. Failure values bypass the bound function, other values are used as inputs to the bound function.
Useful for:
Building computations from sequences of functions that may fail or using exception handling to structure error handling.
Zero and plus:
Zero is represented by an empty error and the plus operation executes its second argument if the first fails.
Example type:
Data.Either String a

The Error monad (also called the Exception monad).

Synopsis

The ErrorT monad transformer

class Error a whereSource

An exception to be thrown. An instance must redefine at least one of noMsg, strMsg.

Methods

noMsg :: aSource

Creates an exception without a message. Default implementation is strMsg "".

strMsg :: String -> aSource

Creates an exception with a message. Default implementation 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) 
Monad m => Functor (ErrorT e m) 
(MonadFix m, Error e) => MonadFix (ErrorT e m) 
(Monad m, Error e) => MonadPlus (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.