Copyright | (c) 2016 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Scheduling for concurrent computations.
- type Scheduler tid action lookahead s = [(Decision tid, action)] -> Maybe (tid, action) -> NonEmpty (tid, lookahead) -> s -> (Maybe tid, s)
- data Decision tid
- tidOf :: tid -> Decision tid -> tid
- decisionOf :: (Eq tid, Foldable f) => Maybe tid -> f tid -> tid -> Decision tid
- data NonEmpty a :: * -> * = a :| [a]
- randomSched :: RandomGen g => Scheduler tid action lookahead g
- roundRobinSched :: Ord tid => Scheduler tid action lookahead ()
- randomSchedNP :: (RandomGen g, Eq tid) => Scheduler tid action lookahead g
- roundRobinSchedNP :: Ord tid => Scheduler tid action lookahead ()
- makeNonPreemptive :: Eq tid => Scheduler tid action lookahead s -> Scheduler tid action lookahead s
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:
- The trace so far.
- The last thread executed (if this is the first invocation, this
is
Nothing
). - The runnable threads at this point.
- The state.
It returns a thread to execute, or Nothing
if execution should
abort here, and also a new state.
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.
:: (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.
Non-empty (and non-strict) list type.
Since: 4.9.0.0
a :| [a] infixr 5 |
Monad NonEmpty | |
Functor NonEmpty | |
MonadFix NonEmpty | |
Applicative NonEmpty | |
Foldable NonEmpty | |
Traversable NonEmpty | |
Generic1 NonEmpty | |
MonadZip NonEmpty | |
IsList (NonEmpty a) | |
Eq a => Eq (NonEmpty a) | |
Data a => Data (NonEmpty a) | |
Ord a => Ord (NonEmpty a) | |
Read a => Read (NonEmpty a) | |
Show a => Show (NonEmpty a) | |
Generic (NonEmpty a) | |
Semigroup (NonEmpty a) | |
NFData a => NFData (NonEmpty a) | Since: 1.4.2.0 |
type Rep1 NonEmpty | |
type Rep (NonEmpty a) | |
type Item (NonEmpty 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.