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

Control.Monad.Stack.Fail

Documentation

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

Associated Types

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

Methods

liftFail :: PopFail m a -> m a Source #

Instances

Instances details
Monad m => FailStack (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (MaybeT m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (MaybeT m) = m

Methods

liftFail :: PopFail (MaybeT m) a -> MaybeT m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (AccumT w m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (AccumT w m) = PopFail m

Methods

liftFail :: PopFail (AccumT w m) a -> AccumT w m a Source #

FailStack m => FailStack (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (ExceptT e m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (ExceptT e m) = PopFail m

Methods

liftFail :: PopFail (ExceptT e m) a -> ExceptT e m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (IdentityT m) 
Instance details

Defined in Control.Monad.Stack.Fail

Methods

liftFail :: PopFail (IdentityT m) a -> IdentityT m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (ReaderT r m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (ReaderT r m) = PopFail m

Methods

liftFail :: PopFail (ReaderT r m) a -> ReaderT r m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (SelectT r m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (SelectT r m) = PopFail m

Methods

liftFail :: PopFail (SelectT r m) a -> SelectT r m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (StateT s m) = PopFail m

Methods

liftFail :: PopFail (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (StateT s m) = PopFail m

Methods

liftFail :: PopFail (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (WriterT w m) = PopFail m

Methods

liftFail :: PopFail (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (WriterT w m) = PopFail m

Methods

liftFail :: PopFail (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (WriterT w m) = PopFail m

Methods

liftFail :: PopFail (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (ContT r m) 
Instance details

Defined in Control.Monad.Stack.Fail

type PopFail (ContT r m) = PopFail m

Methods

liftFail :: PopFail (ContT r m) a -> ContT r m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Fail

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

Methods

liftFail :: PopFail (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Fail

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

Methods

liftFail :: PopFail (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Fail

Associated Types

type PopFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Fail

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

Methods

liftFail :: PopFail (RWST r w s m) a -> RWST r w s m a Source #

type FailDepth (n :: Nat) (m :: Type -> Type) = IteratePop n MaybeT m Source #

type MonadFailDepth (n :: Nat) (m :: Type -> Type) = (FailConstraints n m, MonadFail (FailDepth n m)) Source #

depthFail :: forall (n :: Nat) m a. FailConstraints n m => FailDepth n m a -> m a Source #