Copyright | (c) 2015--2018 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | DeriveAnyClass, DeriveGeneric, FlexibleContexts, LambdaCase, ViewPatterns |
Safe Haskell | None |
Language | Haskell2010 |
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
- data DPOR = DPOR {}
- validateDPOR :: HasCallStack => DPOR -> DPOR
- data BacktrackStep = BacktrackStep {}
- initialState :: [ThreadId] -> DPOR
- findSchedulePrefix :: DPOR -> Maybe ([ThreadId], Bool, Map ThreadId ThreadAction)
- incorporateTrace :: HasCallStack => Bool -> MemType -> Bool -> Trace -> DPOR -> DPOR
- findBacktrackSteps :: Bool -> MemType -> BacktrackFunc -> Bool -> Seq ([(ThreadId, Lookahead)], [ThreadId]) -> Trace -> [BacktrackStep]
- incorporateBacktrackSteps :: HasCallStack => [BacktrackStep] -> DPOR -> DPOR
- data DPORSchedState k = DPORSchedState {
- schedSleep :: Map ThreadId ThreadAction
- schedPrefix :: [ThreadId]
- schedBPoints :: Seq ([(ThreadId, Lookahead)], [ThreadId])
- schedIgnore :: Bool
- schedBoundKill :: Bool
- schedDepState :: DepState
- schedBState :: Maybe k
- initialDPORSchedState :: Map ThreadId ThreadAction -> [ThreadId] -> DPORSchedState k
- type IncrementalBoundFunc k = Maybe k -> Maybe (ThreadId, ThreadAction) -> (Decision, Lookahead) -> Maybe k
- type BacktrackFunc = [BacktrackStep] -> [(Int, Bool, ThreadId)] -> [BacktrackStep]
- backtrackAt :: HasCallStack => (ThreadId -> BacktrackStep -> Bool) -> BacktrackFunc
- dporSched :: HasCallStack => Bool -> MemType -> IncrementalBoundFunc k -> Scheduler (DPORSchedState k)
- independent :: Bool -> DepState -> ThreadId -> ThreadAction -> ThreadId -> ThreadAction -> Bool
- dependent :: Bool -> DepState -> ThreadId -> ThreadAction -> ThreadId -> ThreadAction -> Bool
- dependent' :: Bool -> DepState -> ThreadId -> ThreadAction -> ThreadId -> Lookahead -> Bool
- dependentActions :: DepState -> ActionType -> ActionType -> Bool
- data DepState = DepState {}
- initialDepState :: DepState
- updateDepState :: MemType -> DepState -> ThreadId -> ThreadAction -> DepState
- updateIOState :: MemType -> ThreadAction -> Map IORefId Int -> Map IORefId Int
- updateMVState :: ThreadAction -> Set MVarId -> Set MVarId
- updateMaskState :: ThreadId -> ThreadAction -> Map ThreadId MaskingState -> Map ThreadId MaskingState
- isBuffered :: DepState -> IORefId -> Bool
- numBuffered :: DepState -> IORefId -> Int
- isFull :: DepState -> MVarId -> Bool
- canInterrupt :: DepState -> ThreadId -> ThreadAction -> Bool
- canInterruptL :: DepState -> ThreadId -> Lookahead -> Bool
- isMaskedInterruptible :: DepState -> ThreadId -> Bool
- isMaskedUninterruptible :: DepState -> ThreadId -> Bool
- initialDPORThread :: DPOR -> ThreadId
- didYield :: ThreadAction -> Bool
- willYield :: Lookahead -> Bool
- killsDaemons :: ThreadId -> Lookahead -> Bool
Dynamic partial-order reduction
DPOR execution is represented as a tree of states, characterised by the decisions that lead to that state.
DPOR | |
|
Instances
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.
BacktrackStep | |
|
Instances
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.
:: 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. |
-> DPOR | |
-> DPOR |
Add a new trace to the stack. This won't work if to-dos aren't explored depth-first.
:: 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. |
-> 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
DPORSchedState | |
|
Instances
initialDPORSchedState Source #
:: Map ThreadId ThreadAction | The initial sleep set. |
-> [ThreadId] | The schedule prefix. |
-> 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.
:: HasCallStack | |
=> (ThreadId -> BacktrackStep -> Bool) | If this returns |
-> 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.
:: HasCallStack | |
=> Bool | True if all IO is thread safe. |
-> MemType | |
-> 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 -> DepState -> 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.
This should not be used to re-order traces which contain subconcurrency.
dependent :: Bool -> DepState -> 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 -> DepState -> ThreadId -> ThreadAction -> ThreadId -> Lookahead -> Bool Source #
dependentActions :: DepState -> ActionType -> ActionType -> Bool Source #
Check if two ActionType
s are dependent. Note that this is not
sufficient to know if two ThreadAction
s are dependent, without
being so great an over-approximation as to be useless!
Dependency function state
DepState | |
|
initialDepState :: DepState Source #
Initial dependency state.
updateDepState :: MemType -> DepState -> ThreadId -> ThreadAction -> DepState Source #
Update the dependency state with the action that has just happened.
updateIOState :: MemType -> ThreadAction -> Map IORefId Int -> Map IORefId Int Source #
Update the IORef
buffer state with the action that has just
happened.
updateMVState :: ThreadAction -> Set MVarId -> Set MVarId Source #
Update the MVar
full/empty 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.
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
initialDPORThread :: DPOR -> ThreadId Source #
didYield :: ThreadAction -> Bool Source #
Check if a thread yielded.