transformers-either-0.1.2: An Either monad transformer
Copyright(C) 2017 Tim McGilchrist
LicenseBSD-style (see the file LICENSE)
Maintainertimmcgil@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Monad.Trans.Either

Description

This monad transformer extends Control.Monad.Trans.Except with a more familar Either naming.

Synopsis

Control.Monad.Trans.Either

type EitherT = ExceptT Source #

Type alias for ExceptT

pattern EitherT :: m (Either x a) -> ExceptT x m a Source #

newEitherT :: m (Either x a) -> EitherT x m a Source #

Constructor for computations in the either monad. (The inverse of runEitherT).

runEitherT :: EitherT x m a -> m (Either x a) Source #

Extractor for computations in the either monad. (The inverse of newEitherT).

eitherT :: Monad m => (x -> m b) -> (a -> m b) -> EitherT x m a -> m b Source #

Map over both arguments at the same time.

Specialised version of bimap for EitherT.

left :: Monad m => x -> EitherT x m a Source #

Constructor for left computations.

right :: Monad m => a -> EitherT x m a Source #

Constructor for right computations.

mapEitherT :: (m (Either x a) -> n (Either y b)) -> EitherT x m a -> EitherT y n b Source #

 

hoistEither :: Monad m => Either x a -> EitherT x m a Source #

Hoist an Either into an EitherT m.

bimapEitherT :: Functor m => (x -> y) -> (a -> b) -> EitherT x m a -> EitherT y m b Source #

Map the unwrapped computation using the given function.

Extensions

firstEitherT :: Functor m => (x -> y) -> EitherT x m a -> EitherT y m a Source #

Map the Left unwrapped computation using the given function.

secondEitherT :: Functor m => (a -> b) -> EitherT x m a -> EitherT x m b Source #

Map the Right unwrapped computation using the given function.

hoistMaybe :: Monad m => x -> Maybe a -> EitherT x m a Source #

Hoist Maybe a into Right a.

hoistEitherT :: (forall b. m b -> n b) -> EitherT x m a -> EitherT x n a Source #

Hoist Either m into an Either n.

handleIOEitherT :: MonadIO m => (IOException -> x) -> IO a -> EitherT x m a Source #

Try an IO action inside an EitherT. If the IO action throws an IOException, catch it and wrap it with the provided handler to convert it to the error type of the EitherT transformer. Exceptions other than IOException will escape the EitherT transformer.

Note: IOError is a type synonym for IOException.

handleEitherT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> EitherT x m a Source #

Try any monad action and catch the specified exception, wrapping it to convert it to the error type of the EitherT transformer. Exceptions other that the specified exception type will escape the EitherT transformer.

  • Warning*: This function should be used with caution! In particular, it is bad practice to catch SomeException because that includes asynchronous exceptions like stack/heap overflow, thread killed and user interrupt. Trying to handle StackOverflow, HeapOverflow and ThreadKilled exceptions could cause your program to crash or behave in unexpected ways.

handlesEitherT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> EitherT x m a Source #

Try a monad action and catch any of the exceptions caught by the provided handlers. The handler for each exception type needs to wrap it to convert it to the error type of the EitherT transformer. Exceptions not explicitly handled by the provided handlers will escape the EitherT transformer.

handleLeftT :: Monad m => (e -> EitherT e m a) -> EitherT e m a -> EitherT e m a Source #

Handle an error. Equivalent to handleError in mtl package.

catchIOEitherT :: MonadIO m => IO a -> (IOException -> x) -> EitherT x m a Source #

catchEitherT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> EitherT x m a Source #

Flipped handleEitherT.

catchesEitherT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> EitherT x m a Source #

catchLeftT :: Monad m => EitherT e m a -> (e -> EitherT e m a) -> EitherT e m a Source #

Flipped handleLeftT.

bracketEitherT :: Monad m => EitherT e m a -> (a -> EitherT e m b) -> (a -> EitherT e m c) -> EitherT e m c Source #

Acquire a resource in EitherT and then perform an action with it, cleaning up afterwards regardless of left.

This function does not clean up in the event of an exception. Prefer bracketExceptionT in any impure setting.

bracketExceptionT :: MonadMask m => EitherT e m a -> (a -> EitherT e m c) -> (a -> EitherT e m b) -> EitherT e m b Source #

Acquire a resource in EitherT and then perform an action with it, cleaning up afterwards regardless of left or exception.

Like bracketEitherT, but the cleanup is called even when the bracketed function throws an exception. Exceptions in the bracketed function are caught to allow the cleanup to run and then rethrown.