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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Stack.Writer

Documentation

class Monad m => WriterStack m where Source #

Associated Types

type PopWriter m :: * -> * Source #

Methods

liftWriter :: PopWriter m a -> m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (MaybeT m) a -> MaybeT m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (ExceptT e m) a -> ExceptT e m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (ReaderT r m) a -> ReaderT r m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (StateT s m) a -> StateT s m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (AccumT w m) a -> AccumT w m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (WriterT w m) a -> WriterT w m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (SelectT r m) a -> SelectT r m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (ContT r m) a -> ContT r m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (RWST r w s m) a -> RWST r w s m a Source #

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

Defined in Control.Monad.Stack.Writer

Associated Types

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

Methods

liftWriter :: PopWriter (RWST r w s m) a -> RWST r w s m a Source #

depthWriter :: forall n m a. WriterConstraints n m => WriterDepth n m a -> m a Source #