monad-classes-0.3.0.1: more flexible mtl

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Classes.Run

Contents

Description

Functions to run outer layers of monadic stacks.

These are provided for convenience only; you can use the running functions (like runState) from the transformers' modules directly.

Note that reader and state runners have their arguments swapped around; this makes it convenient to chain them.

Synopsis

Identity

run :: Identity a -> a Source

Reader

runReader :: r -> ReaderT r m a -> m a Source

State

runStateLazy :: s -> StateT s m a -> m (a, s) Source

runStateStrict :: s -> StateT s m a -> m (a, s) Source

evalStateLazy :: Monad m => s -> StateT s m a -> m a Source

evalStateStrict :: Monad m => s -> StateT s m a -> m a Source

execStateLazy :: Monad m => s -> StateT s m a -> m s Source

execStateStrict :: Monad m => s -> StateT s m a -> m s Source

Writer

runWriterLazy :: (Monad m, Monoid w) => WriterT w m a -> m (a, w) Source

runWriterStrict :: (Monad m, Monoid w) => StateT w m a -> m (a, w) Source

evalWriterLazy :: (Monad m, Monoid w) => WriterT w m a -> m a Source

evalWriterStrict :: (Monad m, Monoid w) => StateT w m a -> m a Source

execWriterLazy :: (Monad m, Monoid w) => WriterT w m a -> m w Source

execWriterStrict :: (Monad m, Monoid w) => StateT w m a -> m w Source

evalWriterWith :: forall w m a. (w -> m ()) -> CustomWriterT w m a -> m a Source

mapWriter :: forall w1 w2 m a. MonadWriter w2 m => (w1 -> w2) -> CustomWriterT w1 m a -> m a Source

Transform all writer requests with a given function

newtype CustomWriterT' w n m a Source

Constructors

CustomWriterT (Proxied (w -> n ()) m a) 

Instances

Monad m => MonadWriterN Zero w (CustomWriterT' * w m m) 
MonadBase b m => MonadBase b (CustomWriterT' * w n m) 
MonadBaseControl b m => MonadBaseControl b (CustomWriterT' * w n m) 
MonadTrans (CustomWriterT' * w n) 
MonadTransControl (CustomWriterT' * w n) 
Alternative m => Alternative (CustomWriterT' * w n m) 
Monad m => Monad (CustomWriterT' * w n m) 
Functor m => Functor (CustomWriterT' * w n m) 
MonadPlus m => MonadPlus (CustomWriterT' * w n m) 
Applicative m => Applicative (CustomWriterT' * w n m) 
MonadIO m => MonadIO (CustomWriterT' * w n m) 
type CanDo * (CustomWriterT' * w n m) eff 
type StT (CustomWriterT' * w n) a = StT (Proxied * (w -> n ())) a 
type StM (CustomWriterT' * w n m) a = ComposeSt (CustomWriterT' * w n) m a 

type CustomWriterT w m a = CustomWriterT' w m m a Source

Except

runExcept :: ExceptT e m a -> m (Either e a) Source

runMaybe :: MaybeT m a -> m (Maybe a) Source

Zoom

runZoom :: forall big small m a. (forall f. Functor f => (small -> f small) -> big -> f big) -> ZoomT big small m a -> m a Source

newtype ZoomT big small m a Source

Constructors

ZoomT (Proxied (VLLens big small) m a) 

Instances

MonadState big m => MonadStateN Zero small (ZoomT * big small m) 
MonadReader big m => MonadReaderN Zero small (ZoomT * big small m) 
(MonadState big m, Monoid small) => MonadWriterN Zero small (ZoomT * big small m) 
MonadBase b m => MonadBase b (ZoomT * big small m) 
MonadBaseControl b m => MonadBaseControl b (ZoomT * big small m) 
MonadTrans (ZoomT * big small) 
MonadTransControl (ZoomT * big small) 
Alternative m => Alternative (ZoomT * big small m) 
Monad m => Monad (ZoomT * big small m) 
Functor m => Functor (ZoomT * big small m) 
MonadPlus m => MonadPlus (ZoomT * big small m) 
Applicative m => Applicative (ZoomT * big small m) 
MonadIO m => MonadIO (ZoomT * big small m) 
type CanDo * (ZoomT * big small m) eff 
type StT (ZoomT * big small) a = a 
type StM (ZoomT * big small m) a = StM m a