concurrent-state-0.3.1.1: MTL-like library using TVars

Portabilityportable
Stabilityexperimental
Maintainerme@joelt.io
Safe HaskellSafe-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.

Synopsis

Documentation

The StateC monad transformer

data StateC s m a Source

A concurrent state transformer monad parameterized by:

  • s - The state. This is contained in a TVar.
  • 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 => MonadIO (StateC s m) 

Specializations of MonadState operations

modify :: MonadIO m => (s -> s) -> StateC s m ()Source

Monadic state transformer. Maps an old state to a new state inside a state monad. The old state is thrown away.

This is provided because Control.Monad.State's modify function is defined in terms of get and put, which results in two STM actions for every modify. Instead, modify can be specialized as a call to modifyTVar.

Concurrent state operations

runStateCSource

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.

evalStateCSource

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.

execStateCSource

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.

Lifting other operations

liftCallCCC :: ((((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. This version rolls back to the original TVar upon entering the continuation.

liftCallCCC' :: ((((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

In-situ lifting of a callCC operation to the new monad. This version uses the current TVar upon entering the continuation. It does not satisfy the laws of a monad transformer.

liftCatchC :: (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.

liftListenC :: Monad m => (m (a, TVar s) -> m ((a, TVar s), w)) -> StateC s m a -> StateC s m (a, w)Source

Lift a listen operation to the new monad.

liftPassC :: Monad m => (m ((a, TVar s), b) -> m (a, TVar s)) -> StateC s m (a, b) -> StateC s m aSource

Lift a pass operation to the new monad.