transformers-except-0.1.1: An Except monad transformer with

Copyright(C) 2017 Tim McGilchrist
LicenseBSD-style (see the file LICENSE)
Maintainertimmcgil@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Except.Extra

Contents

Description

This monad transformer extends Control.Monad.Trans.Except with a few more conveniences.

Synopsis

Control.Monad.Trans.Except.Extra

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

Constructor for computations in the ExceptT monad. (The inverse of runExceptT).

runExceptT :: ExceptT e m a -> m (Either e a) #

The inverse of ExceptT.

exceptT :: Monad m => (x -> m b) -> (a -> m b) -> ExceptT x m a -> m b Source #

Map over both arguments at the same time.

Specialised version of bimap for ExceptT.

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

Constructor for left computations.

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

Constructor for right computations.

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b #

Map the unwrapped computation using the given function.

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

Hoist an Either into an ExceptT m.

bimapExceptT :: Functor m => (x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b Source #

Map the unwrapped computation using the given function.

Extensions

firstExceptT :: Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a Source #

Map the Left unwrapped computation using the given function.

secondExceptT :: Functor m => (a -> b) -> ExceptT x m a -> ExceptT x m b Source #

Map the Right unwrapped computation using the given function.

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

Hoist Maybe a into Right a.

hoistExceptT :: (forall b. m b -> n b) -> ExceptT x m a -> ExceptT x n a Source #

Hoist Except m into an Except n.

handleIOExceptT :: MonadIO m => (IOException -> x) -> IO a -> ExceptT x m a Source #

Try an IO action inside an ExceptT. 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 ExceptT transformer. Exceptions other than IOException will escape the ExceptT transformer.

Note: IOError is a type synonym for IOException.

handleExceptT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> ExceptT x m a Source #

Try any monad action and catch the specified exception, wrapping it to convert it to the error type of the ExceptT transformer. Exceptions other that the specified exception type will escape the ExceptT 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.

handlesExceptT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> ExceptT 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 ExceptT transformer. Exceptions not explicitly handled by the provided handlers will escape the ExceptT transformer.

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

Handle an error. Equivalent to handleError in mtl package.

catchIOExceptT :: MonadIO m => IO a -> (IOException -> x) -> ExceptT x m a Source #

catchExceptT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> ExceptT x m a Source #

Flipped handleExceptT.

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

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

Flipped handleLeftT.

bracketExceptT :: Monad m => ExceptT e m a -> (a -> ExceptT e m b) -> (a -> ExceptT e m c) -> ExceptT e m c Source #

Acquire a resource in ExceptT 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 => ExceptT e m a -> (a -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m b Source #

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

Like bracketExceptT, 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.