Copyright | (c) 2018 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | BangPatterns, FlexibleContexts, LambdaCase, RankNTypes |
Safe Haskell | None |
Language | Haskell2010 |
Internal types and functions for SCT. This module is NOT considered to form part of the public interface of this library.
- sct :: (MonadConc n, HasCallStack) => Settings n a -> ([ThreadId] -> s) -> (s -> Maybe t) -> ((Scheduler g -> g -> n (Either Failure a, g, Trace)) -> s -> t -> n (s, Maybe (Either Failure a, Trace))) -> ConcT n a -> n [(Either Failure a, Trace)]
- sct' :: (MonadConc n, HasCallStack) => Settings n a -> s -> (s -> Maybe t) -> (s -> t -> n (s, Maybe (Either Failure a, Trace))) -> (forall x. Scheduler x -> x -> n (Either Failure a, x, Trace)) -> ThreadId -> CRefId -> n [(Either Failure a, Trace)]
- simplifyExecution :: (MonadConc n, HasCallStack) => Settings n a -> (forall x. Scheduler x -> x -> n (Either Failure a, x, Trace)) -> ThreadId -> CRefId -> Either Failure a -> Trace -> n (Either Failure a, Trace)
- replay :: MonadConc n => (forall x. Scheduler x -> x -> n (Either Failure a, x, Trace)) -> [(ThreadId, ThreadAction)] -> n (Either Failure a, [(ThreadId, ThreadAction)], Trace)
- simplify :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- lexicoNormalForm :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- permuteBy :: MemType -> [ThreadId -> ThreadId -> Bool] -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- dropCommits :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- pullBack :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- pushForward :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- renumber :: MemType -> Int -> Int -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)]
- toId :: Coercible Id a => Int -> a
- fromId :: Coercible a Id => a -> Int
Exploration
:: (MonadConc n, HasCallStack) | |
=> Settings n a | The SCT settings ( |
-> ([ThreadId] -> s) | Initial state |
-> (s -> Maybe t) | State predicate |
-> ((Scheduler g -> g -> n (Either Failure a, g, Trace)) -> s -> t -> n (s, Maybe (Either Failure a, Trace))) | Run the computation and update the state |
-> ConcT n a | |
-> n [(Either Failure a, Trace)] |
General-purpose SCT function.
:: (MonadConc n, HasCallStack) | |
=> Settings n a | The SCT settings ( |
-> s | Initial state |
-> (s -> Maybe t) | State predicate |
-> (s -> t -> n (s, Maybe (Either Failure a, Trace))) | Run the computation and update the state |
-> (forall x. Scheduler x -> x -> n (Either Failure a, x, Trace)) | Just run the computation |
-> ThreadId | The first available |
-> CRefId | The first available |
-> n [(Either Failure a, Trace)] |
Like sct
but given a function to run the computation.
:: (MonadConc n, HasCallStack) | |
=> Settings n a | The SCT settings ( |
-> (forall x. Scheduler x -> x -> n (Either Failure a, x, Trace)) | Just run the computation |
-> ThreadId | The first available |
-> CRefId | The first available |
-> Either Failure a | The expected result |
-> Trace | |
-> n (Either Failure a, Trace) |
Given a result and a trace, produce a more minimal trace.
In principle, simplification is semantics preserving and can be done without needing to execute the computation again. However, there are two good reasons to do so:
- It's a sanity check that there are no bugs.
- It's easier to generate a reduced sequence of scheduling decisions and let dejafu generate the full trace, than to generate a reduced trace directly
Unlike shrinking in randomised property-testing tools like QuickCheck or Hedgehog, we only run the test case once, at the end, rather than after every simplification step.
:: MonadConc n | |
=> (forall x. Scheduler x -> x -> n (Either Failure a, x, Trace)) | Run the computation |
-> [(ThreadId, ThreadAction)] | The reduced sequence of scheduling decisions |
-> n (Either Failure a, [(ThreadId, ThreadAction)], Trace) |
Replay an execution.
Schedule simplification
simplify :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)] Source #
Simplify a trace by permuting adjacent independent actions to reduce context switching.
lexicoNormalForm :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)] Source #
Put a trace into lexicographic (by thread ID) normal form.
permuteBy :: MemType -> [ThreadId -> ThreadId -> Bool] -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)] Source #
Swap adjacent independent actions in the trace if a predicate holds.
dropCommits :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)] Source #
Throw away commit actions which are followed by a memory barrier.
pullBack :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)] Source #
Attempt to reduce context switches by "pulling" thread actions back to a prior execution of that thread.
Simple example, say we have [(tidA, act1), (tidB, act2), (tidA,
act3)]
, where act2
and act3
are independent. In this case
pullBack
will swap them, giving the sequence [(tidA, act1),
(tidA, act3), (tidB, act2)]
. It works for arbitrary separations.
pushForward :: MemType -> [(ThreadId, ThreadAction)] -> [(ThreadId, ThreadAction)] Source #
Attempt to reduce context switches by "pushing" thread actions forward to a future execution of that thread.
This is kind of the opposite of pullBack
, but there are cases
where one applies but not the other.
Simple example, say we have [(tidA, act1), (tidB, act2), (tidA,
act3)]
, where act1
and act2
are independent. In this case
pushForward
will swap them, giving the sequence [(tidB, act2),
(tidA, act1), (tidA, act3)]
. It works for arbitrary separations.
:: MemType | The memory model determines how commit threads are numbered. |
-> Int | First free thread ID. |
-> Int | First free |
-> [(ThreadId, ThreadAction)] | |
-> [(ThreadId, ThreadAction)] |
Re-number threads and CRefs.
Permuting forks or newCRefs makes the existing numbering invalid, which then causes problems for scheduling. Just re-numbering threads isn't enough, as CRef IDs are used to determine commit thread IDs.
Renumbered things will not fix their names, so don't rely on those at all.