| Portability | portable |
|---|---|
| Stability | experimental |
| Maintainer | me@joelt.io |
| Safe Haskell | Safe-Inferred |
Control.Monad.State.Concurrent.Lazy
Contents
Description
Concurrent state monad, providing a State-like interface but allowing for multiple threads to operate on the same value simultaneously.
This module performs state computations lazily. For a strict version, see Control.Monad.State.Concurrent.Strict.
- module Control.Monad.State
- data StateC s m a
- runStateC :: MonadIO m => StateC s m a -> TVar s -> m (a, s)
- evalStateC :: MonadIO m => StateC s m a -> TVar s -> m a
- execStateC :: MonadIO m => StateC s m a -> TVar s -> m s
- runStatesC :: MonadFork m => [StateC s m a] -> s -> m ([a], s)
- evalStatesC :: MonadFork m => [StateC s m a] -> s -> m [a]
- execStatesC :: MonadFork m => [StateC s m a] -> s -> m s
- liftCallCC :: ((((a, TVar s) -> m (b, TVar s)) -> m (a, TVar s)) -> m (a, TVar s)) -> ((a -> StateC s m b) -> StateC s m a) -> StateC s m a
- liftCatch :: (m (a, TVar s) -> (e -> m (a, TVar s)) -> m (a, TVar s)) -> StateC s m a -> (e -> StateC s m a) -> StateC s m a
- liftListen :: Monad m => (m (a, TVar s) -> m ((a, TVar s), w)) -> StateC s m a -> StateC s m (a, w)
- liftPass :: Monad m => (m ((a, TVar s), b) -> m (a, TVar s)) -> StateC s m (a, b) -> StateC s m a
Documentation
module Control.Monad.State
The StateC monad transformer
A concurrent state transformer monad parameterized by:
-
s- The state. This is contained in aTVar. -
m- The inner monad.
The return function leaves the state unchanged, while >>= performs
actions atomically on the held TVar.
This is very similar to transformers' StateT, with the exception of
the MonadIO constraint on every instance, which is necessary to
perform STM actions.
Instances
| (Functor m, MonadIO m) => MonadState s (StateC s m) | |
| MonadTrans (StateC s) | |
| MonadIO m => Monad (StateC s m) | |
| (Functor m, MonadIO m) => Functor (StateC s m) | |
| (MonadIO m, MonadFix m) => MonadFix (StateC s m) | |
| (MonadPlus m, MonadIO m) => MonadPlus (StateC s m) | |
| (Functor m, MonadIO m) => Applicative (StateC s m) | |
| (MonadIO m, Functor m, MonadPlus m) => Alternative (StateC s m) | |
| (MonadIO m, MonadCatch m) => MonadCatch (StateC s m) | |
| MonadIO m => MonadIO (StateC s m) | |
| MonadFork m => MonadFork (StateC s m) |
Concurrent state operations
Arguments
| :: MonadIO m | |
| => StateC s m a | state-passing computation to execute |
| -> TVar s | initial state |
| -> m (a, s) | return value and final state |
Unwrap a concurrent state monad computation as a function.
Arguments
| :: MonadIO m | |
| => StateC s m a | state-passing computation to execute |
| -> TVar s | initial state |
| -> m a | return value |
Evaluate a concurrent state computation with the given initial state and return the final value, discarding the final state.
evalStateCm s =liftMfst(runStateCm s)
Arguments
| :: MonadIO m | |
| => StateC s m a | state-passing computation to execute |
| -> TVar s | initial state |
| -> m s | final state |
Execute a concurrent state computation with the given initial state and return the final state, discarding the final value.
execStateCm s =liftMsnd(runStateCm s)
Running concurrent operations on a single input
Arguments
| :: MonadFork m | |
| => [StateC s m a] | state-passing computations to execute |
| -> s | initial state |
| -> m ([a], s) | return values and final state |
Run multiple state operations on the same value, returning the resultant state and the value produced by each operation.
Arguments
| :: MonadFork m | |
| => [StateC s m a] | state-passing computations to execute |
| -> s | initial state |
| -> m [a] | return values |
Run multiple state operations on the same value, returning all values produced by each operation.
evalStatesCms s =liftMfst(runStatesCms s)
Arguments
| :: MonadFork m | |
| => [StateC s m a] | state-passing computations to execute |
| -> s | initial state |
| -> m s | final state |
Run multiple state operations on the same value, returning the resultant state.
execStatesCms s =liftMsnd(runStatesCms s)
Lifting other operations
liftCallCC :: ((((a, TVar s) -> m (b, TVar s)) -> m (a, TVar s)) -> m (a, TVar s)) -> ((a -> StateC s m b) -> StateC s m a) -> StateC s m aSource
Uniform lifting of a callCC operation to the new monad.
liftCatch :: (m (a, TVar s) -> (e -> m (a, TVar s)) -> m (a, TVar s)) -> StateC s m a -> (e -> StateC s m a) -> StateC s m aSource
Lift a catchError operation to the new monad.