Copyright | (c) Nils Schweinsberg 2010 |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | mail@n-sch.de |
Stability | unstable |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Control.Concurrent.MState
Description
Synopsis
- data MState t m a
- module Control.Monad.State.Class
- runMState :: MonadPeelIO m => MState t m a -> t -> m (a, t)
- evalMState :: MonadPeelIO m => Bool -> MState t m a -> t -> m a
- execMState :: MonadPeelIO 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
- mapMState_ :: MonadIO n => (m a -> n b) -> MState t m a -> MState t n b
- modifyM :: MonadIO m => (t -> (a, t)) -> MState t m a
- modifyM_ :: MonadIO m => (t -> t) -> MState t m ()
- forkM :: MonadPeelIO m => MState t m () -> MState t m ThreadId
- forkM_ :: MonadPeelIO m => MState t m () -> MState t m ()
- killMState :: MonadPeelIO m => MState t m ()
- waitM :: MonadPeelIO m => ThreadId -> 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
module Control.Monad.State.Class
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.
Arguments
:: MonadPeelIO m | |
=> Bool | Wait for all threads to finish? |
-> MState t m a | Action to evaluate |
-> t | Initial state value |
-> m a |
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 b Source #
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 -> (a, t)) -> MState t m a Source #
Modify the MState
, block all other threads from accessing the state in
the meantime (using atomically
from the Control.Concurrent.STM library).
Concurrency
killMState :: MonadPeelIO m => MState t m () Source #
Kill all threads in the current MState
application.
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