Copyright | (c) 2011 Brent Yorgey |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | byorgey@cis.upenn.edu |
Safe Haskell | None |
Language | Haskell2010 |
A state monad which allows the state to be saved and restored on a stack.
- Computation type:
- Computations with implicit access to a read/write state, with additional operations for pushing the current state on a stack and later restoring the state from the top of the stack.
- Binding strategy:
- Same as for the usual state monad; the state and accompanying stack of saved states are threaded through computations.
- Useful for:
- Remembering state while emitting commands for some system which itself has saveable/restorable state, such as OpenGL or Cairo.
Simple example:
ghci> let p = get >>= liftIO . print ghci> evalStateStackT (put 2 >> p >> save >> put 3 >> p >> restore >> p) 0 2 3 2
- class MonadState s m => MonadStateStack s m where
- newtype StateStackT s m a = StateStackT {
- unStateStackT :: StateT (s, [s]) m a
- type StateStack s a = StateStackT s Identity a
- runStateStackT :: Monad m => StateStackT s m a -> s -> m (a, s)
- evalStateStackT :: Monad m => StateStackT s m a -> s -> m a
- execStateStackT :: Monad m => StateStackT s m a -> s -> m s
- runStateStack :: StateStack s a -> s -> (a, s)
- evalStateStack :: StateStack s a -> s -> a
- execStateStack :: StateStack s a -> s -> s
- liftState :: Monad m => StateT s m a -> StateStackT s m a
The MonadStateStack
class
class MonadState s m => MonadStateStack s m where Source
Class of monads which support a state along with a stack for saving and restoring states.
:: m () | Save the current state on the stack |
:: m () | Restore the top state from the stack |
MonadStateStack s m => MonadStateStack s (MaybeT m) Source | |
MonadStateStack s m => MonadStateStack s (ListT m) Source | |
MonadStateStack s m => MonadStateStack s (IdentityT m) Source | |
(Monoid w, MonadStateStack s m) => MonadStateStack s (WriterT w m) Source | |
(Monoid w, MonadStateStack s m) => MonadStateStack s (WriterT w m) Source | |
MonadStateStack s m => MonadStateStack s (StateT s m) Source | |
MonadStateStack s m => MonadStateStack s (StateT s m) Source | |
MonadStateStack s m => MonadStateStack s (ReaderT r m) Source | |
MonadStateStack s m => MonadStateStack s (ExceptT e m) Source | |
MonadStateStack s m => MonadStateStack s (ContT r m) Source | |
Monad m => MonadStateStack s (StateStackT s m) Source |
The StateStackT
transformer
newtype StateStackT s m a Source
A monad transformer which adds a save/restorable state to an existing monad.
StateStackT | |
|
Monad m => MonadState s (StateStackT s m) Source | |
Monad m => MonadStateStack s (StateStackT s m) Source | |
MonadTrans (StateStackT s) Source | |
Monad m => Monad (StateStackT s m) Source | |
Functor m => Functor (StateStackT s m) Source | |
Monad m => Applicative (StateStackT s m) Source | |
MonadIO m => MonadIO (StateStackT s m) Source | |
MonadCont m => MonadCont (StateStackT s m) Source |
type StateStack s a = StateStackT s Identity a Source
Running StateStackT
and StateStack
computations
runStateStackT :: Monad m => StateStackT s m a -> s -> m (a, s) Source
Run a StateStackT
computation from an initial state, resulting
in a computation of the underlying monad which yields the return
value and final state.
evalStateStackT :: Monad m => StateStackT s m a -> s -> m a Source
Like runStateStackT
, but discard the final state.
execStateStackT :: Monad m => StateStackT s m a -> s -> m s Source
Like runStateStackT
, but discard the return value and yield
only the final state.
runStateStack :: StateStack s a -> s -> (a, s) Source
Run a StateStack
computation from an initial state, resulting
in a pair of the final return value and final state.
evalStateStack :: StateStack s a -> s -> a Source
Like runStateStack
, but discard the final state.
execStateStack :: StateStack s a -> s -> s Source
Like runStateStack
, but discard the return value and yield
only the final state.
liftState :: Monad m => StateT s m a -> StateStackT s m a Source
StateT
computations can always be lifted to StateStackT
computations which do not manipulate the state stack.