Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This module provides throwEither
and catchEither
for Either
. These two
functions reside here because throwEither
and catchEither
correspond to return
and (>>=
) for the flipped Either
monad: EitherR
. Additionally, this
module defines handleE
as the flipped version of catchE
for ExceptT
.
throwEither
and catchEither
improve upon MonadError
because:
catchEither
is more general thancatch
and allows you to change the left value's type- Both are Haskell98
More advanced users can use EitherR
and ExceptRT
to program in an
entirely symmetric "success monad" where exceptional results are the norm
and successful results terminate the computation. This allows you to chain
error-handlers using do
notation and pass around exceptional values of
varying types until you can finally recover from the error:
runExceptRT $ do e2 <- ioExceptionHandler e1 bool <- arithmeticExceptionhandler e2 when bool $ lift $ putStrLn "DEBUG: Arithmetic handler did something"
If any of the above error handlers succeed
, no other handlers are tried.
If you choose not to typefully distinguish between the error and sucess
monad, then use flipEither
and flipET
, which swap the type variables without
changing the type.
- newtype EitherR r e = EitherR {
- runEitherR :: Either e r
- succeed :: r -> EitherR r e
- throwEither :: e -> Either e r
- catchEither :: Either a r -> (a -> Either b r) -> Either b r
- handleEither :: (a -> Either b r) -> Either a r -> Either b r
- fmapL :: (a -> b) -> Either a r -> Either b r
- flipEither :: Either a b -> Either b a
- newtype ExceptRT r m e = ExceptRT {
- runExceptRT :: ExceptT e m r
- succeedT :: Monad m => r -> ExceptRT r m e
- handleE :: Monad m => (a -> ExceptT b m r) -> ExceptT a m r -> ExceptT b m r
- fmapLT :: Monad m => (a -> b) -> ExceptT a m r -> ExceptT b m r
- flipET :: Monad m => ExceptT a m b -> ExceptT b m a
EitherR
If "Either e r
" is the error monad, then "EitherR r e
" is the
corresponding success monad, where:
return
isthrowEither
.- (
>>=
) iscatchEither
. - Successful results abort the computation
EitherR | |
|
Operations in the EitherR monad
Conversions to the Either monad
throwEither :: e -> Either e r Source
throwEither
in the error monad corresponds to return
in the success monad
catchEither :: Either a r -> (a -> Either b r) -> Either b r Source
catchEither
in the error monad corresponds to (>>=
) in the success monad
handleEither :: (a -> Either b r) -> Either a r -> Either b r Source
catchEither
with the arguments flipped
Flip alternative
flipEither :: Either a b -> Either b a Source
Flip the type variables of Either
ExceptRT
EitherR
converted into a monad transformer
ExceptRT | |
|
MonadTrans (ExceptRT r) Source | |
Monad m => Monad (ExceptRT r m) Source | |
Monad m => Functor (ExceptRT r m) Source | |
Monad m => Applicative (ExceptRT r m) Source | |
(Monad m, Monoid r) => Alternative (ExceptRT r m) Source | |
(Monad m, Monoid r) => MonadPlus (ExceptRT r m) Source | |
MonadIO m => MonadIO (ExceptRT r m) Source |
Operations in the ExceptRT monad
Conversions to the ExceptT monad
handleE :: Monad m => (a -> ExceptT b m r) -> ExceptT a m r -> ExceptT b m r Source
catchT
with the arguments flipped