either-3.1: An either monad transformer

PortabilityMPTCs
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Monad.Trans.Either

Description

This module provides a minimalist Either monad transformer.

Synopsis

Documentation

newtype EitherT e m a Source

EitherT is a version of ErrorT that does not require a spurious Error instance for the Left case.

Either is a perfectly usable Monad without such a constraint. ErrorT is not the generalization of the current Either monad, it is something else.

This is necessary for both theoretical and practical reasons. For instance an apomorphism is the generalized anamorphism for this Monad, but it cannot be written with ErrorT.

In addition to the combinators here, the errors package provides a large number of combinators for working with this type.

Constructors

EitherT 

Fields

runEitherT :: m (Either e a)
 

Instances

(Monad (EitherT e m), Monad m) => MonadError e (EitherT e m) 
(Monad (EitherT e m), MonadReader r m) => MonadReader r (EitherT e m) 
(Monad (EitherT e m), MonadState s m) => MonadState s (EitherT e m) 
(Monoid s, Monad (EitherT e m), MonadWriter s m) => MonadWriter s (EitherT e m) 
MonadTrans (EitherT e) 
Monad m => Monad (EitherT e m) 
Functor m => Functor (EitherT e m) 
(Monad (EitherT e m), MonadFix m) => MonadFix (EitherT e m) 
(Functor (EitherT e m), Functor m, Monad m) => Applicative (EitherT e m) 
Foldable m => Foldable (EitherT e m) 
(Functor (EitherT e f), Foldable (EitherT e f), Traversable f) => Traversable (EitherT e f) 
(Monad (EitherT e m), MonadRandom m) => MonadRandom (EitherT e m) 
(Monad (EitherT e m), MonadIO m) => MonadIO (EitherT e m) 
(Monad (EitherT e m), MonadCont m) => MonadCont (EitherT e m) 
(Functor (EitherT e m), Functor m, Monad m) => Alt (EitherT e m) 
(Functor (EitherT e m), Functor m, Monad m) => Apply (EitherT e m) 
(Apply (EitherT e m), Functor m, Monad m) => Bind (EitherT e m) 
Eq (m (Either e a)) => Eq (EitherT e m a) 
(Eq (EitherT e m a), Ord (m (Either e a))) => Ord (EitherT e m a) 
Read (m (Either e a)) => Read (EitherT e m a) 
Show (m (Either e a)) => Show (EitherT e m a) 
Monad m => Semigroup (EitherT e m a) 

eitherT :: Monad m => (a -> m c) -> (b -> m c) -> EitherT a m b -> m cSource

Given a pair of actions, one to perform in case of failure, and one to perform in case of success, run an EitherT and get back a monadic result.

bimapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m bSource

Map over both failure and success.

mapEitherT :: (m (Either e a) -> n (Either e' b)) -> EitherT e m a -> EitherT e' n bSource

Map the unwrapped computation using the given function.

 runEitherT (mapEitherT f m) = f (runEitherT m)

hoistEither :: Monad m => Either e a -> EitherT e m aSource

Lift an Either into an EitherT

left :: Monad m => e -> EitherT e m aSource

Analogous to Left. Equivalent to throwError.

right :: Monad m => a -> EitherT e m aSource

Analogous to Right. Equivalent to return.