Treat daemon threads specially.

dporSched now schedules all daemon threads if any of the initial
decisions willl terminate the computation. Closes #40.
This commit is contained in:
Michael Walker 2016-06-05 00:42:45 +01:00
parent c7aee7646f
commit a056f54b72
4 changed files with 49 additions and 10 deletions

View File

@ -317,6 +317,10 @@ sctBoundedM memtype bf backtrack run =
updateCRState updateCRState
(dependent memtype) (dependent memtype)
(dependent' memtype) (dependent' memtype)
#if MIN_VERSION_dpor(0,2,0)
-- dpor-0.2 knows about daemon threads.
(\_ (t, l) _ -> t == initialThread && case l of WillStop -> True; _ -> False)
#endif
initialThread initialThread
(>=initialThread) (>=initialThread)
bf bf

View File

@ -104,6 +104,7 @@ module Test.DPOR
import Control.DeepSeq (NFData) import Control.DeepSeq (NFData)
import Data.List (nub) import Data.List (nub)
import Data.List.NonEmpty (NonEmpty)
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import Test.DPOR.Internal import Test.DPOR.Internal
@ -129,6 +130,14 @@ import Test.DPOR.Schedule
-- the most specific and (2) will be more pessimistic (due to, -- the most specific and (2) will be more pessimistic (due to,
-- typically, less information being available when merely looking -- typically, less information being available when merely looking
-- ahead). -- ahead).
--
-- The daemon-termination predicate returns @True@ if the action being
-- looked at will cause the entire computation to terminate,
-- regardless of the other runnable threads (which are passed in the
-- 'NonEmpty' list). Such actions will then be put off for as long as
-- possible. This allows supporting concurrency models with daemon
-- threads without doing something as drastic as imposing a dependency
-- between the program-terminating action and /everything/ else.
dpor :: ( Ord tid dpor :: ( Ord tid
, NFData tid , NFData tid
, NFData action , NFData action
@ -148,6 +157,8 @@ dpor :: ( Ord tid
-- ^ The dependency (1) function. -- ^ The dependency (1) function.
-> (s -> (tid, action) -> (tid, lookahead) -> Bool) -> (s -> (tid, action) -> (tid, lookahead) -> Bool)
-- ^ The dependency (2) function. -- ^ The dependency (2) function.
-> (s -> (tid, lookahead) -> NonEmpty tid -> Bool)
-- ^ The daemon-termination predicate.
-> tid -> tid
-- ^ The initial thread. -- ^ The initial thread.
-> (tid -> Bool) -> (tid -> Bool)
@ -173,6 +184,7 @@ dpor didYield
ststep ststep
dependency1 dependency1
dependency2 dependency2
killsDaemons
initialTid initialTid
predicate predicate
inBound inBound
@ -203,7 +215,7 @@ dpor didYield
nextPrefix = findSchedulePrefix predicate (const (0, ())) nextPrefix = findSchedulePrefix predicate (const (0, ()))
-- The DPOR scheduler. -- The DPOR scheduler.
scheduler = dporSched didYield willYield dependency1 ststep inBound scheduler = dporSched didYield willYield dependency1 killsDaemons ststep inBound
-- Find the new backtracking steps. -- Find the new backtracking steps.
findBacktracks = findBacktrackSteps stinit ststep dependency2 backtrack . findBacktracks = findBacktrackSteps stinit ststep dependency2 backtrack .
@ -231,6 +243,8 @@ simpleDPOR :: ( Ord tid
-- ^ The dependency (1) function. -- ^ The dependency (1) function.
-> ((tid, action) -> (tid, lookahead) -> Bool) -> ((tid, action) -> (tid, lookahead) -> Bool)
-- ^ The dependency (2) function. -- ^ The dependency (2) function.
-> ((tid, lookahead) -> NonEmpty tid -> Bool)
-- ^ The daemon-termination predicate.
-> tid -> tid
-- ^ The initial thread. -- ^ The initial thread.
-> BoundFunc tid action lookahead -> BoundFunc tid action lookahead
@ -249,6 +263,7 @@ simpleDPOR didYield
willYield willYield
dependency1 dependency1
dependency2 dependency2
killsDaemons
initialTid initialTid
inBound inBound
backtrack backtrack
@ -258,6 +273,7 @@ simpleDPOR didYield
(\_ _ -> ()) (\_ _ -> ())
(const dependency1) (const dependency1)
(const dependency2) (const dependency2)
(const killsDaemons)
initialTid initialTid
(const True) (const True)
inBound inBound

View File

@ -468,13 +468,15 @@ dporSched :: (Ord tid, NFData tid, NFData action, NFData lookahead, NFData s)
-- ^ Determine if a thread will yield. -- ^ Determine if a thread will yield.
-> (s -> (tid, action) -> (tid, action) -> Bool) -> (s -> (tid, action) -> (tid, action) -> Bool)
-- ^ Dependency function. -- ^ Dependency function.
-> (s -> (tid, lookahead) -> NonEmpty tid -> Bool)
-- ^ Daemon-termination predicate.
-> (s -> (tid, action) -> s) -> (s -> (tid, action) -> s)
-- ^ Dependency function's state step function. -- ^ Dependency function's state step function.
-> BoundFunc tid action lookahead -> BoundFunc tid action lookahead
-- ^ Bound function: returns true if that schedule prefix terminated -- ^ Bound function: returns true if that schedule prefix terminated
-- with the lookahead decision fits within the bound. -- with the lookahead decision fits within the bound.
-> DPORScheduler tid action lookahead s -> DPORScheduler tid action lookahead s
dporSched didYield willYield dependency ststep inBound trc prior threads s = force schedule where dporSched didYield willYield dependency killsDaemons ststep inBound trc prior threads s = force schedule where
-- Pick a thread to run. -- Pick a thread to run.
schedule = case schedPrefix s of schedule = case schedPrefix s of
-- If there is a decision available, make it -- If there is a decision available, make it
@ -498,33 +500,44 @@ dporSched didYield willYield dependency ststep inBound trc prior threads s = for
-- The next scheduler state -- The next scheduler state
nextState rest = s nextState rest = s
{ schedBPoints = schedBPoints s |> (threads, rest) { schedBPoints = schedBPoints s |> (threads, rest)
, schedDepState = let ds = schedDepState s in maybe ds (ststep ds) prior , schedDepState = nextDepState
} }
nextDepState = let ds = schedDepState s in maybe ds (ststep ds) prior
-- Pick a new thread to run, which does not exceed the bound. Choose -- Pick a new thread to run, which does not exceed the bound. Choose
-- the current thread if available and it hasn't just yielded, -- the current thread if available and it hasn't just yielded,
-- otherwise add all runnable threads. -- otherwise add all runnable threads.
initialise = restrictToBound . yieldsToEnd $ case prior of initialise = restrictToBound . tryDaemons . yieldsToEnd $ case prior of
Just (tid, act) Just (tid, act)
| didYield act -> map fst (toList threads) | not (didYield act) && tid `elem` tids -> [tid]
| any (\(t, _) -> t == tid) threads -> [tid] _ -> tids'
_ -> map fst (toList threads)
-- If one of the chosen actions will kill the computation, and there
-- are daemon threads, try them instead.
tryDaemons ts
| any doesKill ts = filter (not . doesKill) tids' ++ filter doesKill ts
| otherwise = ts
doesKill t = killsDaemons nextDepState (t, action t) tids
-- Restrict the possible decisions to those in the bound. -- Restrict the possible decisions to those in the bound.
restrictToBound = fst . partition (\t -> inBound trc (decision t, action t)) restrictToBound = filter (\t -> inBound trc (decision t, action t))
-- Move the threads which will immediately yield to the end of the list -- Move the threads which will immediately yield to the end of the list
yieldsToEnd ts = case partition (willYield . action) ts of yieldsToEnd ts = case partition (willYield . action) ts of
(yields, noyields) -> noyields ++ yields (yields, noyields) -> noyields ++ yields
-- Get the decision that will lead to a thread being scheduled. -- Get the decision that will lead to a thread being scheduled.
decision = decisionOf (fst <$> prior) (S.fromList $ map fst threads') decision = decisionOf (fst <$> prior) (S.fromList tids')
-- Get the action of a thread -- Get the action of a thread
action t = fromJust $ lookup t threads' action t = fromJust $ lookup t threads'
-- The runnable thread IDs
tids = fst <$> threads
-- The runnable threads as a normal list. -- The runnable threads as a normal list.
threads' = toList threads threads' = toList threads
tids' = toList tids
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- * Utilities -- * Utilities

View File

@ -23,6 +23,7 @@ module Test.DPOR.Random
) where ) where
import Control.DeepSeq (NFData) import Control.DeepSeq (NFData)
import Data.List.NonEmpty (NonEmpty)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import System.Random (RandomGen, randomR) import System.Random (RandomGen, randomR)
@ -65,6 +66,8 @@ randomDPOR :: ( Ord tid
-- ^ The dependency (1) function. -- ^ The dependency (1) function.
-> (s -> (tid, action) -> (tid, lookahead) -> Bool) -> (s -> (tid, action) -> (tid, lookahead) -> Bool)
-- ^ The dependency (2) function. -- ^ The dependency (2) function.
-> (s -> (tid, lookahead) -> NonEmpty tid -> Bool)
-- ^ The daemon-termination predicate.
-> tid -> tid
-- ^ The initial thread. -- ^ The initial thread.
-> (tid -> Bool) -> (tid -> Bool)
@ -96,6 +99,7 @@ randomDPOR didYield
ststep ststep
dependency1 dependency1
dependency2 dependency2
killsDaemons
initialTid initialTid
predicate predicate
inBound inBound
@ -131,7 +135,7 @@ randomDPOR didYield
nextPrefix = findSchedulePrefix predicate . gen nextPrefix = findSchedulePrefix predicate . gen
-- The DPOR scheduler. -- The DPOR scheduler.
scheduler = dporSched didYield willYield dependency1 ststep inBound scheduler = dporSched didYield willYield dependency1 killsDaemons ststep inBound
-- Find the new backtracking steps. -- Find the new backtracking steps.
findBacktracks = findBacktrackSteps stinit ststep dependency2 backtrack . findBacktracks = findBacktrackSteps stinit ststep dependency2 backtrack .
@ -183,6 +187,7 @@ boundedRandom didYield willYield initialTid inBoundm
ststep ststep
dependency1 dependency1
dependency2 dependency2
killsDaemons
initialTid initialTid
predicate predicate
inBound inBound
@ -193,6 +198,7 @@ boundedRandom didYield willYield initialTid inBoundm
ststep _ _ = () ststep _ _ = ()
dependency1 _ _ _ = True dependency1 _ _ _ = True
dependency2 _ _ _ = True dependency2 _ _ _ = True
killsDaemons _ _ _ = True
predicate _ = True predicate _ = True
inBound = fromMaybe trueBound inBoundm inBound = fromMaybe trueBound inBoundm
backtrack = backtrackAt (const False) False backtrack = backtrackAt (const False) False