| Copyright | (c) Ivan Lazar Miljenovic |
|---|---|
| License | 3-Clause BSD-style |
| Maintainer | Ivan.Miljenovic@gmail.com |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.Monad.Levels.RWS.Lazy
Description
Note that the original definitions are used for the various reader,
writer and state computations: as such, if there is (for example)
another level that satisfies 'IsReader r' above the one that satisfies
'IsRWS r w s' in the stack, then calling ask will use the higher
level.
- newtype RWST r w s m a :: * -> * -> * -> (* -> *) -> * -> * = RWST {
- runRWST :: r -> s -> m (a, s, w)
- module Control.Monad.Levels.RWS
Documentation
newtype RWST r w s m a :: * -> * -> * -> (* -> *) -> * -> *
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
| (MonadTower m, Monoid w) => IsRWS r w s (RWST r w s m) | |
| (MonadTower m, Monoid w) => IsReader r (RWST r w s m) | |
| (MonadTower m, Monoid w) => IsState s (RWST r w s m) | |
| (Monoid w, MonadTower m) => IsWriter w (RWST r w s m) | |
| Monoid w => MonadTrans (RWST r w s) | |
| (Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) | |
| (Monoid w, Monad m) => Monad (RWST r w s m) | |
| Functor m => Functor (RWST r w s m) | |
| (Monoid w, MonadFix m) => MonadFix (RWST r w s m) | |
| (Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
| (Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
| (Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
| (Monoid w, MonadTower m) => MonadLevel_ (RWST r w s m) | |
| (Monoid w, MonadTower m) => MonadTower_ (RWST r w s m) | |
| type LowerMonad (RWST r w s m) = m | |
| type WithLower_ (RWST r w s m) = AddIG | |
| type AllowOtherValues (RWST r w s m) = True | |
| type DefaultAllowConstraints (RWST r w s m) = True | |
| type BaseMonad (RWST r w s m) = BaseMonad m | |
| type InnerValue (RWST r w s m) a = (a, s, w) |
module Control.Monad.Levels.RWS