Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Version on StateT which evaluates the state strictly at every step
- newtype StrictStateT s m a = StrictStateT {
- runStateT :: s -> m (a, s)
- modify :: MonadState s m => (s -> s) -> m ()
- evalStateT :: Monad m => StrictStateT s m a -> s -> m a
- execStateT :: Monad m => StrictStateT s m a -> s -> m s
- type StrictState s = StrictStateT s Identity
- runState :: StrictState s a -> s -> (a, s)
- evalState :: StrictState s a -> s -> a
- execState :: StrictState s a -> s -> s
Transformer
newtype StrictStateT s m a Source
StrictStateT | |
|
Monad m => MonadState s (StrictStateT s m) | |
MonadTrans (StrictStateT s) | |
Monad m => Monad (StrictStateT s m) | |
Monad m => Functor (StrictStateT s m) | |
Monad m => Applicative (StrictStateT s m) |
modify :: MonadState s m => (s -> s) -> m ()
Monadic state transformer.
Maps an old state to a new state inside a state monad. The old state is thrown away.
Main> :t modify ((+1) :: Int -> Int) modify (...) :: (MonadState Int a) => a ()
This says that modify (+1)
acts over any
Monad that is a member of the MonadState
class,
with an Int
state.
evalStateT :: Monad m => StrictStateT s m a -> s -> m a Source
execStateT :: Monad m => StrictStateT s m a -> s -> m s Source
As base monad
type StrictState s = StrictStateT s Identity Source
runState :: StrictState s a -> s -> (a, s) Source
evalState :: StrictState s a -> s -> a Source
execState :: StrictState s a -> s -> s Source