effect-stack-0.3: Reducing the pain of transformer stacks with duplicated effects

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Stack.State

Documentation

class Monad m => StateStack m where Source #

Associated Types

type PopState m :: * -> * Source #

Methods

liftState :: PopState m a -> m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (MaybeT m) :: Type -> Type Source #

Methods

liftState :: PopState (MaybeT m) a -> MaybeT m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (IdentityT m) :: Type -> Type Source #

Methods

liftState :: PopState (IdentityT m) a -> IdentityT m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (ExceptT e m) :: Type -> Type Source #

Methods

liftState :: PopState (ExceptT e m) a -> ExceptT e m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (ReaderT r m) :: Type -> Type Source #

Methods

liftState :: PopState (ReaderT r m) a -> ReaderT r m a Source #

Monad m => StateStack (StateT s m) Source # 
Instance details

Defined in Control.Monad.Stack.State

Associated Types

type PopState (StateT s m) :: Type -> Type Source #

Methods

liftState :: PopState (StateT s m) a -> StateT s m a Source #

Monad m => StateStack (StateT s m) Source # 
Instance details

Defined in Control.Monad.Stack.State

Associated Types

type PopState (StateT s m) :: Type -> Type Source #

Methods

liftState :: PopState (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (WriterT w m) :: Type -> Type Source #

Methods

liftState :: PopState (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (WriterT w m) :: Type -> Type Source #

Methods

liftState :: PopState (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (AccumT w m) :: Type -> Type Source #

Methods

liftState :: PopState (AccumT w m) a -> AccumT w m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (WriterT w m) :: Type -> Type Source #

Methods

liftState :: PopState (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (SelectT r m) :: Type -> Type Source #

Methods

liftState :: PopState (SelectT r m) a -> SelectT r m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (ContT r m) :: Type -> Type Source #

Methods

liftState :: PopState (ContT r m) a -> ContT r m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (RWST r w s m) :: Type -> Type Source #

Methods

liftState :: PopState (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (RWST r w s m) :: Type -> Type Source #

Methods

liftState :: PopState (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.State

Associated Types

type PopState (RWST r w s m) :: Type -> Type Source #

Methods

liftState :: PopState (RWST r w s m) a -> RWST r w s m a Source #

depthState :: forall n m a. StateConstraints n m => StateDepth n m a -> m a Source #