errors-2.2.3: Simplified error-handling

Safe HaskellSafe
LanguageHaskell98

Data.EitherR

Contents

Description

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 than catch 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.

Synopsis

EitherR

newtype EitherR r e Source #

If "Either e r" is the error monad, then "EitherR r e" is the corresponding success monad, where:

Constructors

EitherR 

Fields

Instances

Monad (EitherR r) Source # 

Methods

(>>=) :: EitherR r a -> (a -> EitherR r b) -> EitherR r b #

(>>) :: EitherR r a -> EitherR r b -> EitherR r b #

return :: a -> EitherR r a #

fail :: String -> EitherR r a #

Functor (EitherR r) Source # 

Methods

fmap :: (a -> b) -> EitherR r a -> EitherR r b #

(<$) :: a -> EitherR r b -> EitherR r a #

Applicative (EitherR r) Source # 

Methods

pure :: a -> EitherR r a #

(<*>) :: EitherR r (a -> b) -> EitherR r a -> EitherR r b #

liftA2 :: (a -> b -> c) -> EitherR r a -> EitherR r b -> EitherR r c #

(*>) :: EitherR r a -> EitherR r b -> EitherR r b #

(<*) :: EitherR r a -> EitherR r b -> EitherR r a #

Monoid r => Alternative (EitherR r) Source # 

Methods

empty :: EitherR r a #

(<|>) :: EitherR r a -> EitherR r a -> EitherR r a #

some :: EitherR r a -> EitherR r [a] #

many :: EitherR r a -> EitherR r [a] #

Monoid r => MonadPlus (EitherR r) Source # 

Methods

mzero :: EitherR r a #

mplus :: EitherR r a -> EitherR r a -> EitherR r a #

Operations in the EitherR monad

succeed :: r -> EitherR r e Source #

Complete error handling, returning a result

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

fmapL :: (a -> b) -> Either a r -> Either b r Source #

Map a function over the Left value of an Either

Flip alternative

flipEither :: Either a b -> Either b a Source #

Flip the type variables of Either

ExceptRT

newtype ExceptRT r m e Source #

EitherR converted into a monad transformer

Constructors

ExceptRT 

Fields

Instances

MonadTrans (ExceptRT r) Source # 

Methods

lift :: Monad m => m a -> ExceptRT r m a #

Monad m => Monad (ExceptRT r m) Source # 

Methods

(>>=) :: ExceptRT r m a -> (a -> ExceptRT r m b) -> ExceptRT r m b #

(>>) :: ExceptRT r m a -> ExceptRT r m b -> ExceptRT r m b #

return :: a -> ExceptRT r m a #

fail :: String -> ExceptRT r m a #

Monad m => Functor (ExceptRT r m) Source # 

Methods

fmap :: (a -> b) -> ExceptRT r m a -> ExceptRT r m b #

(<$) :: a -> ExceptRT r m b -> ExceptRT r m a #

Monad m => Applicative (ExceptRT r m) Source # 

Methods

pure :: a -> ExceptRT r m a #

(<*>) :: ExceptRT r m (a -> b) -> ExceptRT r m a -> ExceptRT r m b #

liftA2 :: (a -> b -> c) -> ExceptRT r m a -> ExceptRT r m b -> ExceptRT r m c #

(*>) :: ExceptRT r m a -> ExceptRT r m b -> ExceptRT r m b #

(<*) :: ExceptRT r m a -> ExceptRT r m b -> ExceptRT r m a #

MonadIO m => MonadIO (ExceptRT r m) Source # 

Methods

liftIO :: IO a -> ExceptRT r m a #

(Monad m, Monoid r) => Alternative (ExceptRT r m) Source # 

Methods

empty :: ExceptRT r m a #

(<|>) :: ExceptRT r m a -> ExceptRT r m a -> ExceptRT r m a #

some :: ExceptRT r m a -> ExceptRT r m [a] #

many :: ExceptRT r m a -> ExceptRT r m [a] #

(Monad m, Monoid r) => MonadPlus (ExceptRT r m) Source # 

Methods

mzero :: ExceptRT r m a #

mplus :: ExceptRT r m a -> ExceptRT r m a -> ExceptRT r m a #

Operations in the ExceptRT monad

succeedT :: Monad m => r -> ExceptRT r m e Source #

Complete error handling, returning a result

Conversions to the ExceptT monad

handleE :: Monad m => (a -> ExceptT b m r) -> ExceptT a m r -> ExceptT b m r Source #

catchE with the arguments flipped

fmapLT :: Functor m => (a -> b) -> ExceptT a m r -> ExceptT b m r Source #

Map a function over the Left value of an ExceptT

Flip alternative

flipET :: Monad m => ExceptT a m b -> ExceptT b m a Source #

Flip the type variables of an ExceptT