dejafu-1.0.0.2: A library for unit-testing concurrent programs.

Copyright(c) 2017 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityCPP, ExistentialQuantification, MultiParamTypeClasses, NoMonoLocalBinds, TypeFamilies
Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.Conc.Internal.STM

Contents

Description

MonadSTM testing implementation, internal types and definitions. This module is NOT considered to form part of the public interface of this library.

Synopsis

The S monad

newtype S n r a Source #

The underlying monad is based on continuations over primitive actions.

This is not Cont because we want to give it a custom MonadFail instance.

Constructors

S 

Fields

Instances

Monad (S n r) Source # 

Methods

(>>=) :: S n r a -> (a -> S n r b) -> S n r b #

(>>) :: S n r a -> S n r b -> S n r b #

return :: a -> S n r a #

fail :: String -> S n r a #

Functor (S n r) Source # 

Methods

fmap :: (a -> b) -> S n r a -> S n r b #

(<$) :: a -> S n r b -> S n r a #

MonadFail (S n r) Source # 

Methods

fail :: String -> S n r a #

Applicative (S n r) Source # 

Methods

pure :: a -> S n r a #

(<*>) :: S n r (a -> b) -> S n r a -> S n r b #

liftA2 :: (a -> b -> c) -> S n r a -> S n r b -> S n r c #

(*>) :: S n r a -> S n r b -> S n r b #

(<*) :: S n r a -> S n r b -> S n r a #

Alternative (S n r) Source # 

Methods

empty :: S n r a #

(<|>) :: S n r a -> S n r a -> S n r a #

some :: S n r a -> S n r [a] #

many :: S n r a -> S n r [a] #

MonadPlus (S n r) Source # 

Methods

mzero :: S n r a #

mplus :: S n r a -> S n r a -> S n r a #

MonadSTM (S n r) Source # 

Associated Types

type TVar (S n r :: * -> *) :: * -> * #

Methods

newTVar :: a -> S n r (TVar (S n r) a) #

newTVarN :: String -> a -> S n r (TVar (S n r) a) #

readTVar :: TVar (S n r) a -> S n r a #

writeTVar :: TVar (S n r) a -> a -> S n r () #

MonadThrow (S n r) Source # 

Methods

throwM :: Exception e => e -> S n r a #

MonadCatch (S n r) Source # 

Methods

catch :: Exception e => S n r a -> (e -> S n r a) -> S n r a #

type TVar (S n r) Source # 
type TVar (S n r) = TVar r

Primitive actions

data STMAction n r Source #

STM transactions are represented as a sequence of primitive actions.

Constructors

Exception e => SCatch (e -> S n r a) (S n r a) (a -> STMAction n r) 
SRead (TVar r a) (a -> STMAction n r) 
SWrite (TVar r a) a (STMAction n r) 
SOrElse (S n r a) (S n r a) (a -> STMAction n r) 
SNew String a (TVar r a -> STMAction n r) 
Exception e => SThrow e 
SRetry 
SStop (n ()) 

TVars

newtype TVar r a Source #

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

Constructors

TVar (TVarId, r a) 

Output

data Result a Source #

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

Constructors

Success [TVarId] [TVarId] a

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

Retry [TVarId]

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

Exception SomeException

The transaction aborted by throwing an exception.

Instances

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Execution

runTransaction :: MonadRef r n => S n r a -> IdSource -> n (Result a, IdSource, [TAction]) Source #

Run a transaction, returning the result and new initial TVarId. If the transaction failed, any effects are undone.

doTransaction :: MonadRef r n => S n r a -> IdSource -> n (Result a, n (), IdSource, [TAction]) Source #

Run a STM transaction, returning an action to undo its effects.

If the transaction fails, its effects will automatically be undone, so the undo action returned will be pure ().

stepTrans :: MonadRef r n => STMAction n r -> IdSource -> n (STMAction n r, n (), IdSource, [TVarId], [TVarId], TAction) Source #

Run a transaction for one step.