| Portability | non-portable (requires STM) |
|---|---|
| Stability | experimental |
| Maintainer | Peter Robinson <robinson@ecs.tuwien.ac.at> |
Control.Concurrent.AdvSTM
Contents
Description
Extends Control.Concurrent.STM with IO hooks
- class Monad m => MonadAdvSTM m where
- onCommit :: IO () -> m ()
- unsafeOnRetry :: IO () -> m ()
- orElse :: m a -> m a -> m a
- retry :: m a
- check :: Bool -> m ()
- alwaysSucceeds :: m a -> m ()
- always :: m Bool -> m ()
- runAtomic :: m a -> IO a
- catchSTM :: Exception e => m a -> (e -> m a) -> m a
- liftAdv :: STM a -> m a
- readTVar :: TVar a -> m a
- writeTVar :: TVar a -> a -> m ()
- newTVar :: a -> m (TVar a)
- data AdvSTM a
- unsafeRetryWith :: (Monad m, MonadAdvSTM m) => IO () -> m b
- atomically :: AdvSTM a -> IO a
- unsafeIOToAdvSTM :: IO a -> AdvSTM a
- debugAdvSTM :: String -> Int -> AdvSTM ()
- debugMode :: Bool -> AdvSTM ()
Class MonadAdvSTM
class Monad m => MonadAdvSTM m whereSource
A type class for extended-STM monads. For a concrete instantiation see
AdvSTM
Methods
onCommit :: IO () -> m ()Source
Takes an IO action that will be executed iff the transaction commits.
- When a TVar was modified in a transaction and this transaction commits, this update remains invisible to other threads until the corresponding onCommit action was run.
- If the onCommit action throws an exception, the original value of the TVars will be restored.
- Accessing a modified TVar within the onCommit action will cause a
Deadlockexception to be thrown.
As a general rule, onCommit should
only be used for "real" (i.e. without atomic blocks) IO actions and is certainly
not the right place to fiddle with TVars. For example, if you wanted to
write a TVar value to a file on commit, you could write:
tvar <- newTVarIO "bla"
atomically $ do
x <- readTVar tvar
onCommit (writeFile "myfile" x)
Adds an IO action to the retry job-queue. If the transaction retries, a new helper thread is forked that runs the retry actions, and, after the helper thread is done, the transaction retries.
Uses unsafeIOToSTM to fork a helper thread that runs the retry
actions.
orElse :: m a -> m a -> m aSource
See orElse
Runs any IO actions added by unsafeOnRetry and then retries the
transaction.
See check
alwaysSucceeds :: m a -> m ()Source
See alwaysSucceeds
always :: m Bool -> m ()Source
See always
runAtomic :: m a -> IO aSource
Runs a transaction atomically in the IO monad.
catchSTM :: Exception e => m a -> (e -> m a) -> m aSource
See catchSTM
Lifts STM actions to MonadAdvSTM.
readTVar :: TVar a -> m aSource
Reads a value from a TVar. Blocks until the IO onCommit action(s) of
the corresponding transaction are complete.
See onCommit for a more detailed description of this behaviour.
writeTVar :: TVar a -> a -> m ()Source
Writes a value to a TVar. Blocks until the onCommit IO-action(s) are
complete. See onCommit for details.
newTVar :: a -> m (TVar a)Source
See newTVar
Instances
Monad AdvSTM
Drop-in replacement for the STM monad
unsafeRetryWith :: (Monad m, MonadAdvSTM m) => IO () -> m bSource
Adds the IO action to the retry queue and then retries the transaction
atomically :: AdvSTM a -> IO aSource
See atomically
unsafeIOToAdvSTM :: IO a -> AdvSTM aSource
See unsafeIOToSTM