effect-stack-0.3.0.1: Reducing the pain of transformer stacks with duplicated effects
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Stack.Error

Documentation

class Monad m => ErrorStack (m :: Type -> Type) where Source #

Associated Types

type PopError (m :: Type -> Type) :: Type -> Type Source #

Methods

liftError :: PopError m a -> m a Source #

Instances

Instances details
ErrorStack m => ErrorStack (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (MaybeT m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (MaybeT m) = PopError m

Methods

liftError :: PopError (MaybeT m) a -> MaybeT m a Source #

(ErrorStack m, Monoid w) => ErrorStack (AccumT w m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (AccumT w m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (AccumT w m) = PopError m

Methods

liftError :: PopError (AccumT w m) a -> AccumT w m a Source #

Monad m => ErrorStack (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (ExceptT e m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (ExceptT e m) = m

Methods

liftError :: PopError (ExceptT e m) a -> ExceptT e m a Source #

ErrorStack m => ErrorStack (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (IdentityT m) 
Instance details

Defined in Control.Monad.Stack.Error

Methods

liftError :: PopError (IdentityT m) a -> IdentityT m a Source #

ErrorStack m => ErrorStack (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (ReaderT r m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (ReaderT r m) = PopError m

Methods

liftError :: PopError (ReaderT r m) a -> ReaderT r m a Source #

ErrorStack m => ErrorStack (SelectT r m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (SelectT r m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (SelectT r m) = PopError m

Methods

liftError :: PopError (SelectT r m) a -> SelectT r m a Source #

ErrorStack m => ErrorStack (StateT s m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (StateT s m) = PopError m

Methods

liftError :: PopError (StateT s m) a -> StateT s m a Source #

ErrorStack m => ErrorStack (StateT s m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (StateT s m) = PopError m

Methods

liftError :: PopError (StateT s m) a -> StateT s m a Source #

(ErrorStack m, Monoid w) => ErrorStack (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (WriterT w m) = PopError m

Methods

liftError :: PopError (WriterT w m) a -> WriterT w m a Source #

(ErrorStack m, Monoid w) => ErrorStack (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (WriterT w m) = PopError m

Methods

liftError :: PopError (WriterT w m) a -> WriterT w m a Source #

(ErrorStack m, Monoid w) => ErrorStack (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (WriterT w m) = PopError m

Methods

liftError :: PopError (WriterT w m) a -> WriterT w m a Source #

ErrorStack m => ErrorStack (ContT r m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (ContT r m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (ContT r m) = PopError m

Methods

liftError :: PopError (ContT r m) a -> ContT r m a Source #

(ErrorStack m, Monoid w) => ErrorStack (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (RWST r w s m) = PopError m

Methods

liftError :: PopError (RWST r w s m) a -> RWST r w s m a Source #

(ErrorStack m, Monoid w) => ErrorStack (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (RWST r w s m) = PopError m

Methods

liftError :: PopError (RWST r w s m) a -> RWST r w s m a Source #

(ErrorStack m, Monoid w) => ErrorStack (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Stack.Error

Associated Types

type PopError (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Error

type PopError (RWST r w s m) = PopError m

Methods

liftError :: PopError (RWST r w s m) a -> RWST r w s m a Source #

type ErrorDepth (n :: Nat) (m :: Type -> Type) = IteratePop n ExceptT m Source #

type MonadErrorDepth (n :: Nat) (m :: Type -> Type) e = (ErrorConstraints n m, MonadError e (ErrorDepth n m)) Source #

depthError :: forall (n :: Nat) m a. ErrorConstraints n m => ErrorDepth n m a -> m a Source #