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

Control.Monad.Stack.Accum

Documentation

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

Associated Types

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

Methods

liftAccum :: PopAccum m a -> m a Source #

Instances

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (MaybeT m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (MaybeT m) = PopAccum m

Methods

liftAccum :: PopAccum (MaybeT m) a -> MaybeT m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (AccumT w m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (AccumT w m) = m

Methods

liftAccum :: PopAccum (AccumT w m) a -> AccumT w m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (ExceptT e m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (ExceptT e m) = PopAccum m

Methods

liftAccum :: PopAccum (ExceptT e m) a -> ExceptT e m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (IdentityT m) 
Instance details

Defined in Control.Monad.Stack.Accum

Methods

liftAccum :: PopAccum (IdentityT m) a -> IdentityT m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (ReaderT r m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (ReaderT r m) = PopAccum m

Methods

liftAccum :: PopAccum (ReaderT r m) a -> ReaderT r m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (SelectT r m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (SelectT r m) = PopAccum m

Methods

liftAccum :: PopAccum (SelectT r m) a -> SelectT r m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (StateT s m) = PopAccum m

Methods

liftAccum :: PopAccum (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (StateT s m) = PopAccum m

Methods

liftAccum :: PopAccum (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (WriterT w m) = PopAccum m

Methods

liftAccum :: PopAccum (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (WriterT w m) = PopAccum m

Methods

liftAccum :: PopAccum (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (WriterT w m) = PopAccum m

Methods

liftAccum :: PopAccum (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (ContT r m) 
Instance details

Defined in Control.Monad.Stack.Accum

type PopAccum (ContT r m) = PopAccum m

Methods

liftAccum :: PopAccum (ContT r m) a -> ContT r m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Accum

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

Methods

liftAccum :: PopAccum (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Accum

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

Methods

liftAccum :: PopAccum (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Accum

Associated Types

type PopAccum (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Accum

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

Methods

liftAccum :: PopAccum (RWST r w s m) a -> RWST r w s m a Source #

type AccumDepth (n :: Nat) (m :: Type -> Type) = IteratePop n AccumT m Source #

depthAccum :: forall (n :: Nat) m a. AccumConstraints n m => AccumDepth n m a -> m a Source #