| 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
- module Control.Monad.State.Class
- runMState :: Forkable m => MState t m a -> t -> m (a, t)
- evalMState :: Forkable m => Bool -> 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
- modifyM :: MonadIO m => (t -> t) -> MState t m ()
- class MonadPeelIO m => Forkable m where
- forkM :: Forkable m => MState t m () -> MState t m ThreadId
- killMState :: Forkable m => MState t m ()
The MState Monad
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
| 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) | |
| MonadTransPeel (MState t) | |
| 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) | |
| MonadPeelIO m => MonadPeelIO (MState t m) | |
| MonadIO m => MonadIO (MState t m) | |
| MonadCont m => MonadCont (MState t m) |
module Control.Monad.State.Class
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.
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.
modifyM :: MonadIO m => (t -> t) -> MState t m ()Source
Modify the MState, block all other threads from accessing the state in the
meantime (using atomically from the Control.Concurrent.STM library).
Concurrency
class MonadPeelIO m => Forkable m whereSource
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