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

Portabilityportable
Stabilityunstable
Maintainermail@n-sch.de

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 is an abstract data definition for a State monad which can be used in concurrent applications. Use forkM to start a new thread with the same state.

Instances

MonadError e m => MonadError e (MState t m) 
MonadReader r m => MonadReader r (MState t m) 
MonadIO m => MonadState t (MState t m) 
MonadWriter w m => MonadWriter w (MState t m) 
MonadTrans (MState t) 
Monad m => Monad (MState t m) 
Monad m => Functor (MState t m) 
MonadFix m => MonadFix (MState t m) 
MonadPlus m => MonadPlus (MState t m) 
MonadIO m => MonadIO (MState t m) 
MonadCont m => MonadCont (MState t m) 

runMStateSource

Arguments

:: Forkable 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

evalMStateSource

Arguments

:: Forkable m 
=> MState t m a

Action to evaluate

-> t

Initial state value

-> m a 

Run a MState application, ignoring the final state

execMStateSource

Arguments

:: Forkable m 
=> MState t m a

Action to execute

-> t

Initial state value

-> m t 

Run a MState application, ignoring the function value

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.

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

Apply a function to the state before running the MState

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

Modify the MState, block all other threads from accessing the state in the meantime.

Concurrency

class MonadPeelIO m => Forkable m whereSource

Typeclass for forkable monads, for instance:

 instance Forkable IO where
   fork = forkIO

This is only the basic information about how to fork a new thread in the current monad. To start a new thread in a MState application you should always use forkM.

Methods

fork :: m () -> m ThreadIdSource

Instances

forkMSource

Arguments

:: Forkable m 
=> MState t m ()

State action to be forked

-> MState t m ThreadId 

Start a new thread, using the fork function from the Forkable type class. When using this function, the main process will wait for all child processes 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
 
     -- First increase in the current thread
     inc
     -- This thread should get killed before it can "inc" our state:
     kill =<< forkM incDelayed
     -- Second increase with a small delay in a forked thread
     forkM incDelayed
 
     return ()
 
   where
     inc        = modifyM (+1)
     kill       = liftIO . killThread
     incDelayed = do liftIO $ threadDelay 2000000
                     inc