mstate-0.2.7: MState: A consistent State monad for concurrent applications.

Portabilityportable
Stabilityunstable
Maintainermail@n-sch.de
Safe HaskellSafe-Inferred

Control.Concurrent.MState

Contents

Description

MState: A consistent state monad for concurrent applications.

Synopsis

The MState Monad

data MState t m a Source

The MState monad is a state monad for concurrent applications. To create a new thread sharing the same (modifiable) state use the forkM function.

Instances

runMStateSource

Arguments

:: MonadPeelIO m 
=> MState t m a

Action to run

-> t

Initial state value

-> m (a, t) 

Run a MState application, returning both, the function value and the final state. Note that this function has to wait for all threads to finish before it can return the final state.

evalMStateSource

Arguments

:: MonadPeelIO m 
=> Bool

Wait for all threads to finish?

-> MState t m a

Action to evaluate

-> t

Initial state value

-> m a 

Run a MState application, ignoring the final state. If the first argument is True this function will wait for all threads to finish before returning the final result, otherwise it will return the function value as soon as its acquired.

execMStateSource

Arguments

:: MonadPeelIO m 
=> MState t m a

Action to execute

-> t

Initial state value

-> m t 

Run a MState application, ignoring the function value. This function will wait for all threads to finish before returning the final state.

mapMState :: (MonadIO m, MonadIO n) => (m (a, t) -> n (b, t)) -> MState t m a -> MState t n bSource

Map a stateful computation from one (return value, state) pair to another. See Control.Monad.State.Lazy for more information. Be aware that both MStates still share the same state.

mapMState_ :: (MonadIO m, MonadIO n) => (m a -> n b) -> MState t m a -> MState t n bSource

modifyM :: MonadIO m => (t -> (a, t)) -> MState t m aSource

Modify the MState, block all other threads from accessing the state in the meantime (using atomically from the Control.Concurrent.STM library).

modifyM_ :: MonadIO m => (t -> t) -> MState t m ()Source

Concurrency

forkM :: MonadPeelIO m => MState t m () -> MState t m ThreadIdSource

Start a new stateful thread.

forkM_ :: MonadPeelIO m => MState t m () -> MState t m ()Source

killMState :: MonadPeelIO m => MState t m ()Source

Kill all threads in the current MState application.

waitM :: MonadPeelIO m => ThreadId -> MState t m ()Source

Wait for a thread to finish

Example

Example usage:

 import Control.Concurrent
 import Control.Concurrent.MState
 import Control.Monad.State

 type MyState a = MState Int IO a

 -- Expected state value: 2
 main :: IO ()
 main = print =<< execMState incTwice 0

 incTwice :: MyState ()
 incTwice = do
     -- increase in the current thread
     inc
     -- This thread should get killed before it can "inc" our state:
     t_id <- forkM $ do
         delay 2
         inc
     -- Second increase with a small delay in a forked thread, killing the
     -- thread above
     forkM $ do
         delay 1
         inc
         kill t_id
     return ()
   where
     inc   = modifyM (+1)
     kill  = liftIO . killThread
     delay = liftIO . threadDelay . (*1000000) -- in seconds