Stability | experimental |
---|---|
Maintainer | ekmett@gmail.com |
Safe Haskell | None |
A generalized State monad, parameterized by a Representable functor. The representation of that functor serves as the state.
- type State g = StateT g Identity
- runState :: Indexable g => State g a -> Key g -> (a, Key g)
- evalState :: Indexable g => State g a -> Key g -> a
- execState :: Indexable g => State g a -> Key g -> Key g
- mapState :: Functor g => ((a, Key g) -> (b, Key g)) -> State g a -> State g b
- newtype StateT g m a = StateT {}
- stateT :: Representable g => (Key g -> m (a, Key g)) -> StateT g m a
- runStateT :: Indexable g => StateT g m a -> Key g -> m (a, Key g)
- evalStateT :: (Indexable g, Monad m) => StateT g m a -> Key g -> m a
- execStateT :: (Indexable g, Monad m) => StateT g m a -> Key g -> m (Key g)
- mapStateT :: Functor g => (m (a, Key g) -> n (b, Key g)) -> StateT g m a -> StateT g n b
- liftCallCC :: Representable g => ((((a, Key g) -> m (b, Key g)) -> m (a, Key g)) -> m (a, Key g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a
- liftCallCC' :: Representable g => ((((a, Key g) -> m (b, Key g)) -> m (a, Key g)) -> m (a, Key g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a
- get :: MonadState s m => m s
- gets :: MonadState s m => (s -> a) -> m a
- put :: MonadState s m => s -> m ()
- modify :: MonadState s m => (s -> s) -> m ()
Documentation
type State g = StateT g IdentitySource
A memoized state monad parameterized by a representable functor g
, where
the representatation of g
, Key g
is the state to carry.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
:: Indexable g | |
=> State g a | state-passing computation to execute |
-> Key g | initial state |
-> (a, Key g) | return value and final state |
Unwrap a state monad computation as a function.
(The inverse of state
.)
A state transformer monad parameterized by:
-
g
- A representable functor used to memoize results for a stateKey g
-
m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
(Monad (StateT g m), Functor f, Representable g, MonadFree f m) => MonadFree f (StateT g m) | |
(Monad (StateT g m), Representable g, MonadReader e m) => MonadReader e (StateT g m) | |
(Monad (StateT g m), Representable g, Monad m, ~ * (Key g) s) => MonadState s (StateT g m) | |
(Monoid w, Monad (StateT g m), Representable g, MonadWriter w m) => MonadWriter w (StateT g m) | |
Representable f => MonadTrans (StateT f) | |
(MonadTrans (StateT f), Representable f) => BindTrans (StateT f) | |
(Representable g, Monad m) => Monad (StateT g m) | |
(Functor g, Functor m) => Functor (StateT g m) | |
(Functor (StateT g m), Representable g, Functor m, Monad m) => Applicative (StateT g m) | |
(Monad (StateT g m), Representable g, MonadCont m) => MonadCont (StateT g m) | |
(Functor (StateT g m), Functor g, Indexable g, Bind m) => Apply (StateT g m) | |
(Apply (StateT g m), Functor g, Indexable g, Bind m) => Bind (StateT g m) |
evalStateT :: (Indexable g, Monad m) => StateT g m a -> Key g -> m aSource
Evaluate a state computation with the given initial state and return the final value, discarding the final state.
evalStateT
m s =liftM
fst
(runStateT
m s)
execStateT :: (Indexable g, Monad m) => StateT g m a -> Key g -> m (Key g)Source
Evaluate a state computation with the given initial state and return the final state, discarding the final value.
execStateT
m s =liftM
snd
(runStateT
m s)
liftCallCC :: Representable g => ((((a, Key g) -> m (b, Key g)) -> m (a, Key g)) -> m (a, Key g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m aSource
Uniform lifting of a callCC
operation to the new monad.
This version rolls back to the original state on entering the
continuation.
liftCallCC' :: Representable g => ((((a, Key g) -> m (b, Key g)) -> m (a, Key g)) -> m (a, Key g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m aSource
In-situ lifting of a callCC
operation to the new monad.
This version uses the current state on entering the continuation.
It does not satisfy the laws of a monad transformer.
get :: MonadState s m => m s
Return the state from the internals of the monad.
gets :: MonadState s m => (s -> a) -> m a
Gets specific component of the state, using a projection function supplied.
put :: MonadState s m => s -> m ()
Replace the state inside the monad.
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.