| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
Control.Monad.RWS.CPS
- newtype RWST r w s m a = RWST {
- unRWST :: forall x. r -> s -> w -> (a -> s -> w -> m x) -> m x
- runRWST :: (Monad m, Monoid w) => RWST r w s m a -> r -> s -> m (a, s, w)
- evalRWST :: (Monad m, Monoid w) => RWST r w s m a -> r -> s -> m (a, w)
- execRWST :: (Monad m, Monoid w) => RWST r w s m a -> r -> s -> m (s, w)
- module Control.Monad.RWS.Class
The RWST monad transformer
newtype RWST r w s m a Source #
A monad transformer adding reading an environment of type r,
collecting an output of type w and updating a state of type s
to an inner monad m.
Instances
| (Monoid w, Monad m) => MonadRWS r w s (RWST r w s m) Source # | |
| (Monoid w, Monad m) => MonadReader r (RWST r w s m) Source # | |
| (Monad m, Monoid w) => MonadState s (RWST r w s m) Source # | |
| (Monoid w, Monad m) => MonadWriter w (RWST r w s m) Source # | |
| MonadTrans (RWST r w s) Source # | |
| Monad m => Monad (RWST r w s m) Source # | |
| Functor (RWST r w s m) Source # | |
| Applicative (RWST r w s m) Source # | |
| MonadIO m => MonadIO (RWST r w s m) Source # | |
Arguments
| :: (Monad m, Monoid w) | |
| => RWST r w s m a | computation to execute |
| -> r | initial environment |
| -> s | initial value |
| -> m (a, w) | computation yielding final value and output |
Evaluate a computation with the given initial state and environment, returning the final value and output, discarding the final state.
Arguments
| :: (Monad m, Monoid w) | |
| => RWST r w s m a | computation to execute |
| -> r | initial environment |
| -> s | initial value |
| -> m (s, w) | computation yielding final state and output |
Evaluate a computation with the given initial state and environment, returning the final state and output, discarding the final value.
Re-exports
module Control.Monad.RWS.Class