| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trans.State.Ref
Description
An implementation of StateT built on top of mutable references,
providing a proper monad morphism.
Please see the documentation at https://www.stackage.org/package/monad-unlift for more details on using this module.
- data StateRefT ref s m a
- runStateRefT :: (Monad m, s ~ RefElement (ref s), MCState (ref s) ~ PrimState b, MonadBase b m, MutableRef (ref s), PrimMonad b) => StateRefT ref s m a -> s -> m (a, s)
- runStateIORefT :: (Monad m, RealWorld ~ PrimState b, MonadBase b m, PrimMonad b) => StateRefT IORef s m a -> s -> m (a, s)
- runStateSTRefT :: (Monad m, ps ~ PrimState b, MonadBase b m, PrimMonad b) => StateRefT (STRef ps) s m a -> s -> m (a, s)
- module Control.Monad.State.Class
Documentation
data StateRefT ref s m a Source #
Since: 0.1.0
Instances
| MonadBase b m => MonadBase b (StateRefT ref s m) Source # | |
| MonadBaseControl b m => MonadBaseControl b (StateRefT ref s m) Source # | |
| MonadReader r m => MonadReader r (StateRefT ref s m) Source # | Since: 0.2.1 |
| ((~) * (MCState (ref s)) (PrimState b), Monad m, (~) * s (RefElement (ref s)), MutableRef (ref s), PrimMonad b, MonadBase b m) => MonadState s (StateRefT ref s m) Source # | |
| MonadTrans (StateRefT ref s) Source # | |
| MonadTransControl (StateRefT ref s) Source # | |
| Monad m => Monad (StateRefT ref s m) Source # | |
| Functor m => Functor (StateRefT ref s m) Source # | |
| Applicative m => Applicative (StateRefT ref s m) Source # | |
| MonadIO m => MonadIO (StateRefT ref s m) Source # | |
| MonadThrow m => MonadThrow (StateRefT ref s m) Source # | |
| MonadCatch m => MonadCatch (StateRefT ref s m) Source # | |
| MonadMask m => MonadMask (StateRefT ref s m) Source # | |
| MonadResource m => MonadResource (StateRefT ref s m) Source # | |
| type StT (StateRefT ref s) a Source # | |
| type StM (StateRefT ref s m) a Source # | |
runStateRefT :: (Monad m, s ~ RefElement (ref s), MCState (ref s) ~ PrimState b, MonadBase b m, MutableRef (ref s), PrimMonad b) => StateRefT ref s m a -> s -> m (a, s) Source #
Since: 0.1.0
runStateIORefT :: (Monad m, RealWorld ~ PrimState b, MonadBase b m, PrimMonad b) => StateRefT IORef s m a -> s -> m (a, s) Source #
Since: 0.1.0
runStateSTRefT :: (Monad m, ps ~ PrimState b, MonadBase b m, PrimMonad b) => StateRefT (STRef ps) s m a -> s -> m (a, s) Source #
Since: 0.1.0
module Control.Monad.State.Class