stm-io-hooks-0.0.1: An STM monad with IO hooks

Portabilitynon-portable (requires STM)
Stabilityexperimental
MaintainerPeter Robinson <robinson@ecs.tuwien.ac.at>

Control.Concurrent.AdvSTM

Contents

Description

Extends Control.Concurrent.STM with IO hooks

Synopsis

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 Deadlock exception 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)

unsafeOnRetry :: IO () -> m ()Source

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. Warning: Uses unsafeIOToSTM to fork a helper thread that runs the retry actions!

orElse :: m a -> m a -> m aSource

See orElse

retry :: m aSource

See retry. Skips any IO actions added by unsafeOnRetry.

check :: Bool -> m ()Source

See check

alwaysSucceeds :: m a -> m ()Source

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

liftAdv :: STM a -> m aSource

Lifts STM actions to MonadAdvSTM.

Instances

Monad AdvSTM

data AdvSTM a Source

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

debugAdvSTM :: String -> Int -> AdvSTM ()Source

Uses unsafeIOToSTM to output the Thread Id and a message and delays for a given number of ms WARNING: Can lead to deadlocks!

debugMode :: Bool -> AdvSTM ()Source

Switches the debug mode on or off WARNING: Can lead to deadlocks!