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

Control.Monad.Stack.Cont

Documentation

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

Associated Types

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

Methods

liftCont :: PopCont m a -> m a Source #

Instances

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (MaybeT m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (MaybeT m) = PopCont m

Methods

liftCont :: PopCont (MaybeT m) a -> MaybeT m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (AccumT w m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (AccumT w m) = PopCont m

Methods

liftCont :: PopCont (AccumT w m) a -> AccumT w m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (ExceptT e m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (ExceptT e m) = PopCont m

Methods

liftCont :: PopCont (ExceptT e m) a -> ExceptT e m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (IdentityT m) 
Instance details

Defined in Control.Monad.Stack.Cont

Methods

liftCont :: PopCont (IdentityT m) a -> IdentityT m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (ReaderT r m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (ReaderT r m) = PopCont m

Methods

liftCont :: PopCont (ReaderT r m) a -> ReaderT r m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (SelectT r m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (SelectT r m) = PopCont m

Methods

liftCont :: PopCont (SelectT r m) a -> SelectT r m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (StateT s m) = PopCont m

Methods

liftCont :: PopCont (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (StateT s m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (StateT s m) = PopCont m

Methods

liftCont :: PopCont (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (WriterT w m) = PopCont m

Methods

liftCont :: PopCont (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (WriterT w m) = PopCont m

Methods

liftCont :: PopCont (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (WriterT w m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (WriterT w m) = PopCont m

Methods

liftCont :: PopCont (WriterT w m) a -> WriterT w m a Source #

Monad m => ContStack (ContT r m) Source # 
Instance details

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (ContT r m) 
Instance details

Defined in Control.Monad.Stack.Cont

type PopCont (ContT r m) = m

Methods

liftCont :: PopCont (ContT r m) a -> ContT r m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Cont

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

Methods

liftCont :: PopCont (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Cont

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

Methods

liftCont :: PopCont (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Cont

Associated Types

type PopCont (RWST r w s m) 
Instance details

Defined in Control.Monad.Stack.Cont

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

Methods

liftCont :: PopCont (RWST r w s m) a -> RWST r w s m a Source #

type ContDepth (n :: Nat) (m :: Type -> Type) = IteratePop n ContTag m Source #

type MonadContDepth (n :: Nat) (m :: Type -> Type) = (ContConstraints n m, MonadCont (ContDepth n m)) Source #

depthCont :: forall (n :: Nat) m a. ContConstraints n m => ContDepth n m a -> m a Source #