transformers-0.5.6.2: Concrete functor and monad transformers
Copyright(C) 2013 Ross Paterson
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Except

Description

This monad transformer extends a monad with the ability to throw exceptions.

A sequence of actions terminates normally, producing a value, only if none of the actions in the sequence throws an exception. If one throws an exception, the rest of the sequence is skipped and the composite action exits with that exception.

If the value of the exception is not required, the variant in Control.Monad.Trans.Maybe may be used instead.

Synopsis

The Except monad

type Except e = ExceptT e Identity Source #

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception. For a variant that continues after an error and collects all the errors, see Errors.

except :: Monad m => Either e a -> ExceptT e m a Source #

Constructor for computations in the exception monad. (The inverse of runExcept).

runExcept :: Except e a -> Either e a Source #

Extractor for computations in the exception monad. (The inverse of except).

mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b Source #

Map the unwrapped computation using the given function.

withExcept :: (e -> e') -> Except e a -> Except e' a Source #

Transform any exceptions thrown by the computation using the given function (a specialization of withExceptT).

The ExceptT monad transformer

newtype ExceptT e m a Source #

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

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

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Constructors

ExceptT (m (Either e a)) 

Instances

Instances details
MonadTrans (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a Source #

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

Defined in Control.Monad.Trans.Except

Methods

fail :: String -> ExceptT e m a Source #

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

Defined in Control.Monad.Trans.Except

Methods

mfix :: (a -> ExceptT e m a) -> ExceptT e m a Source #

MonadIO m => MonadIO (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a Source #

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

Defined in Control.Monad.Trans.Except

Methods

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

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

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

Foldable f => Foldable (ExceptT e f) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fold :: Monoid m => ExceptT e f m -> m Source #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m Source #

foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m Source #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b Source #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b Source #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b Source #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b Source #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a Source #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a Source #

toList :: ExceptT e f a -> [a] Source #

null :: ExceptT e f a -> Bool Source #

length :: ExceptT e f a -> Int Source #

elem :: Eq a => a -> ExceptT e f a -> Bool Source #

maximum :: Ord a => ExceptT e f a -> a Source #

minimum :: Ord a => ExceptT e f a -> a Source #

sum :: Num a => ExceptT e f a -> a Source #

product :: Num a => ExceptT e f a -> a Source #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

(Ord e, Ord1 m) => Ord1 (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

(Read e, Read1 m) => Read1 (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

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

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

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e m a] Source #

(Show e, Show1 m) => Show1 (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

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

Contravariant m => Contravariant (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a' -> a) -> ExceptT e m a -> ExceptT e m a' Source #

(>$) :: b -> ExceptT e m b -> ExceptT e m a Source #

Traversable f => Traversable (ExceptT e f) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ExceptT e f a -> f0 (ExceptT e f b) Source #

sequenceA :: Applicative f0 => ExceptT e f (f0 a) -> f0 (ExceptT e f a) Source #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) Source #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) Source #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

empty :: ExceptT e m a Source #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

some :: ExceptT e m a -> ExceptT e m [a] Source #

many :: ExceptT e m a -> ExceptT e m [a] Source #

(Functor m, Monad m) => Applicative (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

pure :: a -> ExceptT e m a Source #

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

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

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b Source #

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

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

Defined in Control.Monad.Trans.Except

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b Source #

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

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

Defined in Control.Monad.Trans.Except

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b Source #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b Source #

return :: a -> ExceptT e m a Source #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzero :: ExceptT e m a Source #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

(Read e, Read1 m, Read a) => Read (ExceptT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Except

(Show e, Show1 m, Show a) => Show (ExceptT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS Source #

show :: ExceptT e m a -> String Source #

showList :: [ExceptT e m a] -> ShowS Source #

(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

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

(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

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

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

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

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

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

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

runExceptT :: ExceptT e m a -> m (Either e a) Source #

The inverse of ExceptT.

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b Source #

Map the unwrapped computation using the given function.

withExceptT :: Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a Source #

Transform any exceptions thrown by the computation using the given function.

Exception operations

throwE :: Monad m => e -> ExceptT e m a Source #

Signal an exception value e.

catchE Source #

Arguments

:: Monad m 
=> ExceptT e m a

the inner computation

-> (e -> ExceptT e' m a)

a handler for exceptions in the inner computation

-> ExceptT e' m a 

Handle an exception.

Lifting other operations

liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b Source #

Lift a callCC operation to the new monad.

liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a Source #

Lift a listen operation to the new monad.

liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a Source #

Lift a pass operation to the new monad.