exceptiot-0.0.1.0: ExceptT, but uses IO instead of Either
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Except.Catch

Synopsis

Documentation

newtype ExceptCatchT e m a Source #

This type is useful for translating a MonadError constraint into MonadCatch. This type does not have an Either return, which means we can provide a MonadUnliftIO instance.

Since: 0.1.0.0

Constructors

ExceptCatchT 

Fields

Instances

Instances details
(MonadCatch m, Exception e) => MonadError e (ExceptCatchT e m) Source #

Since: 0.1.0.0

Instance details

Defined in Control.Monad.Except.Catch

Methods

throwError :: e -> ExceptCatchT e m a #

catchError :: ExceptCatchT e m a -> (e -> ExceptCatchT e m a) -> ExceptCatchT e m a #

MonadReader r m => MonadReader r (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

ask :: ExceptCatchT e m r #

local :: (r -> r) -> ExceptCatchT e m a -> ExceptCatchT e m a #

reader :: (r -> a) -> ExceptCatchT e m a #

MonadState s m => MonadState s (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

get :: ExceptCatchT e m s #

put :: s -> ExceptCatchT e m () #

state :: (s -> (a, s)) -> ExceptCatchT e m a #

MonadWriter w m => MonadWriter w (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

writer :: (a, w) -> ExceptCatchT e m a #

tell :: w -> ExceptCatchT e m () #

listen :: ExceptCatchT e m a -> ExceptCatchT e m (a, w) #

pass :: ExceptCatchT e m (a, w -> w) -> ExceptCatchT e m a #

MonadFail m => MonadFail (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

fail :: String -> ExceptCatchT e m a #

MonadFix m => MonadFix (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

mfix :: (a -> ExceptCatchT e m a) -> ExceptCatchT e m a #

MonadIO m => MonadIO (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

liftIO :: IO a -> ExceptCatchT e m a #

Alternative m => Alternative (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

empty :: ExceptCatchT e m a #

(<|>) :: ExceptCatchT e m a -> ExceptCatchT e m a -> ExceptCatchT e m a #

some :: ExceptCatchT e m a -> ExceptCatchT e m [a] #

many :: ExceptCatchT e m a -> ExceptCatchT e m [a] #

Applicative m => Applicative (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

pure :: a -> ExceptCatchT e m a #

(<*>) :: ExceptCatchT e m (a -> b) -> ExceptCatchT e m a -> ExceptCatchT e m b #

liftA2 :: (a -> b -> c) -> ExceptCatchT e m a -> ExceptCatchT e m b -> ExceptCatchT e m c #

(*>) :: ExceptCatchT e m a -> ExceptCatchT e m b -> ExceptCatchT e m b #

(<*) :: ExceptCatchT e m a -> ExceptCatchT e m b -> ExceptCatchT e m a #

Functor m => Functor (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

fmap :: (a -> b) -> ExceptCatchT e m a -> ExceptCatchT e m b #

(<$) :: a -> ExceptCatchT e m b -> ExceptCatchT e m a #

Monad m => Monad (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

(>>=) :: ExceptCatchT e m a -> (a -> ExceptCatchT e m b) -> ExceptCatchT e m b #

(>>) :: ExceptCatchT e m a -> ExceptCatchT e m b -> ExceptCatchT e m b #

return :: a -> ExceptCatchT e m a #

MonadPlus m => MonadPlus (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

mzero :: ExceptCatchT e m a #

mplus :: ExceptCatchT e m a -> ExceptCatchT e m a -> ExceptCatchT e m a #

MonadCatch m => MonadCatch (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

catch :: Exception e0 => ExceptCatchT e m a -> (e0 -> ExceptCatchT e m a) -> ExceptCatchT e m a #

MonadMask m => MonadMask (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

mask :: ((forall a. ExceptCatchT e m a -> ExceptCatchT e m a) -> ExceptCatchT e m b) -> ExceptCatchT e m b #

uninterruptibleMask :: ((forall a. ExceptCatchT e m a -> ExceptCatchT e m a) -> ExceptCatchT e m b) -> ExceptCatchT e m b #

generalBracket :: ExceptCatchT e m a -> (a -> ExitCase b -> ExceptCatchT e m c) -> (a -> ExceptCatchT e m b) -> ExceptCatchT e m (b, c) #

MonadThrow m => MonadThrow (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptCatchT e m a #

MonadUnliftIO m => MonadUnliftIO (ExceptCatchT e m) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

withRunInIO :: ((forall a. ExceptCatchT e m a -> IO a) -> IO b) -> ExceptCatchT e m b #

Monoid (m a) => Monoid (ExceptCatchT e m a) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

mempty :: ExceptCatchT e m a #

mappend :: ExceptCatchT e m a -> ExceptCatchT e m a -> ExceptCatchT e m a #

mconcat :: [ExceptCatchT e m a] -> ExceptCatchT e m a #

Semigroup (m a) => Semigroup (ExceptCatchT e m a) Source # 
Instance details

Defined in Control.Monad.Except.Catch

Methods

(<>) :: ExceptCatchT e m a -> ExceptCatchT e m a -> ExceptCatchT e m a #

sconcat :: NonEmpty (ExceptCatchT e m a) -> ExceptCatchT e m a #

stimes :: Integral b => b -> ExceptCatchT e m a -> ExceptCatchT e m a #

runExceptCatchT :: (Exception e, MonadCatch m) => ExceptCatchT e m a -> m (Either e a) Source #

Run an ExceptCatchT action. This will catch any thrown e exceptions, regardless of whether you used throwM or throwError.

Any exception that is not mentioned in e will be thrown - this does not catch all exceptions!

Since: 0.1.0.0

modifyError :: (Exception e, MonadCatch m, MonadError e' m) => (e -> e') -> ExceptCatchT e m a -> m a Source #

Like modifyError, but it selects the ExceptCatchT instance for IO exceptions instead of the ExceptT instance with an Either error.

Since: 0.1.0.0