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

Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.Deterministic

Contents

Description

Deterministic traced execution of concurrent computations which don't do IO.

This works by executing the computation on a single thread, calling out to the supplied scheduler after each step to determine which thread runs next.

Synopsis

The Conc Monad

data Conc t a Source

The Conc monad itself. This uses the same universally-quantified indexing state trick as used by ST and STRefs to prevent mutable references from leaking out of the monad.

Instances

Monad (Conc t) 
Functor (Conc t) 
Applicative (Conc t) 
MonadThrow (Conc t) 
MonadCatch (Conc t) 
MonadMask (Conc t) 
MonadConc (Conc t) 
type STMLike (Conc t) = STMLike t (ST t) (STRef t) 
type CVar (Conc t) = CVar t 
type CRef (Conc t) = CRef t 
type ThreadId (Conc t) = Int 

data Failure Source

An indication of how a concurrent computation failed.

Constructors

InternalError

Will be raised if the scheduler does something bad. This should never arise unless you write your own, faulty, scheduler! If it does, please file a bug report.

Deadlock

The computation became blocked indefinitely on CVars.

STMDeadlock

The computation became blocked indefinitely on CTVars.

UncaughtException

An uncaught exception bubbled to the top of the computation.

FailureInNoTest

A computation annotated with _concNoTest produced a failure, rather than a result.

runConc :: Scheduler s -> s -> (forall t. Conc t a) -> (Either Failure a, s, Trace) Source

Run a concurrent computation with a given Scheduler and initial state, returning a failure reason on error. Also returned is the final state of the scheduler, and an execution trace.

Note how the t in Conc is universally quantified, what this means in practice is that you can't do something like this:

runConc roundRobinSched () newEmptyCVar

So mutable references cannot leak out of the Conc computation. If this is making your head hurt, check out the "How runST works" section of https://ocharles.org.uk/blog/guest-posts/2014-12-18-rank-n-types.html

runConc' :: Scheduler s -> s -> (forall t. Conc t a) -> (Either Failure a, s, Trace') Source

Variant of runConc which produces a Trace'.

Concurrency

fork :: Conc t () -> Conc t ThreadId Source

Run the provided computation concurrently.

forkFinally :: Conc t a -> (Either SomeException a -> Conc t ()) -> Conc t ThreadId Source

Fork a thread and call the supplied function when the thread is about to terminate, with an exception or a returned value. The function is called with asynchronous exceptions masked.

This function is useful for informing the parent when a child terminates, for example.

forkWithUnmask :: ((forall a. Conc t a -> Conc t a) -> Conc t ()) -> Conc t ThreadId Source

Like fork, but the child thread is passed a function that can be used to unmask asynchronous exceptions. This function should not be used within a mask or uninterruptibleMask.

forkOn :: Int -> Conc t () -> Conc t ThreadId Source

Fork a computation to happen on a specific processor. This implementation only has a single processor.

getNumCapabilities :: Conc t Int Source

Get the number of Haskell threads that can run simultaneously. This implementation lies and always returns 2. There is no way to verify in the computation that this is a lie, and will potentially avoid special-case behaviour for 1 capability, so it seems a sane choice.

myThreadId :: Conc t ThreadId Source

Get the ThreadId of the current thread.

spawn :: Conc t a -> Conc t (CVar t a) Source

Run the provided computation concurrently, returning the result.

atomically :: STMLike t (ST t) (STRef t) a -> Conc t a Source

Run the provided MonadSTM transaction atomically. If retry is called, it will be blocked until any of the touched CTVars have been written to.

throw :: Exception e => e -> Conc t a Source

Raise an exception in the Conc monad. The exception is raised when the action is run, not when it is applied. It short-citcuits the rest of the computation:

throw e >> x == throw e

throwTo :: Exception e => ThreadId -> e -> Conc t () Source

Throw an exception to the target thread. This blocks until the exception is delivered, and it is just as if the target thread had raised it with throw. This can interrupt a blocked action.

killThread :: ThreadId -> Conc t () Source

Raise the ThreadKilled exception in the target thread. Note that if the thread is prepared to catch this exception, it won't actually kill it.

catch :: Exception e => Conc t a -> (e -> Conc t a) -> Conc t a Source

Catch an exception raised by throw. This cannot catch errors, such as evaluating undefined, or division by zero. If you need that, use Control.Exception.catch and ConcIO.

mask :: ((forall a. Conc t a -> Conc t a) -> Conc t b) -> Conc t b Source

Executes a computation with asynchronous exceptions masked. That is, any thread which attempts to raise an exception in the current thread with throwTo will be blocked until asynchronous exceptions are unmasked again.

The argument passed to mask is a function that takes as its argument another function, which can be used to restore the prevailing masking state within the context of the masked computation. This function should not be used within an uninterruptibleMask.

uninterruptibleMask :: ((forall a. Conc t a -> Conc t a) -> Conc t b) -> Conc t b Source

Like mask, but the masked computation is not interruptible. THIS SHOULD BE USED WITH GREAT CARE, because if a thread executing in uninterruptibleMask blocks for any reason, then the thread (and possibly the program, if this is the main thread) will be unresponsive and unkillable. This function should only be necessary if you need to mask exceptions around an interruptible operation, and you can guarantee that the interruptible operation will only block for a short period of time. The supplied unmasking function should not be used within a mask.

CVars

data CVar t a Source

The concurrent variable type used with the Conc monad. One notable difference between these and MVars is that MVars are single-wakeup, and wake up in a FIFO order. Writing to a CVar wakes up all threads blocked on reading it, and it is up to the scheduler which one runs next. Taking from a CVar behaves analogously.

Instances

Eq (CVar t a) 

newEmptyCVar :: Conc t (CVar t a) Source

Create a new empty CVar.

putCVar :: CVar t a -> a -> Conc t () Source

Block on a CVar until it is empty, then write to it.

tryPutCVar :: CVar t a -> a -> Conc t Bool Source

Put a value into a CVar if there isn't one, without blocking.

readCVar :: CVar t a -> Conc t a Source

Block on a CVar until it is full, then read from it (without emptying).

takeCVar :: CVar t a -> Conc t a Source

Block on a CVar until it is full, then read from it (with emptying).

tryTakeCVar :: CVar t a -> Conc t (Maybe a) Source

Read a value from a CVar if there is one, without blocking.

CRefs

data CRef t a Source

The mutable non-blocking reference type. These are like IORefs, but don't have the potential re-ordering problem mentioned in Data.IORef.

Instances

Eq (CRef t a) 

newCRef :: a -> Conc t (CRef t a) Source

Create a new CRef.

readCRef :: CRef t a -> Conc t a Source

Read the value from a CRef.

writeCRef :: CRef t a -> a -> Conc t () Source

Replace the value stored inside a CRef.

modifyCRef :: CRef t a -> (a -> (a, b)) -> Conc t b Source

Atomically modify the value inside a CRef.

Testing

_concNoTest :: Conc t a -> Conc t a Source

Run the argument in one step. If the argument fails, the whole computation will fail.

_concKnowsAbout :: Either (CVar t a) (CTVar t (STRef t) a) -> Conc t () Source

Record that the referenced variable is known by the current thread.

_concForgets :: Either (CVar t a) (CTVar t (STRef t) a) -> Conc t () Source

Record that the referenced variable will never be touched by the current thread.

_concAllKnown :: Conc t () Source

Record that all CVars and CTVars known by the current thread have been passed to _concKnowsAbout.

Execution traces

type Trace = [(Decision, [(Decision, Lookahead)], ThreadAction)] Source

One of the outputs of the runner is a Trace, which is a log of decisions made, alternative decisions (including what action would have been performed had that decision been taken), and the action a thread took in its step.

type Trace' = [(Decision, [(Decision, NonEmpty Lookahead)], ThreadAction)] Source

Like a Trace, but gives more lookahead (where possible) for alternative decisions.

data Decision Source

Scheduling decisions are based on the state of the running program, and so we can capture some of that state in recording what specific decision we made.

Constructors

Start ThreadId

Start a new thread, because the last was blocked (or it's the start of computation).

Continue

Continue running the last thread for another step.

SwitchTo ThreadId

Pre-empt the running thread, and switch to another.

data ThreadAction Source

All the actions that a thread can perform.

Constructors

Fork ThreadId

Start a new thread.

MyThreadId

Get the ThreadId of the current thread.

New CVarId

Create a new CVar.

Put CVarId [ThreadId]

Put into a CVar, possibly waking up some threads.

BlockedPut CVarId

Get blocked on a put.

TryPut CVarId Bool [ThreadId]

Try to put into a CVar, possibly waking up some threads.

Read CVarId

Read from a CVar.

BlockedRead CVarId

Get blocked on a read.

Take CVarId [ThreadId]

Take from a CVar, possibly waking up some threads.

BlockedTake CVarId

Get blocked on a take.

TryTake CVarId Bool [ThreadId]

Try to take from a CVar, possibly waking up some threads.

NewRef CRefId

Create a new CRef.

ReadRef CRefId

Read from a CRef.

ModRef CRefId

Modify a CRef.

STM [ThreadId]

An STM transaction was executed, possibly waking up some threads.

FreshSTM

An STM transaction was executed, and all it did was create and write to new CTVars, no existing CTVars were touched.

BlockedSTM

Got blocked in an STM transaction.

Catching

Register a new exception handler

PopCatching

Pop the innermost exception handler from the stack.

Throw

Throw an exception.

ThrowTo ThreadId

Throw an exception to a thread.

BlockedThrowTo ThreadId

Get blocked on a throwTo.

Killed

Killed by an uncaught exception.

SetMasking Bool MaskingState

Set the masking state. If True, this is being used to set the masking state to the original state in the argument passed to a masked function.

ResetMasking Bool MaskingState

Return to an earlier masking state. If True, this is being used to return to the state of the masked block in the argument passed to a masked function.

Lift

Lift an action from the underlying monad. Note that the penultimate action in a trace will always be a Lift, this is an artefact of how the runner works.

NoTest

A computation annotated with _concNoTest was executed in a single step.

KnowsAbout

A _concKnowsAbout annotation was processed.

Forgets

A _concForgets annotation was processed.

AllKnown

A _concALlKnown annotation was processed.

Stop

Cease execution and terminate.

data Lookahead Source

A one-step look-ahead at what a thread will do next.

Constructors

WillFork

Will start a new thread.

WillMyThreadId

Will get the ThreadId.

WillNew

Will create a new CVar.

WillPut CVarId

Will put into a CVar, possibly waking up some threads.

WillTryPut CVarId

Will try to put into a CVar, possibly waking up some threads.

WillRead CVarId

Will read from a CVar.

WillTake CVarId

Will take from a CVar, possibly waking up some threads.

WillTryTake CVarId

Will try to take from a CVar, possibly waking up some threads.

WillNewRef

Will create a new CRef.

WillReadRef CRefId

Will read from a CRef.

WillModRef CRefId

Will modify a CRef.

WillSTM

Will execute an STM transaction, possibly waking up some threads.

WillCatching

Will register a new exception handler

WillPopCatching

Will pop the innermost exception handler from the stack.

WillThrow

Will throw an exception.

WillThrowTo ThreadId

Will throw an exception to a thread.

WillSetMasking Bool MaskingState

Will set the masking state. If True, this is being used to set the masking state to the original state in the argument passed to a masked function.

WillResetMasking Bool MaskingState

Will return to an earlier masking state. If True, this is being used to return to the state of the masked block in the argument passed to a masked function.

WillLift

Will lift an action from the underlying monad. Note that the penultimate action in a trace will always be a Lift, this is an artefact of how the runner works.

WillNoTest

Will execute a computation annotated with _concNoTest in a single step.

WillKnowsAbout

Will process a _concKnowsAbout annotation.

WillForgets

Will process a _concForgets annotation.

WillAllKnown

Will process a _concALlKnown annotation.

WillStop

Will cease execution and terminate.

type CVarId = Int Source

Every CVar has a unique identifier.

type CRefId = Int Source

Every CRef has a unique identifier.

data MaskingState :: *

Describes the behaviour of a thread when an asynchronous exception is received.

Constructors

Unmasked

asynchronous exceptions are unmasked (the normal state)

MaskedInterruptible

the state during mask: asynchronous exceptions are masked, but blocking operations may still be interrupted

MaskedUninterruptible

the state during uninterruptibleMask: asynchronous exceptions are masked, and blocking operations may not be interrupted

showTrace :: Trace -> String Source

Pretty-print a trace.

toTrace :: Trace' -> Trace Source

Throw away information from a Trace' to get just a Trace.

Scheduling