dejafu-0.1.0.0: Overloadable primitives for testable, potentially non-deterministic, concurrency.

Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.STM

Contents

Description

A MonadSTM implementation, which can be run on top of IO or ST.

Synopsis

The STMLike Monad

data STMLike t n r a Source

The MonadSTM implementation, it encapsulates a single atomic transaction. The environment, that is, the collection of defined CTVars is implicit, there is no list of them, they exist purely as references. This makes the types simpler, but means you can't really get an aggregate of them (if you ever wanted to for some reason).

Instances

Monad (STMLike t n r) 
Functor (STMLike t n r) 
Applicative (STMLike t n r) 
MonadThrow (STMLike t n r) 
MonadCatch (STMLike t n r) 
Monad n => MonadSTM (STMLike t n r) 
type CTVar (STMLike t n r) = CTVar t r 

type STMST t a = STMLike t (ST t) (STRef t) a Source

A convenience wrapper around STMLike using STRefs.

type STMIO t a = STMLike t IO IORef a Source

A convenience wrapper around STMLike using IORefs.

data Result a Source

The result of an STM transaction, along with which CTVars it touched whilst executing.

Constructors

Success [CTVarId] [CTVarId] a

The transaction completed successfully, reading the first list CTVars and writing to the second.

Retry [CTVarId]

The transaction aborted by calling retry, and read the returned CTVars. It should be retried when at least one of the CTVars has been mutated.

Exception SomeException

The transaction aborted by throwing an exception.

Instances

runTransaction :: (forall t. STMST t a) -> Result a Source

Run a transaction in the ST monad, starting from a clean environment, and discarding the environment afterwards. This is suitable for testing individual transactions, but not for composing multiple ones.

runTransactionST :: STMST t a -> CTVarId -> ST t (Result a, CTVarId) Source

Run a transaction in the ST monad, returning the result and new initial CTVarId. If the transaction ended by calling retry, any CTVar modifications are undone.

runTransactionIO :: STMIO t a -> CTVarId -> IO (Result a, CTVarId) Source

Run a transaction in the IO monad, returning the result and new initial CTVarId. If the transaction ended by calling retry, any CTVar modifications are undone.

Software Transactional Memory

retry :: Monad n => STMLike t n r a Source

Abort the current transaction, restoring any CTVars written to, and returning the list of CTVars read.

orElse :: Monad n => STMLike t n r a -> STMLike t n r a -> STMLike t n r a Source

Run the first transaction and, if it retrys,

check :: Monad n => Bool -> STMLike t n r () Source

Check whether a condition is true and, if not, call retry.

throwSTM :: Exception e => e -> STMLike t n r a Source

Throw an exception. This aborts the transaction and propagates the exception.

catchSTM :: Exception e => STMLike t n r a -> (e -> STMLike t n r a) -> STMLike t n r a Source

Handling exceptions from throwSTM.

CTVars

data CTVar t r a Source

A CTVar is a tuple of a unique ID and the value contained. The ID is so that blocked transactions can be re-run when a CTVar they depend on has changed.

type CTVarId = Int Source

The unique ID of a CTVar. Only meaningful within a single concurrent computation.

newCTVar :: Monad n => a -> STMLike t n r (CTVar t r a) Source

Create a new CTVar containing the given value.

readCTVar :: Monad n => CTVar t r a -> STMLike t n r a Source

Return the current value stored in a CTVar.

writeCTVar :: Monad n => CTVar t r a -> a -> STMLike t n r () Source

Write the supplied value into the CTVar.