monad-classes-0.3.2.2: 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) Source # 

Methods

tellN :: Proxy# Peano Zero -> w -> CustomWriterT' * w m m () Source #

MonadBase b m => MonadBase b (CustomWriterT' * w n m) Source # 

Methods

liftBase :: b α -> CustomWriterT' * w n m α #

MonadBaseControl b m => MonadBaseControl b (CustomWriterT' * w n m) Source # 

Associated Types

type StM (CustomWriterT' * w n m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (CustomWriterT' * w n m) b -> b a) -> CustomWriterT' * w n m a #

restoreM :: StM (CustomWriterT' * w n m) a -> CustomWriterT' * w n m a #

MonadTrans (CustomWriterT' * w n) Source # 

Methods

lift :: Monad m => m a -> CustomWriterT' * w n m a #

MonadTransControl (CustomWriterT' * w n) Source # 

Associated Types

type StT (CustomWriterT' * w n :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (CustomWriterT' * w n) -> m a) -> CustomWriterT' * w n m a #

restoreT :: Monad m => m (StT (CustomWriterT' * w n) a) -> CustomWriterT' * w n m a #

Monad m => Monad (CustomWriterT' * w n m) Source # 

Methods

(>>=) :: CustomWriterT' * w n m a -> (a -> CustomWriterT' * w n m b) -> CustomWriterT' * w n m b #

(>>) :: CustomWriterT' * w n m a -> CustomWriterT' * w n m b -> CustomWriterT' * w n m b #

return :: a -> CustomWriterT' * w n m a #

fail :: String -> CustomWriterT' * w n m a #

Functor m => Functor (CustomWriterT' * w n m) Source # 

Methods

fmap :: (a -> b) -> CustomWriterT' * w n m a -> CustomWriterT' * w n m b #

(<$) :: a -> CustomWriterT' * w n m b -> CustomWriterT' * w n m a #

Applicative m => Applicative (CustomWriterT' * w n m) Source # 

Methods

pure :: a -> CustomWriterT' * w n m a #

(<*>) :: CustomWriterT' * w n m (a -> b) -> CustomWriterT' * w n m a -> CustomWriterT' * w n m b #

liftA2 :: (a -> b -> c) -> CustomWriterT' * w n m a -> CustomWriterT' * w n m b -> CustomWriterT' * w n m c #

(*>) :: CustomWriterT' * w n m a -> CustomWriterT' * w n m b -> CustomWriterT' * w n m b #

(<*) :: CustomWriterT' * w n m a -> CustomWriterT' * w n m b -> CustomWriterT' * w n m a #

MonadIO m => MonadIO (CustomWriterT' * w n m) Source # 

Methods

liftIO :: IO a -> CustomWriterT' * w n m a #

Alternative m => Alternative (CustomWriterT' * w n m) Source # 

Methods

empty :: CustomWriterT' * w n m a #

(<|>) :: CustomWriterT' * w n m a -> CustomWriterT' * w n m a -> CustomWriterT' * w n m a #

some :: CustomWriterT' * w n m a -> CustomWriterT' * w n m [a] #

many :: CustomWriterT' * w n m a -> CustomWriterT' * w n m [a] #

MonadPlus m => MonadPlus (CustomWriterT' * w n m) Source # 

Methods

mzero :: CustomWriterT' * w n m a #

mplus :: CustomWriterT' * w n m a -> CustomWriterT' * w n m a -> CustomWriterT' * w n m a #

type CanDo * (CustomWriterT' * w n m) eff Source # 
type CanDo * (CustomWriterT' * w n m) eff
type StT (CustomWriterT' * w n) a Source # 
type StT (CustomWriterT' * w n) a = StT (Proxied * (w -> n ())) a
type StM (CustomWriterT' * w n m) a Source # 
type StM (CustomWriterT' * w n m) a = ComposeSt (CustomWriterT' * w n) m a

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

MonadReader big m => MonadReaderN Zero small (ZoomT * big small m) Source # 

Methods

askN :: Proxy# Peano Zero -> ZoomT * big small m small Source #

MonadState big m => MonadStateN Zero small (ZoomT * big small m) Source # 

Methods

stateN :: Proxy# Peano Zero -> (small -> (a, small)) -> ZoomT * big small m a Source #

(MonadState big m, Monoid small) => MonadWriterN Zero small (ZoomT * big small m) Source # 

Methods

tellN :: Proxy# Peano Zero -> small -> ZoomT * big small m () Source #

MonadBase b m => MonadBase b (ZoomT * big small m) Source # 

Methods

liftBase :: b α -> ZoomT * big small m α #

MonadBaseControl b m => MonadBaseControl b (ZoomT * big small m) Source # 

Associated Types

type StM (ZoomT * big small m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ZoomT * big small m) b -> b a) -> ZoomT * big small m a #

restoreM :: StM (ZoomT * big small m) a -> ZoomT * big small m a #

MonadTrans (ZoomT * big small) Source # 

Methods

lift :: Monad m => m a -> ZoomT * big small m a #

MonadTransControl (ZoomT * big small) Source # 

Associated Types

type StT (ZoomT * big small :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ZoomT * big small) -> m a) -> ZoomT * big small m a #

restoreT :: Monad m => m (StT (ZoomT * big small) a) -> ZoomT * big small m a #

Monad m => Monad (ZoomT * big small m) Source # 

Methods

(>>=) :: ZoomT * big small m a -> (a -> ZoomT * big small m b) -> ZoomT * big small m b #

(>>) :: ZoomT * big small m a -> ZoomT * big small m b -> ZoomT * big small m b #

return :: a -> ZoomT * big small m a #

fail :: String -> ZoomT * big small m a #

Functor m => Functor (ZoomT * big small m) Source # 

Methods

fmap :: (a -> b) -> ZoomT * big small m a -> ZoomT * big small m b #

(<$) :: a -> ZoomT * big small m b -> ZoomT * big small m a #

Applicative m => Applicative (ZoomT * big small m) Source # 

Methods

pure :: a -> ZoomT * big small m a #

(<*>) :: ZoomT * big small m (a -> b) -> ZoomT * big small m a -> ZoomT * big small m b #

liftA2 :: (a -> b -> c) -> ZoomT * big small m a -> ZoomT * big small m b -> ZoomT * big small m c #

(*>) :: ZoomT * big small m a -> ZoomT * big small m b -> ZoomT * big small m b #

(<*) :: ZoomT * big small m a -> ZoomT * big small m b -> ZoomT * big small m a #

MonadIO m => MonadIO (ZoomT * big small m) Source # 

Methods

liftIO :: IO a -> ZoomT * big small m a #

Alternative m => Alternative (ZoomT * big small m) Source # 

Methods

empty :: ZoomT * big small m a #

(<|>) :: ZoomT * big small m a -> ZoomT * big small m a -> ZoomT * big small m a #

some :: ZoomT * big small m a -> ZoomT * big small m [a] #

many :: ZoomT * big small m a -> ZoomT * big small m [a] #

MonadPlus m => MonadPlus (ZoomT * big small m) Source # 

Methods

mzero :: ZoomT * big small m a #

mplus :: ZoomT * big small m a -> ZoomT * big small m a -> ZoomT * big small m a #

type CanDo * (ZoomT * big small m) eff Source # 
type CanDo * (ZoomT * big small m) eff
type StT (ZoomT * big small) a Source # 
type StT (ZoomT * big small) a = a
type StM (ZoomT * big small m) a Source # 
type StM (ZoomT * big small m) a = StM m a

ReadState

newtype ReadStateT s m a Source #

ReadState is used to translate reader effects into state effects.

If you run a computation with StateT, this handler is not needed, since StateT already handles read requests.

This is useful in cases when you work in an abstract MonadState monad and thus have no guarantee that its handler will also accept reader requests.

Constructors

ReadStateT (IdentityT m a) 

Instances

MonadState s m => MonadReaderN Zero s (ReadStateT * * s m) Source # 

Methods

askN :: Proxy# Peano Zero -> ReadStateT * * s m s Source #

MonadBase b m => MonadBase b (ReadStateT k * x m) Source # 

Methods

liftBase :: b α -> ReadStateT k * x m α #

MonadBaseControl b m => MonadBaseControl b (ReadStateT k * s m) Source # 

Associated Types

type StM (ReadStateT k * s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ReadStateT k * s m) b -> b a) -> ReadStateT k * s m a #

restoreM :: StM (ReadStateT k * s m) a -> ReadStateT k * s m a #

MonadTrans (ReadStateT k * s) Source # 

Methods

lift :: Monad m => m a -> ReadStateT k * s m a #

MonadTransControl (ReadStateT k * x) Source # 

Associated Types

type StT (ReadStateT k * x :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ReadStateT k * x) -> m a) -> ReadStateT k * x m a #

restoreT :: Monad m => m (StT (ReadStateT k * x) a) -> ReadStateT k * x m a #

Monad m => Monad (ReadStateT k * s m) Source # 

Methods

(>>=) :: ReadStateT k * s m a -> (a -> ReadStateT k * s m b) -> ReadStateT k * s m b #

(>>) :: ReadStateT k * s m a -> ReadStateT k * s m b -> ReadStateT k * s m b #

return :: a -> ReadStateT k * s m a #

fail :: String -> ReadStateT k * s m a #

Functor m => Functor (ReadStateT k * s m) Source # 

Methods

fmap :: (a -> b) -> ReadStateT k * s m a -> ReadStateT k * s m b #

(<$) :: a -> ReadStateT k * s m b -> ReadStateT k * s m a #

Applicative m => Applicative (ReadStateT k * s m) Source # 

Methods

pure :: a -> ReadStateT k * s m a #

(<*>) :: ReadStateT k * s m (a -> b) -> ReadStateT k * s m a -> ReadStateT k * s m b #

liftA2 :: (a -> b -> c) -> ReadStateT k * s m a -> ReadStateT k * s m b -> ReadStateT k * s m c #

(*>) :: ReadStateT k * s m a -> ReadStateT k * s m b -> ReadStateT k * s m b #

(<*) :: ReadStateT k * s m a -> ReadStateT k * s m b -> ReadStateT k * s m a #

type CanDo * (ReadStateT * * s m) eff Source # 
type CanDo * (ReadStateT * * s m) eff
type StT (ReadStateT k * x) a Source # 
type StT (ReadStateT k * x) a = StT (IdentityT *) a
type StM (ReadStateT k * s m) a Source # 
type StM (ReadStateT k * s m) a = StM m a

runReadState :: Proxy s -> ReadStateT s m a -> m a Source #