| Copyright | (c) Edward Kmett & Sjoerd Visscher 2011 | 
|---|---|
| License | BSD3 | 
| Maintainer | ekmett@gmail.com | 
| Stability | experimental | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Control.Monad.Representable.State
Description
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 :: Representable g => State g a -> Rep g -> (a, Rep g)
- evalState :: Representable g => State g a -> Rep g -> a
- execState :: Representable g => State g a -> Rep g -> Rep g
- mapState :: Functor g => ((a, Rep g) -> (b, Rep g)) -> State g a -> State g b
- newtype StateT g m a = StateT {}
- stateT :: Representable g => (Rep g -> m (a, Rep g)) -> StateT g m a
- runStateT :: Representable g => StateT g m a -> Rep g -> m (a, Rep g)
- evalStateT :: (Representable g, Monad m) => StateT g m a -> Rep g -> m a
- execStateT :: (Representable g, Monad m) => StateT g m a -> Rep g -> m (Rep g)
- mapStateT :: Functor g => (m (a, Rep g) -> n (b, Rep g)) -> StateT g m a -> StateT g n b
- liftCallCC :: Representable g => ((((a, Rep g) -> m (b, Rep g)) -> m (a, Rep g)) -> m (a, Rep g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a
- liftCallCC' :: Representable g => ((((a, Rep g) -> m (b, Rep g)) -> m (a, Rep g)) -> m (a, Rep g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a
- class Monad m => MonadState s (m :: * -> *) | m -> s where
Documentation
type State g = StateT g Identity Source #
A memoized state monad parameterized by a representable functor g, where
 the representatation of g, Rep 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.
Arguments
| :: Representable g | |
| => State g a | state-passing computation to execute | 
| -> Rep g | initial state | 
| -> (a, Rep g) | return value and final state | 
Unwrap a state monad computation as a function.
 (The inverse of state.)
Arguments
| :: Representable g | |
| => State g a | state-passing computation to execute | 
| -> Rep g | initial value | 
| -> a | return value of the state computation | 
Arguments
| :: Representable g | |
| => State g a | state-passing computation to execute | 
| -> Rep g | initial value | 
| -> Rep g | final state | 
A state transformer monad parameterized by:
- g- A representable functor used to memoize results for a state- Rep 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.
Instances
| (Functor f, Representable g, MonadFree f m) => MonadFree f (StateT g m) Source # | |
| (Representable g, MonadWriter w m) => MonadWriter w (StateT g m) Source # | |
| (Representable g, Monad m, (~) * (Rep g) s) => MonadState s (StateT g m) Source # | |
| (Representable g, MonadReader e m) => MonadReader e (StateT g m) Source # | |
| Representable f => MonadTrans (StateT f) Source # | |
| Representable f => BindTrans (StateT f) Source # | |
| (Representable g, Monad m) => Monad (StateT g m) Source # | |
| (Functor g, Functor m) => Functor (StateT g m) Source # | |
| (Representable g, Functor m, Monad m) => Applicative (StateT g m) Source # | |
| (Representable g, MonadCont m) => MonadCont (StateT g m) Source # | |
| (Representable g, Bind m) => Apply (StateT g m) Source # | |
| (Representable g, Bind m) => Bind (StateT g m) Source # | |
evalStateT :: (Representable g, Monad m) => StateT g m a -> Rep g -> m a Source #
Evaluate a state computation with the given initial state and return the final value, discarding the final state.
- evalStateTm s =- liftM- fst(- runStateTm s)
execStateT :: (Representable g, Monad m) => StateT g m a -> Rep g -> m (Rep g) Source #
Evaluate a state computation with the given initial state and return the final state, discarding the final value.
- execStateTm s =- liftM- snd(- runStateTm s)
liftCallCC :: Representable g => ((((a, Rep g) -> m (b, Rep g)) -> m (a, Rep g)) -> m (a, Rep g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a Source #
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, Rep g) -> m (b, Rep g)) -> m (a, Rep g)) -> m (a, Rep g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a Source #
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.
class Monad m => MonadState s (m :: * -> *) | m -> s where #
Minimal definition is either both of get and put or just state
Methods
Return the state from the internals of the monad.
Replace the state inside the monad.
state :: (s -> (a, s)) -> m a #
Embed a simple state action into the monad.
Instances
| MonadState s m => MonadState s (MaybeT m) | |
| MonadState s m => MonadState s (ListT m) | |
| (Functor m, MonadState s m) => MonadState s (Free m) | |
| (Representable g, Monad m, (~) * (Rep g) s) => MonadState s (StateT g m) # | |
| (Monoid w, MonadState s m) => MonadState s (WriterT w m) | |
| (Monoid w, MonadState s m) => MonadState s (WriterT w m) | |
| Monad m => MonadState s (StateT s m) | |
| Monad m => MonadState s (StateT s m) | |
| MonadState s m => MonadState s (IdentityT * m) | |
| MonadState s m => MonadState s (ExceptT e m) | |
| (Error e, MonadState s m) => MonadState s (ErrorT e m) | |
| MonadState s m => MonadState s (ReaderT * r m) | |
| MonadState s m => MonadState s (ContT * r m) | |
| (Monad m, Monoid w) => MonadState s (RWST r w s m) | |
| (Monad m, Monoid w) => MonadState s (RWST r w s m) | |