dpor-0.2.0.0: A generic implementation of dynamic partial-order reduction (DPOR) for testing arbitrary models of concurrency.

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

Test.DPOR.Schedule

Contents

Description

Scheduling for concurrent computations.

Synopsis

Scheduling

type Scheduler tid action lookahead s = [(Decision tid, action)] -> Maybe (tid, action) -> NonEmpty (tid, lookahead) -> s -> (Maybe tid, s) Source #

A Scheduler drives the execution of a concurrent program. The parameters it takes are:

  1. The trace so far.
  2. The last thread executed (if this is the first invocation, this is Nothing).
  3. The runnable threads at this point.
  4. The state.

It returns a thread to execute, or Nothing if execution should abort here, and also a new state.

data Decision tid 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 tid

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 tid

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

Instances

Eq tid => Eq (Decision tid) Source # 

Methods

(==) :: Decision tid -> Decision tid -> Bool #

(/=) :: Decision tid -> Decision tid -> Bool #

Show tid => Show (Decision tid) Source # 

Methods

showsPrec :: Int -> Decision tid -> ShowS #

show :: Decision tid -> String #

showList :: [Decision tid] -> ShowS #

NFData tid => NFData (Decision tid) Source # 

Methods

rnf :: Decision tid -> () #

tidOf :: tid -> Decision tid -> tid Source #

Get the resultant thread identifier of a Decision, with a default case for Continue.

decisionOf Source #

Arguments

:: (Eq tid, Foldable f) 
=> Maybe tid

The prior thread.

-> f tid

The runnable threads.

-> tid

The current thread.

-> Decision tid 

Get the Decision that would have resulted in this thread identifier, given a prior thread (if any) and list of runnable threads.

data NonEmpty a :: * -> * #

Non-empty (and non-strict) list type.

Since: 4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Monad NonEmpty 

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty 

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

MonadFix NonEmpty 

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Foldable NonEmpty 

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty 

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Generic1 NonEmpty 

Associated Types

type Rep1 (NonEmpty :: * -> *) :: * -> * #

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

MonadZip NonEmpty 

Methods

mzip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #

mzipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

munzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) #

IsList (NonEmpty a) 

Associated Types

type Item (NonEmpty a) :: * #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Eq a => Eq (NonEmpty a) 

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Data a => Data (NonEmpty a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmpty a -> c (NonEmpty a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmpty a) #

toConstr :: NonEmpty a -> Constr #

dataTypeOf :: NonEmpty a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmpty a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmpty a)) #

gmapT :: (forall b. Data b => b -> b) -> NonEmpty a -> NonEmpty a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmpty a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonEmpty a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmpty a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmpty a -> m (NonEmpty a) #

Ord a => Ord (NonEmpty a) 

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Read a => Read (NonEmpty a) 
Show a => Show (NonEmpty a) 

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Generic (NonEmpty a) 

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Semigroup (NonEmpty a) 

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () #

type Rep1 NonEmpty 
type Rep (NonEmpty a) 
type Item (NonEmpty a) 
type Item (NonEmpty a) = a

Preemptive

randomSched :: RandomGen g => Scheduler tid action lookahead g Source #

A simple random scheduler which, at every step, picks a random thread to run.

roundRobinSched :: Ord tid => Scheduler tid action lookahead () Source #

A round-robin scheduler which, at every step, schedules the thread with the next ThreadId.

Non-preemptive

randomSchedNP :: (RandomGen g, Eq tid) => Scheduler tid action lookahead g Source #

A random scheduler which doesn't preempt the running thread. That is, if the last thread scheduled is still runnable, run that, otherwise schedule randomly.

roundRobinSchedNP :: Ord tid => Scheduler tid action lookahead () Source #

A round-robin scheduler which doesn't preempt the running thread.

Utilities

makeNonPreemptive :: Eq tid => Scheduler tid action lookahead s -> Scheduler tid action lookahead s Source #

Turn a potentially preemptive scheduler into a non-preemptive one.