| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Control.Monad.MultiState
Description
The multi-valued version of mtl's State / StateT / MonadState
- newtype MultiStateT x m a = MultiStateT {
- runMultiStateTRaw :: StateT (HList x) m a
- type MultiStateTNull = MultiStateT Null
- type MultiState x = MultiStateT x Identity
- class Monad m => MonadMultiState a m where
- mGetRaw :: Monad m => MultiStateT a m (HList a)
- withMultiState :: Monad m => x -> MultiStateT (Cons x xs) m a -> MultiStateT xs m a
- withMultiStates :: Monad m => HList xs -> MultiStateT (Append xs ys) m a -> MultiStateT ys m a
- evalMultiStateT :: Monad m => MultiStateT Null m a -> m a
- evalMultiStateTWithInitial :: Monad m => HList a -> MultiStateT a m b -> m b
- mapMultiStateT :: (m (a, HList w) -> m' (a', HList w)) -> MultiStateT w m a -> MultiStateT w m' a'
- data Cons car cdr :: * -> * -> *
- data Null :: *
MultiStateT
newtype MultiStateT x m a Source
A State transformer monad patameterized by:
- x - The list of types constituting the state,
- m - The inner monad.
MultiStateT corresponds to mtl's StateT, but can contain
a heterogenous list of types.
This heterogenous list is represented using Types.Data.List, i.e:
For example,
MultiStateT (Cons Int (Cons Bool Null)) :: (* -> *) -> (* -> *)
is a State wrapper containing the types [Int,Bool].
Constructors
| MultiStateT | |
Fields
| |
Instances
| MonadState s m => MonadState s (MultiStateT c m) | |
| MonadWriter w m => MonadWriter w (MultiStateT c m) | |
| (Monad m, ContainsType a c) => MonadMultiState a (MultiStateT c m) | |
| MonadTrans (MultiStateT x) | |
| Monad m => Monad (MultiStateT x m) | |
| Functor f => Functor (MultiStateT x f) | |
| (Applicative m, Monad m) => Applicative (MultiStateT x m) |
type MultiStateTNull = MultiStateT Null Source
A MultiState transformer carrying an empty state.
type MultiState x = MultiStateT x Identity Source
A state monad parameterized by the list of types x of the state to carry.
Similar to State s = StateT s Identity
MonadMultiState class
class Monad m => MonadMultiState a m where Source
All methods must be defined.
The idea is: Any monad stack is instance of MonadMultiState a, iff
the stack contains a MultiStateT x with a element of x.
Methods
state set function for values of type a.
state get function for values of type a.
Instances
| (MonadTrans t, Monad (t m), MonadMultiState a m) => MonadMultiState a (t m) | |
| (Monad m, ContainsType a c) => MonadMultiState a (MultiStateT c m) |
functions
mGetRaw :: Monad m => MultiStateT a m (HList a) Source
A raw extractor of the contained HList (i.e. the complete state).
For a possible usecase, see withMultiStates.
Arguments
| :: Monad m | |
| => x | The value to add |
| -> MultiStateT (Cons x xs) m a | The computation using the enlarged state |
| -> MultiStateT xs m a | An computation using the smaller state |
Adds an element to the state, thereby transforming a MultiStateT over values with types (x:xs) to a MultiStateT over xs.
Think "Execute this computation with this additional value as state".
Arguments
| :: Monad m | |
| => HList xs | The list of values to add |
| -> MultiStateT (Append xs ys) m a | The computation using the enlarged state |
| -> MultiStateT ys m a | A computation using the smaller state |
Adds a heterogenous list of elements to the state, thereby transforming a MultiStateT over values with types xs++ys to a MultiStateT over ys.
Similar to recursively adding single values with withMultiState.
Note that ys can be Null; in that case the return value can be
evaluated further using evalMultiStateT.
evalMultiStateT :: Monad m => MultiStateT Null m a -> m a Source
Evaluate an empty state computation.
Because the state is empty, no initial state must be provided.
Currently it is not directly possible to extract the final state of a
computation (similar to execStateT and runStateT for mtl's StateT),
but you can use mGetRaw if you need such functionality.
If you want to evaluate a computation over any non-Null state, either use
evalMultiStateTWithInitial- simplify the computation using
withMultiState/withMultiStates, then useevalMultiStateTon the result.
evalMultiStateTWithInitial Source
Arguments
| :: Monad m | |
| => HList a | The initial state |
| -> MultiStateT a m b | The computation to evaluate |
| -> m b |
Evaluate a state computation with the given initial state.
mapMultiStateT :: (m (a, HList w) -> m' (a', HList w)) -> MultiStateT w m a -> MultiStateT w m' a' Source
Map both the return value and the state of a computation using the given function.
re-exports
data Cons car cdr :: * -> * -> *
Instances
| (Show a, Show (HList b)) => Show (HList (Cons a b)) | |
| (Monoid x, Monoid (HList xs)) => Monoid (HList (Cons x xs)) | |
| (Show car, Show cdr) => Show (Cons car cdr) | |
| Typeable (* -> * -> *) Cons | |
| type IsNull (Cons car cdr) = False | |
| type Head (Cons car cdr) = car | |
| type Tail (Cons car cdr) = cdr | |
| type Reverse' (Cons car cdr) a = Reverse' cdr (Cons car a) | |
| type Append (Cons car1 cdr2) l2 = Cons car1 (Append cdr2 l2) |