dejafu-0.5.1.0: Systematic testing for Haskell concurrency.

Copyright(c) 2016 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Test.DejaFu.SCT.Internal

Contents

Description

Internal types and functions for dynamic partial-order reduction. This module is NOT considered to form part of the public interface of this library.

Synopsis

Dynamic partial-order reduction

data DPOR Source #

DPOR execution is represented as a tree of states, characterised by the decisions that lead to that state.

Constructors

DPOR 

Fields

Instances

Eq DPOR Source # 

Methods

(==) :: DPOR -> DPOR -> Bool #

(/=) :: DPOR -> DPOR -> Bool #

Show DPOR Source # 

Methods

showsPrec :: Int -> DPOR -> ShowS #

show :: DPOR -> String #

showList :: [DPOR] -> ShowS #

NFData DPOR Source # 

Methods

rnf :: DPOR -> () #

data BacktrackStep Source #

One step of the execution, including information for backtracking purposes. This backtracking information is used to generate new schedules.

Constructors

BacktrackStep 

Fields

initialState :: DPOR Source #

Initial DPOR state, given an initial thread ID. This initial thread should exist and be runnable at the start of execution.

findSchedulePrefix Source #

Arguments

:: (ThreadId -> Bool)

Some partitioning function, applied to the to-do decisions. If there is an identifier which passes the test, it will be used, rather than any which fail it. This allows a very basic way of domain-specific prioritisation between otherwise equal choices, which may be useful in some cases.

-> DPOR 
-> Maybe ([ThreadId], Bool, Map ThreadId ThreadAction) 

Produce a new schedule prefix from a DPOR tree. If there are no new prefixes remaining, return Nothing. Also returns whether the decision was added conservatively, and the sleep set at the point where divergence happens.

A schedule prefix is a possibly empty sequence of decisions that have already been made, terminated by a single decision from the to-do set. The intent is to put the system into a new state when executed with this initial sequence of scheduling decisions.

incorporateTrace Source #

Arguments

:: (DepState -> ThreadId -> ThreadAction -> ThreadId -> ThreadAction -> Bool)

Dependency function

-> Bool

Whether the "to-do" point which was used to create this new execution was conservative or not.

-> Trace

The execution trace: the decision made, the runnable threads, and the action performed.

-> DPOR 
-> DPOR 

Add a new trace to the tree, creating a new subtree branching off at the point where the "to-do" decision was made.

findBacktrackSteps Source #

Arguments

:: (DepState -> ThreadId -> ThreadAction -> ThreadId -> Lookahead -> Bool)

Dependency function.

-> BacktrackFunc

Backtracking function. Given a list of backtracking points, and a thread to backtrack to at a specific point in that list, add the new backtracking points. There will be at least one: this chosen one, but the function may add others.

-> Bool

Whether the computation was aborted due to no decisions being in-bounds.

-> Seq (NonEmpty (ThreadId, Lookahead), [ThreadId])

A sequence of threads at each step: the nonempty list of runnable threads (with lookahead values), and the list of threads still to try. The reason for the two separate lists is because the threads chosen to try will be dependent on the specific domain.

-> Trace

The execution trace.

-> [BacktrackStep] 

Produce a list of new backtracking points from an execution trace. These are then used to inform new "to-do" points in the DPOR tree.

Two traces are passed in to this function: the first is generated from the special DPOR scheduler, the other from the execution of the concurrent program.

If the trace ends with any threads other than the initial one still runnable, a dependency is imposed between this final action and everything else.

incorporateBacktrackSteps Source #

Arguments

:: ([(Decision, ThreadAction)] -> (Decision, Lookahead) -> Bool)

Bound function: returns true if that schedule prefix terminated with the lookahead decision fits within the bound.

-> [BacktrackStep]

Backtracking steps identified by findBacktrackSteps.

-> DPOR 
-> DPOR 

Add new backtracking points, if they have not already been visited, fit into the bound, and aren't in the sleep set.

DPOR scheduler

data DPORSchedState Source #

The scheduler state

Constructors

DPORSchedState 

Fields

initialDPORSchedState Source #

Arguments

:: Map ThreadId ThreadAction

The initial sleep set.

-> [ThreadId]

The schedule prefix.

-> DPORSchedState 

Initial DPOR scheduler state for a given prefix

type BoundFunc = [(Decision, ThreadAction)] -> (Decision, Lookahead) -> Bool Source #

A bounding function takes the scheduling decisions so far and a decision chosen to come next, and returns if that decision is within the bound.

type BacktrackFunc = [BacktrackStep] -> [(Int, Bool, ThreadId)] -> [BacktrackStep] Source #

A backtracking step is a point in the execution where another decision needs to be made, in order to explore interesting new schedules. A backtracking function takes the steps identified so far and a list of points and thread at that point to backtrack to. More points be added to compensate for the effects of the bounding function. For example, under pre-emption bounding a conservative backtracking point is added at the prior context switch. The bool is whether the point is conservative. Conservative points are always explored, whereas non-conservative ones might be skipped based on future information.

In general, a backtracking function should identify one or more backtracking points, and then use backtrackAt to do the actual work.

backtrackAt Source #

Arguments

:: (ThreadId -> BacktrackStep -> Bool)

If this returns True, backtrack to all runnable threads, rather than just the given thread.

-> BacktrackFunc 

Add a backtracking point. If the thread isn't runnable, add all runnable threads. If the backtracking point is already present, don't re-add it UNLESS this would make it conservative.

dporSched Source #

Arguments

:: (DepState -> ThreadId -> ThreadAction -> ThreadId -> ThreadAction -> Bool)

Dependency function.

-> BoundFunc

Bound function: returns true if that schedule prefix terminated with the lookahead decision fits within the bound.

-> Scheduler DPORSchedState 

DPOR scheduler: takes a list of decisions, and maintains a trace including the runnable threads, and the alternative choices allowed by the bound-specific initialise function.

After the initial decisions are exhausted, this prefers choosing the prior thread if it's (1) still runnable and (2) hasn't just yielded. Furthermore, threads which will yield are ignored in preference of those which will not.

data RandSchedState g Source #

The scheduler state

Constructors

RandSchedState 

Fields

initialRandSchedState :: g -> RandSchedState g Source #

Initial weighted random scheduler state.

randSched :: RandomGen g => Scheduler (RandSchedState g) Source #

Weighted random scheduler: assigns to each new thread a weight, and makes a weighted random choice out of the runnable threads at every step.

data DepState Source #

Constructors

DepState 

Fields

  • depCRState :: Map CRefId Bool

    Keep track of which CRefs have buffered writes.

  • depMaskState :: Map ThreadId MaskingState

    Keep track of thread masking states. If a thread isn't present, the masking state is assumed to be Unmasked. This nicely provides compatibility with dpor-0.1, where the thread IDs are not available.

initialDepState :: DepState Source #

Initial dependency state.

updateDepState :: DepState -> ThreadId -> ThreadAction -> DepState Source #

Update the CRef buffer state with the action that has just happened.

updateCRState :: ThreadAction -> Map CRefId Bool -> Map CRefId Bool Source #

Update the CRef buffer state with the action that has just happened.

updateMaskState :: ThreadId -> ThreadAction -> Map ThreadId MaskingState -> Map ThreadId MaskingState Source #

Update the thread masking state with the action that has just happened.

isBuffered :: DepState -> CRefId -> Bool Source #

Check if a CRef has a buffered write pending.

canInterrupt :: DepState -> ThreadId -> ThreadAction -> Bool Source #

Check if an exception can interrupt a thread (action).

canInterruptL :: DepState -> ThreadId -> Lookahead -> Bool Source #

Check if an exception can interrupt a thread (lookahead).

isMaskedInterruptible :: DepState -> ThreadId -> Bool Source #

Check if a thread is masked interruptible.

isMaskedUninterruptible :: DepState -> ThreadId -> Bool Source #

Check if a thread is masked uninterruptible.

Utilities

didYield :: ThreadAction -> Bool Source #

Check if a thread yielded.

willYield :: Lookahead -> Bool Source #

Check if a thread will yield.

killsDaemons :: ThreadId -> Lookahead -> Bool Source #

Check if an action will kill daemon threads.

toDot Source #

Arguments

:: (ThreadId -> String)

Show a tid - this should produce a string suitable for use as a node identifier.

-> (ThreadAction -> String)

Show a action.

-> DPOR 
-> String 

Render a DPOR value as a graph in GraphViz "dot" format.

toDotFiltered Source #

Arguments

:: (ThreadId -> DPOR -> Bool)

Subtree predicate.

-> (ThreadId -> String) 
-> (ThreadAction -> String) 
-> DPOR 
-> String 

Render a DPOR value as a graph in GraphViz "dot" format, with a function to determine if a subtree should be included or not.

err :: String -> String -> a Source #

Internal errors.

concatPartition :: (a -> Bool) -> [[a]] -> ([a], [a]) Source #

A combination of partition and concat.