statestack-0.2: Simple State-like monad transformer with saveable and restorable state

Maintainerbyorgey@cis.upenn.edu
Safe HaskellNone

Control.Monad.StateStack

Contents

Description

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

Synopsis

The MonadStateStack class

class MonadState s m => MonadStateStack s m whereSource

Class of monads which support a state along with a stack for saving and restoring states.

Methods

saveSource

Arguments

:: m ()

Save the current state on the stack

restoreSource

Arguments

:: m ()

Restore the top state from the stack

Instances

MonadStateStack s m => MonadStateStack s (MaybeT m) 
MonadStateStack s m => MonadStateStack s (ListT m) 
MonadStateStack s m => MonadStateStack s (IdentityT m) 
(Monoid w, MonadStateStack s m) => MonadStateStack s (WriterT w m) 
(Monoid w, MonadStateStack s m) => MonadStateStack s (WriterT w m) 
MonadStateStack s m => MonadStateStack s (StateT s m) 
MonadStateStack s m => MonadStateStack s (StateT s m) 
MonadStateStack s m => MonadStateStack s (ReaderT r m) 
(Error e, MonadStateStack s m) => MonadStateStack s (ErrorT e m) 
MonadStateStack s m => MonadStateStack s (ContT r m) 
Monad m => MonadStateStack s (StateStackT s m) 

The StateStackT transformer

newtype StateStackT s m a Source

A monad transformer which adds a save/restorable state to an existing monad.

Constructors

StateStackT 

Fields

unStateStackT :: StateT (s, [s]) m a
 

Instances

Monad m => MonadState s (StateStackT s m) 
Monad m => MonadStateStack s (StateStackT s m) 
MonadTrans (StateStackT s) 
Monad m => Monad (StateStackT s m) 
Functor m => Functor (StateStackT s m) 
(Monad m, Functor m) => Applicative (StateStackT s m) 
MonadIO m => MonadIO (StateStackT s m) 
MonadCont m => MonadCont (StateStackT s m) 

type StateStack s a = StateStackT s Identity aSource

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 aSource

Like runStateStackT, but discard the final state.

execStateStackT :: Monad m => StateStackT s m a -> s -> m sSource

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 -> aSource

Like runStateStack, but discard the final state.

execStateStack :: StateStack s a -> s -> sSource

Like runStateStack, but discard the return value and yield only the final state.

liftState :: Monad m => StateT s m a -> StateStackT s m aSource

StateT computations can always be lifted to StateStackT computations which do not manipulate the state stack.