Copyright | (C) 2008-2014 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | MPTCs |
Safe Haskell | Trustworthy |
Language | Haskell98 |
This module provides a minimalist Either
monad transformer.
- newtype EitherT e m a = EitherT {
- runEitherT :: m (Either e a)
- eitherT :: Monad m => (a -> m c) -> (b -> m c) -> EitherT a m b -> m c
- bimapEitherT :: Functor m => (e -> f) -> (a -> b) -> EitherT e m a -> EitherT f m b
- mapEitherT :: (m (Either e a) -> n (Either e' b)) -> EitherT e m a -> EitherT e' n b
- hoistEither :: Monad m => Either e a -> EitherT e m a
- bracketEitherT :: Monad m => EitherT e m a -> (a -> EitherT e m b) -> (a -> EitherT e m c) -> EitherT e m c
- bracketEitherT_ :: Monad m => EitherT e m a -> EitherT e m b -> EitherT e m c -> EitherT e m c
- left :: Monad m => e -> EitherT e m a
- right :: Monad m => a -> EitherT e m a
- swapEitherT :: Functor m => EitherT e m a -> EitherT a m e
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.
EitherT | |
|
Monad m => MonadError e (EitherT e m) Source # | |
MonadBase b m => MonadBase b (EitherT e m) Source # | |
(Functor f, MonadFree f m) => MonadFree f (EitherT e m) Source # | |
MonadReader r m => MonadReader r (EitherT e m) Source # | |
MonadState s m => MonadState s (EitherT e m) Source # | |
MonadBaseControl b m => MonadBaseControl b (EitherT e m) Source # | |
MonadWriter s m => MonadWriter s (EitherT e m) Source # | |
MonadTrans (EitherT e) Source # | |
MonadTransControl (EitherT e) Source # | |
MFunctor (EitherT e) Source # | |
Monad m => Monad (EitherT e m) Source # | |
Monad m => Functor (EitherT e m) Source # | |
MonadFix m => MonadFix (EitherT e m) Source # | |
Monad m => Applicative (EitherT e m) Source # | |
Foldable m => Foldable (EitherT e m) Source # | |
(Monad f, Traversable f) => Traversable (EitherT e f) Source # | |
MonadIO m => MonadIO (EitherT e m) Source # | |
(Monad m, Monoid e) => Alternative (EitherT e m) Source # | |
(Monad m, Monoid e) => MonadPlus (EitherT e m) Source # | |
Monad m => Bind (EitherT e m) Source # | |
Monad m => Apply (EitherT e m) Source # | |
(Monad m, Semigroup e) => Alt (EitherT e m) Source # | |
MonadCont m => MonadCont (EitherT e m) Source # | |
MonadThrow m => MonadThrow (EitherT e m) Source # | Throws exceptions into the base monad. |
MonadCatch m => MonadCatch (EitherT e m) Source # | Catches exceptions from the base monad. |
MonadRandom m => MonadRandom (EitherT e m) Source # | |
Eq (m (Either e a)) => Eq (EitherT e m a) Source # | |
Ord (m (Either e a)) => Ord (EitherT e m a) Source # | |
Read (m (Either e a)) => Read (EitherT e m a) Source # | |
Show (m (Either e a)) => Show (EitherT e m a) Source # | |
Monad m => Semigroup (EitherT e m a) Source # | |
type StT (EitherT e) a Source # | |
type StM (EitherT e m) a Source # | |
eitherT :: Monad m => (a -> m c) -> (b -> m c) -> EitherT a m b -> m c Source #
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 b Source #
Map over both failure and success.
mapEitherT :: (m (Either e a) -> n (Either e' b)) -> EitherT e m a -> EitherT e' n b Source #
Map the unwrapped computation using the given function.
runEitherT
(mapEitherT
f m) = f (runEitherT
m)
bracketEitherT :: Monad m => EitherT e m a -> (a -> EitherT e m b) -> (a -> EitherT e m c) -> EitherT e m c Source #
bracketEitherT_ :: Monad m => EitherT e m a -> EitherT e m b -> EitherT e m c -> EitherT e m c Source #
Version of bracketEitherT
which discards the result from the initial
action.
swapEitherT :: Functor m => EitherT e m a -> EitherT a m e Source #
Monad transformer version of swapEither
.