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

Copyright(c) 2015--2018 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityDeriveAnyClass, DeriveGeneric, FlexibleContexts, ViewPatterns
Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.SCT.Internal.DPOR

Contents

Description

Internal types and functions for SCT via 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 # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Methods

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

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

Show DPOR Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Methods

showsPrec :: Int -> DPOR -> ShowS #

show :: DPOR -> String #

showList :: [DPOR] -> ShowS #

Generic DPOR Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Associated Types

type Rep DPOR :: Type -> Type #

Methods

from :: DPOR -> Rep DPOR x #

to :: Rep DPOR x -> DPOR #

NFData DPOR Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Methods

rnf :: DPOR -> () #

type Rep DPOR Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

validateDPOR :: HasCallStack => DPOR -> DPOR Source #

Check the DPOR data invariants and raise an error if any are broken.

This is a reasonable thing to do, because if the state is corrupted then nothing sensible can happen anyway.

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

Instances
Eq BacktrackStep Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Show BacktrackStep Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Generic BacktrackStep Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Associated Types

type Rep BacktrackStep :: Type -> Type #

NFData BacktrackStep Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Methods

rnf :: BacktrackStep -> () #

type Rep BacktrackStep Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

initialState :: [ThreadId] -> DPOR Source #

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

The main thread must be in the list of initially runnable threads.

findSchedulePrefix :: DPOR -> Maybe ([ThreadId], Bool, Map ThreadId ThreadAction) Source #

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

:: HasCallStack 
=> Bool

True if all IO is thread-safe.

-> MemType 
-> 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.

-> ConcurrencyState

The initial concurrency state

-> DPOR 
-> DPOR 

Add a new trace to the stack. This won't work if to-dos aren't explored depth-first.

findBacktrackSteps Source #

Arguments

:: Bool

True if all IO is thread-safe

-> MemType 
-> 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.

-> ConcurrencyState

The initial concurrency state.

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

A sequence of threads at each step: the list of runnable in-bound 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 :: HasCallStack => [BacktrackStep] -> DPOR -> DPOR Source #

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

DPOR scheduler

data DPORSchedState k Source #

The scheduler state

Constructors

DPORSchedState 

Fields

Instances
Eq k => Eq (DPORSchedState k) Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Show k => Show (DPORSchedState k) Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Generic (DPORSchedState k) Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Associated Types

type Rep (DPORSchedState k) :: Type -> Type #

NFData k => NFData (DPORSchedState k) Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

Methods

rnf :: DPORSchedState k -> () #

type Rep (DPORSchedState k) Source # 
Instance details

Defined in Test.DejaFu.SCT.Internal.DPOR

initialDPORSchedState Source #

Arguments

:: Map ThreadId ThreadAction

The initial sleep set.

-> [ThreadId]

The schedule prefix.

-> ConcurrencyState

The initial concurrency state.

-> DPORSchedState k 

Initial DPOR scheduler state for a given prefix

type IncrementalBoundFunc k = Maybe k -> Maybe (ThreadId, ThreadAction) -> (Decision, Lookahead) -> Maybe k Source #

An incremental bounding function is a stateful function that takes the last and next decisions, and returns a new state only if the next 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

:: HasCallStack 
=> (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

:: HasCallStack 
=> Bool

True if all IO is thread safe.

-> IncrementalBoundFunc k

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

-> Scheduler (DPORSchedState k) 

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.

Dependency function

independent :: Bool -> ConcurrencyState -> ThreadId -> ThreadAction -> ThreadId -> ThreadAction -> Bool Source #

Check if two actions commute.

This implements a stronger check that not (dependent ...), as it handles some cases which dependent doesn't need to care about.

dependent :: Bool -> ConcurrencyState -> ThreadId -> ThreadAction -> ThreadId -> ThreadAction -> Bool Source #

Check if an action is dependent on another.

This is basically the same as dependent', but can make use of the additional information in a ThreadAction to make better decisions in a few cases.

dependent' :: Bool -> ConcurrencyState -> ThreadId -> ThreadAction -> ThreadId -> Lookahead -> Bool Source #

Variant of dependent to handle Lookahead.

Termination of the initial thread is handled specially in the DPOR implementation.

dependentActions :: ConcurrencyState -> ActionType -> ActionType -> Bool Source #

Check if two ActionTypes are dependent. Note that this is not sufficient to know if two ThreadActions are dependent, without being so great an over-approximation as to be useless!

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.