unification-fd-0.11.2: Simple generic unification algorithms.
LicenseBSD
Maintainerwren@cpan.org
Stabilityprovisional
Portabilitysemi-portable (CPP, Rank2Types, MPTCs, FlexibleInstances)
Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Monad.EitherK

Description

A continuation-passing variant of Either for short-circuiting at failure. This code is based on Control.Monad.MaybeK.

Synopsis

The short-circuiting monad

data EitherK e a Source #

A continuation-passing encoding of Either as an error monad; also known as Codensity (Either e), if you're familiar with that terminology. N.B., this is not the 2-continuation implementation based on the Church encoding of Either. The latter tends to have worse performance than non-continuation based implementations.

This is generally more efficient than using Either (or the MTL's Error) for two reasons. First is that it right associates all binds, ensuring that bad associativity doesn't artificially introduce midpoints in short-circuiting to the nearest handler. Second is that it removes the need for intermediate case expressions.

Another benefit over MTL's Error is that it doesn't artificially restrict the error type. In fact, there's no reason why e must denote "errors" per se. This could also denote computations which short-circuit with the final answer, or similar methods of non-local control flow.

N.B., the Alternative and MonadPlus instances are left-biased in a and monoidal in e. Thus, they are not commutative.

Instances

Instances details
MonadError e (EitherK e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

throwError :: e -> EitherK e a #

catchError :: EitherK e a -> (e -> EitherK e a) -> EitherK e a #

Monad (EitherK e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

(>>=) :: EitherK e a -> (a -> EitherK e b) -> EitherK e b #

(>>) :: EitherK e a -> EitherK e b -> EitherK e b #

return :: a -> EitherK e a #

Functor (EitherK e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

fmap :: (a -> b) -> EitherK e a -> EitherK e b #

(<$) :: a -> EitherK e b -> EitherK e a #

Applicative (EitherK e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

pure :: a -> EitherK e a #

(<*>) :: EitherK e (a -> b) -> EitherK e a -> EitherK e b #

liftA2 :: (a -> b -> c) -> EitherK e a -> EitherK e b -> EitherK e c #

(*>) :: EitherK e a -> EitherK e b -> EitherK e b #

(<*) :: EitherK e a -> EitherK e b -> EitherK e a #

Monoid e => Alternative (EitherK e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

empty :: EitherK e a #

(<|>) :: EitherK e a -> EitherK e a -> EitherK e a #

some :: EitherK e a -> EitherK e [a] #

many :: EitherK e a -> EitherK e [a] #

Monoid e => MonadPlus (EitherK e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

mzero :: EitherK e a #

mplus :: EitherK e a -> EitherK e a -> EitherK e a #

runEitherK :: EitherK e a -> Either e a Source #

Execute an EitherK and return the concrete Either encoding.

toEitherK :: Either e a -> EitherK e a Source #

Lift an Either into an EitherK.

eitherK :: (e -> b) -> (a -> b) -> EitherK e a -> b Source #

A version of either on EitherK, for convenience. N.B., using this function inserts a case match, reducing the range of short-circuiting.

throwEitherK :: e -> EitherK e a Source #

Throw an error in the EitherK monad. This is identical to throwError.

catchEitherK :: EitherK e a -> (e -> EitherK f a) -> EitherK f a Source #

Handle errors in the EitherK monad. N.B., this type is more general than that of catchError, allowing the type of the errors to change.

The short-circuiting monad transformer

data EitherKT e m a Source #

A monad transformer version of EitherK.

Instances

Instances details
(Applicative m, Monad m) => MonadError e (EitherKT e m) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

throwError :: e -> EitherKT e m a #

catchError :: EitherKT e m a -> (e -> EitherKT e m a) -> EitherKT e m a #

MonadTrans (EitherKT e) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

lift :: Monad m => m a -> EitherKT e m a #

Monad (EitherKT e m) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

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

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

return :: a -> EitherKT e m a #

Functor (EitherKT e m) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

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

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

Applicative (EitherKT e m) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

pure :: a -> EitherKT e m a #

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

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

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

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

(Applicative m, Monad m, Monoid e) => Alternative (EitherKT e m) Source # 
Instance details

Defined in Control.Monad.EitherK

Methods

empty :: EitherKT e m a #

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

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

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

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

Defined in Control.Monad.EitherK

Methods

mzero :: EitherKT e m a #

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

runEitherKT :: Applicative m => EitherKT e m a -> m (Either e a) Source #

Execute an EitherKT and return the concrete Either encoding.

toEitherKT :: Applicative m => Either e a -> EitherKT e m a Source #

Lift an Either into an EitherKT.

liftEitherK :: Applicative m => EitherK e a -> EitherKT e m a Source #

Lift an EitherK into an EitherKT.

lowerEitherK :: Applicative m => EitherKT e m a -> m (EitherK e a) Source #

Lower an EitherKT into an EitherK.

throwEitherKT :: Applicative m => e -> EitherKT e m a Source #

Throw an error in the EitherKT monad. This is identical to throwError.

catchEitherKT :: (Applicative m, Monad m) => EitherKT e m a -> (e -> EitherKT f m a) -> EitherKT f m a Source #

Handle errors in the EitherKT monad. N.B., this type is more general than that of catchError, allowing the type of the errors to change.