| Portability | portable |
|---|---|
| Stability | unstable |
| Maintainer | mail@n-sch.de |
Control.Concurrent.MState
Contents
Description
MState: A consistent State monad for concurrent applications.
- data MState t m a
- runMState :: Forkable m => MState t m a -> t -> m (a, t)
- evalMState :: Forkable m => MState t m a -> t -> m a
- execMState :: Forkable m => MState t m a -> t -> m t
- mapMState :: (MonadIO m, MonadIO n) => (m (a, t) -> n (b, t)) -> MState t m a -> MState t n b
- withMState :: MonadIO m => (t -> t) -> MState t m a -> MState t m a
- modifyM :: MonadIO m => (t -> t) -> MState t m ()
- class MonadIO m => Forkable m where
- forkM :: Forkable m => MState t m () -> MState t m ThreadId
The MState Monad
The MState is an abstract data definition for a State monad which can be
used in concurrent applications. It can be accessed with evalMState and
execMState. To start a new state thread use forkM.
Instances
| MonadReader r m => MonadReader r (MState t m) | |
| MonadIO m => MonadState t (MState t m) | |
| MonadError e m => MonadError e (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) | |
| MonadCont m => MonadCont (MState t m) | |
| MonadIO m => MonadIO (MState t m) |
Run the MState and return both, the function value and the state value
Evaluate the MState monad with the given initial state, throwing away the final state stored in the MVar.
Execute the MState monad with a given initial state. Returns the value of 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.mapState for more information.
withMState :: MonadIO m => (t -> t) -> MState t m a -> MState t m aSource
Apply this function to this state and return the resulting state.
modifyM :: MonadIO m => (t -> t) -> MState t m ()Source
Modify the MState. Block all other threads from accessing the state.
Concurrency
class MonadIO m => Forkable m whereSource
The class which is needed to start new threads in the MState monad. Don't
confuse this with forkM which should be used to fork new threads!
Start a new thread, using forkIO. 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 = print =<< execMState incTwice 0
incTwice :: MyState ()
incTwice = do
-- First inc
inc
-- This thread should get killed before it can "inc" our state:
kill =<< forkM incDelayed
-- This thread should "inc" our state
forkM incDelayed
return ()
where
inc = get >>= put . (+1)
kill = liftIO . killThread
incDelayed = do liftIO $ threadDelay 2000000
inc