{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns -Wno-unused-matches #-}
#if __GLASGOW_HASKELL__ >= 908
{-# OPTIONS_GHC -Wno-x-partial #-}
#endif
module Control.Monad.IOSimPOR.Internal
( IOSim (..)
, runIOSim
, runSimTraceST
, traceM
, traceSTM
, STM
, STMSim
, setCurrentTime
, unshareClock
, TimeoutException (..)
, EventlogEvent (..)
, EventlogMarker (..)
, IOSimThreadId
, ThreadLabel
, Labelled (..)
, SimTrace
, Trace.Trace (SimPORTrace, TraceMainReturn, TraceMainException, TraceDeadlock)
, SimEvent (..)
, SimResult (..)
, SimEventType (..)
, liftST
, execReadTVar
, controlSimTraceST
, ScheduleControl (..)
, ScheduleMod (..)
) where
import Prelude hiding (read)
import Data.Dynamic
import Data.Foldable (foldlM, traverse_)
import qualified Data.List as List
import qualified Data.List.Trace as Trace
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (mapMaybe)
import Data.Ord
import Data.OrdPSQ (OrdPSQ)
import qualified Data.OrdPSQ as PSQ
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Time (UTCTime (..), fromGregorian)
import Control.Exception (NonTermination (..),
assert, throw)
import Control.Monad (join, when)
import Control.Monad.ST.Lazy
import Control.Monad.ST.Lazy.Unsafe (unsafeIOToST, unsafeInterleaveST)
import Data.STRef.Lazy
import Control.Concurrent.Class.MonadSTM.TMVar
import Control.Concurrent.Class.MonadSTM.TVar hiding (TVar)
import Control.Monad.Class.MonadFork (killThread, myThreadId, throwTo)
import Control.Monad.Class.MonadSTM hiding (STM)
import Control.Monad.Class.MonadSTM.Internal (TMVarDefault (TMVar))
import Control.Monad.Class.MonadThrow as MonadThrow
import Control.Monad.Class.MonadTime
import Control.Monad.Class.MonadTimer.SI (TimeoutState (..))
import Control.Monad.IOSim.InternalTypes
import Control.Monad.IOSim.Types hiding (SimEvent (SimEvent),
Trace (SimTrace))
import Control.Monad.IOSim.Types (SimEvent)
import Control.Monad.IOSimPOR.Timeout (unsafeTimeout)
import Control.Monad.IOSimPOR.Types
data Thread s a = Thread {
forall s a. Thread s a -> IOSimThreadId
threadId :: !IOSimThreadId,
forall s a. Thread s a -> ThreadControl s a
threadControl :: !(ThreadControl s a),
forall s a. Thread s a -> ThreadStatus
threadStatus :: !ThreadStatus,
forall s a. Thread s a -> MaskingState
threadMasking :: !MaskingState,
forall s a.
Thread s a
-> [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo :: ![(SomeException, Labelled IOSimThreadId, VectorClock)],
forall s a. Thread s a -> ClockId
threadClockId :: !ClockId,
forall s a. Thread s a -> Maybe ThreadLabel
threadLabel :: Maybe ThreadLabel,
forall s a. Thread s a -> Int
threadNextTId :: !Int,
forall s a. Thread s a -> Int
threadStep :: !Int,
forall s a. Thread s a -> VectorClock
threadVClock :: VectorClock,
forall s a. Thread s a -> Effect
threadEffect :: Effect,
forall s a. Thread s a -> Bool
threadRacy :: !Bool
}
deriving Int -> Thread s a -> ShowS
forall a.
(Int -> a -> ShowS)
-> (a -> ThreadLabel) -> ([a] -> ShowS) -> Show a
forall s a. Int -> Thread s a -> ShowS
forall s a. [Thread s a] -> ShowS
forall s a. Thread s a -> ThreadLabel
showList :: [Thread s a] -> ShowS
$cshowList :: forall s a. [Thread s a] -> ShowS
show :: Thread s a -> ThreadLabel
$cshow :: forall s a. Thread s a -> ThreadLabel
showsPrec :: Int -> Thread s a -> ShowS
$cshowsPrec :: forall s a. Int -> Thread s a -> ShowS
Show
isThreadBlocked :: Thread s a -> Bool
isThreadBlocked :: forall s a. Thread s a -> Bool
isThreadBlocked Thread s a
t = case forall s a. Thread s a -> ThreadStatus
threadStatus Thread s a
t of
ThreadBlocked {} -> Bool
True
ThreadStatus
_ -> Bool
False
isThreadDone :: Thread s a -> Bool
isThreadDone :: forall s a. Thread s a -> Bool
isThreadDone Thread s a
t = case forall s a. Thread s a -> ThreadStatus
threadStatus Thread s a
t of
ThreadStatus
ThreadDone -> Bool
True
ThreadStatus
_ -> Bool
False
threadStepId :: Thread s a -> (IOSimThreadId, Int)
threadStepId :: forall s a. Thread s a -> StepId
threadStepId Thread{ IOSimThreadId
threadId :: IOSimThreadId
threadId :: forall s a. Thread s a -> IOSimThreadId
threadId, Int
threadStep :: Int
threadStep :: forall s a. Thread s a -> Int
threadStep } = (IOSimThreadId
threadId, Int
threadStep)
isRacyThreadId :: IOSimThreadId -> Bool
isRacyThreadId :: IOSimThreadId -> Bool
isRacyThreadId (RacyThreadId [Int]
_) = Bool
True
isRacyThreadId IOSimThreadId
_ = Bool
True
isNotRacyThreadId :: IOSimThreadId -> Bool
isNotRacyThreadId :: IOSimThreadId -> Bool
isNotRacyThreadId (ThreadId [Int]
_) = Bool
True
isNotRacyThreadId IOSimThreadId
_ = Bool
False
bottomVClock :: VectorClock
bottomVClock :: VectorClock
bottomVClock = Map IOSimThreadId Int -> VectorClock
VectorClock forall k a. Map k a
Map.empty
insertVClock :: IOSimThreadId -> Int -> VectorClock -> VectorClock
insertVClock :: IOSimThreadId -> Int -> VectorClock -> VectorClock
insertVClock IOSimThreadId
tid !Int
step (VectorClock Map IOSimThreadId Int
m) = Map IOSimThreadId Int -> VectorClock
VectorClock (forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid Int
step Map IOSimThreadId Int
m)
leastUpperBoundVClock :: VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock :: VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock (VectorClock Map IOSimThreadId Int
m) (VectorClock Map IOSimThreadId Int
m') =
Map IOSimThreadId Int -> VectorClock
VectorClock (forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Ord a => a -> a -> a
max Map IOSimThreadId Int
m Map IOSimThreadId Int
m')
happensBeforeStep :: Step
-> Step
-> Bool
happensBeforeStep :: Step -> Step -> Bool
happensBeforeStep Step
step Step
step' =
forall a. a -> Maybe a
Just (Step -> Int
stepStep Step
step)
forall a. Ord a => a -> a -> Bool
<= forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Step -> IOSimThreadId
stepThreadId Step
step)
(VectorClock -> Map IOSimThreadId Int
getVectorClock forall a b. (a -> b) -> a -> b
$ Step -> VectorClock
stepVClock Step
step')
labelledTVarId :: TVar s a -> ST s (Labelled TVarId)
labelledTVarId :: forall s a. TVar s a -> ST s (Labelled TVarId)
labelledTVarId TVar { TVarId
tvarId :: forall s a. TVar s a -> TVarId
tvarId :: TVarId
tvarId, STRef s (Maybe ThreadLabel)
tvarLabel :: forall s a. TVar s a -> STRef s (Maybe ThreadLabel)
tvarLabel :: STRef s (Maybe ThreadLabel)
tvarLabel } = forall a. a -> Maybe ThreadLabel -> Labelled a
Labelled TVarId
tvarId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. STRef s a -> ST s a
readSTRef STRef s (Maybe ThreadLabel)
tvarLabel
labelledThreads :: Map IOSimThreadId (Thread s a) -> [Labelled IOSimThreadId]
labelledThreads :: forall s a.
Map IOSimThreadId (Thread s a) -> [Labelled IOSimThreadId]
labelledThreads Map IOSimThreadId (Thread s a)
threadMap =
forall a b k. (a -> b -> b) -> b -> Map k a -> b
Map.foldr'
(\Thread { IOSimThreadId
threadId :: IOSimThreadId
threadId :: forall s a. Thread s a -> IOSimThreadId
threadId, Maybe ThreadLabel
threadLabel :: Maybe ThreadLabel
threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel } ![Labelled IOSimThreadId]
acc -> forall a. a -> Maybe ThreadLabel -> Labelled a
Labelled IOSimThreadId
threadId Maybe ThreadLabel
threadLabel forall a. a -> [a] -> [a]
: [Labelled IOSimThreadId]
acc)
[] Map IOSimThreadId (Thread s a)
threadMap
data TimerCompletionInfo s =
Timer !(TVar s TimeoutState)
| TimerRegisterDelay !(TVar s Bool)
| TimerThreadDelay !IOSimThreadId !TimeoutId
| TimerTimeout !IOSimThreadId !TimeoutId !(TMVar (IOSim s) IOSimThreadId)
type RunQueue = OrdPSQ (Down IOSimThreadId) (Down IOSimThreadId) ()
type Timeouts s = OrdPSQ TimeoutId Time (TimerCompletionInfo s)
data SimState s a = SimState {
forall s a. SimState s a -> RunQueue
runqueue :: !RunQueue,
forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads :: !(Map IOSimThreadId (Thread s a)),
forall s a. SimState s a -> Time
curTime :: !Time,
forall s a. SimState s a -> Timeouts s
timers :: !(Timeouts s),
forall s a. SimState s a -> Map ClockId UTCTime
clocks :: !(Map ClockId UTCTime),
forall s a. SimState s a -> TVarId
nextVid :: !TVarId,
forall s a. SimState s a -> TimeoutId
nextTmid :: !TimeoutId,
forall s a. SimState s a -> Races
races :: Races,
forall s a. SimState s a -> ScheduleControl
control :: !ScheduleControl,
forall s a. SimState s a -> ScheduleControl
control0 :: !ScheduleControl,
forall s a. SimState s a -> Maybe Int
perStepTimeLimit :: Maybe Int
}
initialState :: SimState s a
initialState :: forall s a. SimState s a
initialState =
SimState {
runqueue :: RunQueue
runqueue = forall k p v. OrdPSQ k p v
PSQ.empty,
threads :: Map IOSimThreadId (Thread s a)
threads = forall k a. Map k a
Map.empty,
curTime :: Time
curTime = DiffTime -> Time
Time DiffTime
0,
timers :: Timeouts s
timers = forall k p v. OrdPSQ k p v
PSQ.empty,
clocks :: Map ClockId UTCTime
clocks = forall k a. k -> a -> Map k a
Map.singleton ([Int] -> ClockId
ClockId []) UTCTime
epoch1970,
nextVid :: TVarId
nextVid = Int -> TVarId
TVarId Int
0,
nextTmid :: TimeoutId
nextTmid = Int -> TimeoutId
TimeoutId Int
0,
races :: Races
races = Races
noRaces,
control :: ScheduleControl
control = ScheduleControl
ControlDefault,
control0 :: ScheduleControl
control0 = ScheduleControl
ControlDefault,
perStepTimeLimit :: Maybe Int
perStepTimeLimit = forall a. Maybe a
Nothing
}
where
epoch1970 :: UTCTime
epoch1970 = Day -> DiffTime -> UTCTime
UTCTime (Year -> Int -> Int -> Day
fromGregorian Year
1970 Int
1 Int
1) DiffTime
0
invariant :: Maybe (Thread s a) -> SimState s a -> x -> x
invariant :: forall s a x. Maybe (Thread s a) -> SimState s a -> x -> x
invariant (Just Thread s a
running) simstate :: SimState s a
simstate@SimState{RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue,Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads,Map ClockId UTCTime
clocks :: Map ClockId UTCTime
clocks :: forall s a. SimState s a -> Map ClockId UTCTime
clocks} =
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Bool -> Bool
not (forall s a. Thread s a -> Bool
isThreadBlocked Thread s a
running))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
running forall k a. Ord k => k -> Map k a -> Bool
`Map.notMember` Map IOSimThreadId (Thread s a)
threads)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Bool -> Bool
not (forall a. a -> Down a
Down (forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
running) forall k p v. Ord k => k -> OrdPSQ k p v -> Bool
`PSQ.member` RunQueue
runqueue))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall s a. Thread s a -> ClockId
threadClockId Thread s a
running forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map ClockId UTCTime
clocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a x. Maybe (Thread s a) -> SimState s a -> x -> x
invariant forall a. Maybe a
Nothing SimState s a
simstate
invariant Maybe (Thread s a)
Nothing SimState{RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue,Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads,Map ClockId UTCTime
clocks :: Map ClockId UTCTime
clocks :: forall s a. SimState s a -> Map ClockId UTCTime
clocks} =
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall k p v a. (k -> p -> v -> a -> a) -> a -> OrdPSQ k p v -> a
PSQ.fold' (\(Down IOSimThreadId
tid) Down IOSimThreadId
_ ()
_ Bool
a -> IOSimThreadId
tid forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map IOSimThreadId (Thread s a)
threads Bool -> Bool -> Bool
&& Bool
a) Bool
True RunQueue
runqueue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ (forall s a. Thread s a -> Bool
isThreadBlocked Thread s a
t Bool -> Bool -> Bool
|| forall s a. Thread s a -> Bool
isThreadDone Thread s a
t) forall a. Eq a => a -> a -> Bool
== Bool -> Bool
not (forall a. a -> Down a
Down (forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
t) forall k p v. Ord k => k -> OrdPSQ k p v -> Bool
`PSQ.member` RunQueue
runqueue)
| Thread s a
t <- forall k a. Map k a -> [a]
Map.elems Map IOSimThreadId (Thread s a)
threads ])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall (t :: * -> *). Foldable t => t Bool -> Bool
and (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\(Down IOSimThreadId
tid, Down IOSimThreadId
_, ()
_) (Down IOSimThreadId
tid', Down IOSimThreadId
_, ()
_) -> IOSimThreadId
tid forall a. Ord a => a -> a -> Bool
> IOSimThreadId
tid')
(forall k p v. OrdPSQ k p v -> [(k, p, v)]
PSQ.toList RunQueue
runqueue)
(forall a. Int -> [a] -> [a]
drop Int
1 (forall k p v. OrdPSQ k p v -> [(k, p, v)]
PSQ.toList RunQueue
runqueue))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ forall s a. Thread s a -> ClockId
threadClockId Thread s a
t forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map ClockId UTCTime
clocks
| Thread s a
t <- forall k a. Map k a -> [a]
Map.elems Map IOSimThreadId (Thread s a)
threads ])
timeSinceEpoch :: Time -> NominalDiffTime
timeSinceEpoch :: Time -> NominalDiffTime
timeSinceEpoch (Time DiffTime
t) = forall a. Fractional a => Rational -> a
fromRational (forall a. Real a => a -> Rational
toRational DiffTime
t)
insertThread :: Thread s a -> RunQueue -> RunQueue
insertThread :: forall s a. Thread s a -> RunQueue -> RunQueue
insertThread Thread { IOSimThreadId
threadId :: IOSimThreadId
threadId :: forall s a. Thread s a -> IOSimThreadId
threadId } = forall k p v.
(Ord k, Ord p) =>
k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.insert (forall a. a -> Down a
Down IOSimThreadId
threadId) (forall a. a -> Down a
Down IOSimThreadId
threadId) ()
schedule :: forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule :: forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule thread :: Thread s a
thread@Thread{
threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid,
threadControl :: forall s a. Thread s a -> ThreadControl s a
threadControl = ThreadControl SimA s b
action ControlStack s b a
ctl,
threadMasking :: forall s a. Thread s a -> MaskingState
threadMasking = MaskingState
maskst,
threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock,
threadEffect :: forall s a. Thread s a -> Effect
threadEffect = Effect
effect
}
simstate :: SimState s a
simstate@SimState {
RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue,
Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads,
Timeouts s
timers :: Timeouts s
timers :: forall s a. SimState s a -> Timeouts s
timers,
Map ClockId UTCTime
clocks :: Map ClockId UTCTime
clocks :: forall s a. SimState s a -> Map ClockId UTCTime
clocks,
TVarId
nextVid :: TVarId
nextVid :: forall s a. SimState s a -> TVarId
nextVid, TimeoutId
nextTmid :: TimeoutId
nextTmid :: forall s a. SimState s a -> TimeoutId
nextTmid,
curTime :: forall s a. SimState s a -> Time
curTime = Time
time,
ScheduleControl
control :: ScheduleControl
control :: forall s a. SimState s a -> ScheduleControl
control,
Maybe Int
perStepTimeLimit :: Maybe Int
perStepTimeLimit :: forall s a. SimState s a -> Maybe Int
perStepTimeLimit
}
| StepId -> ScheduleControl -> Bool
controlTargets (IOSimThreadId
tid,Int
tstep) ScheduleControl
control =
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (ScheduleControl -> SimEventType
EventFollowControl ScheduleControl
control) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread SimState s a
simstate{ control :: ScheduleControl
control = ScheduleControl -> ScheduleControl
followControl ScheduleControl
control }
| Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ StepId -> ScheduleControl -> Bool
controlFollows (IOSimThreadId
tid,Int
tstep) ScheduleControl
control =
( forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (StepId -> ScheduleControl -> SimEventType
EventAwaitControl (IOSimThreadId
tid,Int
tstep) ScheduleControl
control)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Sleep)
) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Sleep Thread s a
thread SimState s a
simstate
| Bool
otherwise =
forall s a x. Maybe (Thread s a) -> SimState s a -> x -> x
invariant (forall a. a -> Maybe a
Just Thread s a
thread) SimState s a
simstate forall a b. (a -> b) -> a -> b
$
case ScheduleControl
control of
ControlFollow (StepId
s:[StepId]
_) [ScheduleMod]
_
-> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (StepId -> SimEventType
EventPerformAction (IOSimThreadId
tid,Int
tstep)))
ScheduleControl
_ -> forall a. a -> a
id
forall a b. (a -> b) -> a -> b
$
case forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> Maybe a
Just forall a. Int -> a -> Maybe a
unsafeTimeout Maybe Int
perStepTimeLimit SimA s b
action of
Maybe (SimA s b)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. SimTrace a
TraceLoop
Just SimA s b
_ -> case SimA s b
action of
Return b
x -> case ControlStack s b a
ctl of
ControlStack s b a
MainFrame ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl SimEventType
EventThreadFinished
forall a b. (a -> b) -> a -> b
$ forall s a. SimState s a -> SimTrace a -> SimTrace a
traceFinalRacesFound SimState s a
simstate
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> Labelled IOSimThreadId
-> a
-> [Labelled IOSimThreadId]
-> SimTrace a
TraceMainReturn Time
time (forall a. a -> Maybe ThreadLabel -> Labelled a
Labelled IOSimThreadId
tid Maybe ThreadLabel
tlbl) b
x
( forall s a.
Map IOSimThreadId (Thread s a) -> [Labelled IOSimThreadId]
labelledThreads
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. Thread s a -> Bool
isThreadDone)
forall a b. (a -> b) -> a -> b
$ Map IOSimThreadId (Thread s a)
threads
)
ControlStack s b a
ForkFrame -> do
let thread' :: Thread s a
thread' = Thread s a
thread
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Terminated Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl SimEventType
EventThreadFinished
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Terminated)
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
MaskFrame b -> SimA s c
k MaskingState
maskst' ControlStack s c a
ctl' -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (b -> SimA s c
k b
x) ControlStack s c a
ctl'
, threadMasking :: MaskingState
threadMasking = MaskingState
maskst'
}
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Interruptable Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (MaskingState -> SimEventType
EventMask MaskingState
maskst')
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Interruptable)
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
CatchFrame e -> SimA s b
_handler b -> SimA s c
k ControlStack s c a
ctl' -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (b -> SimA s c
k b
x) ControlStack s c a
ctl' }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
TimeoutFrame TimeoutId
tmid TMVar (IOSim s) IOSimThreadId
lock Maybe b -> SimA s c
k ControlStack s c a
ctl' -> do
Bool
v <- forall s a. TMVar (IOSim s) a -> a -> ST s Bool
execTryPutTMVar TMVar (IOSim s) IOSimThreadId
lock forall a. (?callStack::CallStack) => a
undefined
let
threadAction :: IOSim s ()
threadAction :: IOSim s ()
threadAction =
if Bool
v then forall s. TimeoutId -> IOSim s ()
unsafeUnregisterTimeout TimeoutId
tmid
else forall (m :: * -> *) a.
(MonadSTM m, ?callStack::CallStack) =>
STM m a -> m a
atomically (forall (m :: * -> *) a. MonadSTM m => TMVar m a -> STM m a
takeTMVar TMVar (IOSim s) IOSimThreadId
lock) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadFork m => ThreadId m -> m ()
killThread
thread' :: Thread s a
thread' =
Thread s a
thread { threadControl :: ThreadControl s a
threadControl =
forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (case IOSim s ()
threadAction of
IOSim forall r. (() -> SimA s r) -> SimA s r
k' -> forall r. (() -> SimA s r) -> SimA s r
k' (\() -> Maybe b -> SimA s c
k (forall a. a -> Maybe a
Just b
x)))
ControlStack s c a
ctl'
}
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
DelayFrame TimeoutId
tmid SimA s c
k ControlStack s c a
ctl' -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s c
k ControlStack s c a
ctl' }
timers' :: Timeouts s
timers' = forall k p v. (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.delete TimeoutId
tmid Timeouts s
timers
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { timers :: Timeouts s
timers = Timeouts s
timers' }
Throw SomeException
e -> case forall s a.
SomeException
-> Thread s a
-> Timeouts s
-> (Either Bool (Thread s a), Timeouts s)
unwindControlStack SomeException
e Thread s a
thread Timeouts s
timers of
(Right thread0 :: Thread s a
thread0@Thread { threadMasking :: forall s a. Thread s a -> MaskingState
threadMasking = MaskingState
maskst' }, Timeouts s
timers'') -> do
let (Thread s a
thread', Effect
eff) = forall s a. Thread s a -> (Thread s a, Effect)
stepThread Thread s a
thread0
control' :: ScheduleControl
control' = StepId -> ScheduleControl -> ScheduleControl
advanceControl (forall s a. Thread s a -> StepId
threadStepId Thread s a
thread0) ScheduleControl
control
races' :: Races
races' = forall s a. Thread s a -> SimState s a -> Races
updateRaces Thread s a
thread0 SimState s a
simstate
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate{ races :: Races
races = Races
races',
control :: ScheduleControl
control = ScheduleControl
control',
timers :: Timeouts s
timers = Timeouts s
timers'' }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> SimEventType
EventThrow SomeException
e) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (MaskingState -> SimEventType
EventMask MaskingState
maskst') forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (VectorClock -> Effect -> SimEventType
EventEffect VectorClock
vClock Effect
eff) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Races -> SimEventType
EventRaces Races
races')
SimTrace a
trace)
(Left Bool
isMain, Timeouts s
timers'')
| Bool
isMain -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadStatus :: ThreadStatus
threadStatus = ThreadStatus
ThreadDone }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> SimEventType
EventThrow SomeException
e) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> SimEventType
EventThreadUnhandled SomeException
e) forall a b. (a -> b) -> a -> b
$
forall s a. SimState s a -> SimTrace a -> SimTrace a
traceFinalRacesFound SimState s a
simstate { threads :: Map IOSimThreadId (Thread s a)
threads = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid Thread s a
thread' Map IOSimThreadId (Thread s a)
threads } forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> Labelled IOSimThreadId
-> SomeException
-> [Labelled IOSimThreadId]
-> SimTrace a
TraceMainException Time
time (forall a. a -> Maybe ThreadLabel -> Labelled a
Labelled IOSimThreadId
tid Maybe ThreadLabel
tlbl) SomeException
e (forall s a.
Map IOSimThreadId (Thread s a) -> [Labelled IOSimThreadId]
labelledThreads Map IOSimThreadId (Thread s a)
threads))
| Bool
otherwise -> do
let terminated :: Deschedule
terminated = Deschedule
Terminated
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
terminated Thread s a
thread SimState s a
simstate { timers :: Timeouts s
timers = Timeouts s
timers'' }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> SimEventType
EventThrow SomeException
e)
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> SimEventType
EventThreadUnhandled SomeException
e)
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
terminated)
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
Catch SimA s a
action' e -> SimA s a
handler a -> SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s a
action'
(forall a s b c a.
Exception a =>
(a -> SimA s b)
-> (b -> SimA s c) -> ControlStack s c a -> ControlStack s b a
CatchFrame e -> SimA s a
handler a -> SimA s b
k ControlStack s b a
ctl)
}
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
Evaluate a
expr a -> SimA s b
k -> do
Either SomeException a
mbWHNF <- forall a s. IO a -> ST s a
unsafeIOToST forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> m (Either e a)
try forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadEvaluate m => a -> m a
evaluate a
expr
case Either SomeException a
mbWHNF of
Left SomeException
e -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. SomeException -> SimA s a
Throw SomeException
e) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
Right a
whnf -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (a -> SimA s b
k a
whnf) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
Say ThreadLabel
msg SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (ThreadLabel -> SimEventType
EventSay ThreadLabel
msg) SimTrace a
trace)
Output Dynamic
x SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Dynamic -> SimEventType
EventLog Dynamic
x) SimTrace a
trace)
LiftST ST s a
st a -> SimA s b
k -> do
a
x <- forall s a. ST s a -> ST s a
strictToLazyST ST s a
st
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (a -> SimA s b
k a
x) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
GetMonoTime Time -> SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (Time -> SimA s b
k Time
time) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
GetWallTime UTCTime -> SimA s b
k -> do
let clockid :: ClockId
clockid = forall s a. Thread s a -> ClockId
threadClockId Thread s a
thread
clockoff :: UTCTime
clockoff = Map ClockId UTCTime
clocks forall k a. Ord k => Map k a -> k -> a
Map.! ClockId
clockid
walltime :: UTCTime
walltime = Time -> NominalDiffTime
timeSinceEpoch Time
time NominalDiffTime -> UTCTime -> UTCTime
`addUTCTime` UTCTime
clockoff
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (UTCTime -> SimA s b
k UTCTime
walltime) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
SetWallTime UTCTime
walltime' SimA s b
k -> do
let clockid :: ClockId
clockid = forall s a. Thread s a -> ClockId
threadClockId Thread s a
thread
clockoff :: UTCTime
clockoff = Map ClockId UTCTime
clocks forall k a. Ord k => Map k a -> k -> a
Map.! ClockId
clockid
walltime :: UTCTime
walltime = Time -> NominalDiffTime
timeSinceEpoch Time
time NominalDiffTime -> UTCTime -> UTCTime
`addUTCTime` UTCTime
clockoff
clockoff' :: UTCTime
clockoff' = NominalDiffTime -> UTCTime -> UTCTime
addUTCTime (UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime UTCTime
walltime' UTCTime
walltime) UTCTime
clockoff
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
simstate' :: SimState s a
simstate' = SimState s a
simstate { clocks :: Map ClockId UTCTime
clocks = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert ClockId
clockid UTCTime
clockoff' Map ClockId UTCTime
clocks }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate'
UnshareClock SimA s b
k -> do
let clockid :: ClockId
clockid = forall s a. Thread s a -> ClockId
threadClockId Thread s a
thread
clockoff :: UTCTime
clockoff = Map ClockId UTCTime
clocks forall k a. Ord k => Map k a -> k -> a
Map.! ClockId
clockid
clockid' :: ClockId
clockid' = let ThreadId [Int]
i = IOSimThreadId
tid in [Int] -> ClockId
ClockId [Int]
i
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl
, threadClockId :: ClockId
threadClockId = ClockId
clockid' }
simstate' :: SimState s a
simstate' = SimState s a
simstate { clocks :: Map ClockId UTCTime
clocks = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert ClockId
clockid' UTCTime
clockoff Map ClockId UTCTime
clocks }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate'
StartTimeout DiffTime
d SimA s a
_ Maybe a -> SimA s b
_ | DiffTime
d forall a. Ord a => a -> a -> Bool
<= DiffTime
0 ->
forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"schedule: StartTimeout: Impossible happened"
StartTimeout DiffTime
d SimA s a
action' Maybe a -> SimA s b
k -> do
TMVarDefault (IOSim s) IOSimThreadId
lock <- forall (m :: * -> *) a. TVar m (Maybe a) -> TMVarDefault m a
TMVar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. TVarId -> Maybe ThreadLabel -> a -> ST s (TVar s a)
execNewTVar TVarId
nextVid (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ThreadLabel
"lock-" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> ThreadLabel
show TimeoutId
nextTmid) forall a. Maybe a
Nothing
let expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
timers' :: Timeouts s
timers' = forall k p v.
(Ord k, Ord p) =>
k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.insert TimeoutId
nextTmid Time
expiry (forall s.
IOSimThreadId
-> TimeoutId
-> TMVar (IOSim s) IOSimThreadId
-> TimerCompletionInfo s
TimerTimeout IOSimThreadId
tid TimeoutId
nextTmid TMVarDefault (IOSim s) IOSimThreadId
lock) Timeouts s
timers
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl =
forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s a
action'
(forall s b a a.
TimeoutId
-> TMVar (IOSim s) IOSimThreadId
-> (Maybe b -> SimA s a)
-> ControlStack s a a
-> ControlStack s b a
TimeoutFrame TimeoutId
nextTmid TMVarDefault (IOSim s) IOSimThreadId
lock Maybe a -> SimA s b
k ControlStack s b a
ctl)
}
SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield Thread s a
thread' SimState s a
simstate { timers :: Timeouts s
timers = Timeouts s
timers'
, nextTmid :: TimeoutId
nextTmid = forall a. Enum a => a -> a
succ TimeoutId
nextTmid }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> IOSimThreadId -> Time -> SimEventType
EventTimeoutCreated TimeoutId
nextTmid IOSimThreadId
tid Time
expiry) SimTrace a
trace)
UnregisterTimeout TimeoutId
tmid SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { timers :: Timeouts s
timers = forall k p v. (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.delete TimeoutId
tmid Timeouts s
timers }
RegisterDelay DiffTime
d TVar s Bool -> SimA s b
k | DiffTime
d forall a. Ord a => a -> a -> Bool
< DiffTime
0 -> do
TVar s Bool
tvar <- forall a s. TVarId -> Maybe ThreadLabel -> a -> ST s (TVar s a)
execNewTVar TVarId
nextVid
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ThreadLabel
"<<timeout " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> ThreadLabel
show (TimeoutId -> Int
unTimeoutId TimeoutId
nextTmid) forall a. [a] -> [a] -> [a]
++ ThreadLabel
">>")
Bool
True
forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef (forall s a. TVar s a -> STRef s VectorClock
tvarVClock TVar s Bool
tvar) (VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock VectorClock
vClock)
let !expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
!thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (TVar s Bool -> SimA s b
k TVar s Bool
tvar) ControlStack s b a
ctl }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { nextVid :: TVarId
nextVid = forall a. Enum a => a -> a
succ TVarId
nextVid }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> TVarId -> Time -> SimEventType
EventRegisterDelayCreated TimeoutId
nextTmid TVarId
nextVid Time
expiry) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> SimEventType
EventRegisterDelayFired TimeoutId
nextTmid) forall a b. (a -> b) -> a -> b
$
SimTrace a
trace)
RegisterDelay DiffTime
d TVar s Bool -> SimA s b
k -> do
TVar s Bool
tvar <- forall a s. TVarId -> Maybe ThreadLabel -> a -> ST s (TVar s a)
execNewTVar TVarId
nextVid
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ThreadLabel
"<<timeout " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> ThreadLabel
show (TimeoutId -> Int
unTimeoutId TimeoutId
nextTmid) forall a. [a] -> [a] -> [a]
++ ThreadLabel
">>")
Bool
False
forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef (forall s a. TVar s a -> STRef s VectorClock
tvarVClock TVar s Bool
tvar) (VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock VectorClock
vClock)
let !expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
!timers' :: Timeouts s
timers' = forall k p v.
(Ord k, Ord p) =>
k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.insert TimeoutId
nextTmid Time
expiry (forall s. TVar s Bool -> TimerCompletionInfo s
TimerRegisterDelay TVar s Bool
tvar) Timeouts s
timers
!thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (TVar s Bool -> SimA s b
k TVar s Bool
tvar) ControlStack s b a
ctl }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { timers :: Timeouts s
timers = Timeouts s
timers'
, nextVid :: TVarId
nextVid = forall a. Enum a => a -> a
succ TVarId
nextVid
, nextTmid :: TimeoutId
nextTmid = forall a. Enum a => a -> a
succ TimeoutId
nextTmid }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl
(TimeoutId -> TVarId -> Time -> SimEventType
EventRegisterDelayCreated TimeoutId
nextTmid TVarId
nextVid Time
expiry) SimTrace a
trace)
ThreadDelay DiffTime
d SimA s b
k | DiffTime
d forall a. Ord a => a -> a -> Bool
< DiffTime
0 -> do
let expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall a s. a -> SimA s a
Return ()) (forall s a a b.
TimeoutId -> SimA s a -> ControlStack s a a -> ControlStack s b a
DelayFrame TimeoutId
nextTmid SimA s b
k ControlStack s b a
ctl) }
simstate' :: SimState s a
simstate' = SimState s a
simstate { nextTmid :: TimeoutId
nextTmid = forall a. Enum a => a -> a
succ TimeoutId
nextTmid }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate'
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> Time -> SimEventType
EventThreadDelay TimeoutId
nextTmid Time
expiry) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> SimEventType
EventThreadDelayFired TimeoutId
nextTmid) forall a b. (a -> b) -> a -> b
$
SimTrace a
trace)
ThreadDelay DiffTime
d SimA s b
k -> do
let expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
timers' :: Timeouts s
timers' = forall k p v.
(Ord k, Ord p) =>
k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.insert TimeoutId
nextTmid Time
expiry (forall s. IOSimThreadId -> TimeoutId -> TimerCompletionInfo s
TimerThreadDelay IOSimThreadId
tid TimeoutId
nextTmid) Timeouts s
timers
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall a s. a -> SimA s a
Return ()) (forall s a a b.
TimeoutId -> SimA s a -> ControlStack s a a -> ControlStack s b a
DelayFrame TimeoutId
nextTmid SimA s b
k ControlStack s b a
ctl) }
SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule (BlockedReason -> Deschedule
Blocked BlockedReason
BlockedOnDelay) Thread s a
thread'
SimState s a
simstate { timers :: Timeouts s
timers = Timeouts s
timers',
nextTmid :: TimeoutId
nextTmid = forall a. Enum a => a -> a
succ TimeoutId
nextTmid }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> Time -> SimEventType
EventThreadDelay TimeoutId
nextTmid Time
expiry) SimTrace a
trace)
NewTimeout DiffTime
d Timeout s -> SimA s b
k | DiffTime
d forall a. Ord a => a -> a -> Bool
< DiffTime
0 -> do
let t :: Timeout s
t = forall s. TimeoutId -> Timeout s
NegativeTimeout TimeoutId
nextTmid
expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (Timeout s -> SimA s b
k Timeout s
t) ControlStack s b a
ctl }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { nextTmid :: TimeoutId
nextTmid = forall a. Enum a => a -> a
succ TimeoutId
nextTmid }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> TVarId -> Time -> SimEventType
EventTimerCreated TimeoutId
nextTmid TVarId
nextVid Time
expiry) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> SimEventType
EventTimerCancelled TimeoutId
nextTmid) forall a b. (a -> b) -> a -> b
$
SimTrace a
trace)
NewTimeout DiffTime
d Timeout s -> SimA s b
k -> do
TVar s TimeoutState
tvar <- forall a s. TVarId -> Maybe ThreadLabel -> a -> ST s (TVar s a)
execNewTVar TVarId
nextVid
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ThreadLabel
"<<timeout-state " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> ThreadLabel
show (TimeoutId -> Int
unTimeoutId TimeoutId
nextTmid) forall a. [a] -> [a] -> [a]
++ ThreadLabel
">>")
TimeoutState
TimeoutPending
forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef (forall s a. TVar s a -> STRef s VectorClock
tvarVClock TVar s TimeoutState
tvar) (VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock VectorClock
vClock)
let expiry :: Time
expiry = DiffTime
d DiffTime -> Time -> Time
`addTime` Time
time
t :: Timeout s
t = forall s. TVar s TimeoutState -> TimeoutId -> Timeout s
Timeout TVar s TimeoutState
tvar TimeoutId
nextTmid
timers' :: Timeouts s
timers' = forall k p v.
(Ord k, Ord p) =>
k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.insert TimeoutId
nextTmid Time
expiry (forall s. TVar s TimeoutState -> TimerCompletionInfo s
Timer TVar s TimeoutState
tvar) Timeouts s
timers
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (Timeout s -> SimA s b
k Timeout s
t) ControlStack s b a
ctl }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { timers :: Timeouts s
timers = Timeouts s
timers'
, nextVid :: TVarId
nextVid = forall a. Enum a => a -> a
succ (forall a. Enum a => a -> a
succ TVarId
nextVid)
, nextTmid :: TimeoutId
nextTmid = forall a. Enum a => a -> a
succ TimeoutId
nextTmid }
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> TVarId -> Time -> SimEventType
EventTimerCreated TimeoutId
nextTmid TVarId
nextVid Time
expiry) SimTrace a
trace)
CancelTimeout (Timeout TVar s TimeoutState
tvar TimeoutId
tmid) SimA s b
k -> do
let timers' :: Timeouts s
timers' = forall k p v. (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.delete TimeoutId
tmid Timeouts s
timers
[SomeTVar s]
written <- forall s. StmA s () -> ST s [SomeTVar s]
execAtomically' (forall s a. STM s a -> StmA s a
runSTM forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadSTM m => TVar m a -> a -> STM m ()
writeTVar TVar s TimeoutState
tvar TimeoutState
TimeoutCancelled)
([IOSimThreadId]
wakeup, Map IOSimThreadId (Set (Labelled TVarId))
wokeby) <- forall s.
[SomeTVar s]
-> ST
s ([IOSimThreadId], Map IOSimThreadId (Set (Labelled TVarId)))
threadsUnblockedByWrites [SomeTVar s]
written
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(SomeTVar TVar s a
var) -> forall s a. TVar s a -> ST s ()
unblockAllThreadsFromTVar TVar s a
var) [SomeTVar s]
written
let effect' :: Effect
effect' = Effect
effect
forall a. Semigroup a => a -> a -> a
<> forall s. [SomeTVar s] -> Effect
writeEffects [SomeTVar s]
written
forall a. Semigroup a => a -> a -> a
<> [IOSimThreadId] -> Effect
wakeupEffects [IOSimThreadId]
wakeup
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl
, threadEffect :: Effect
threadEffect = Effect
effect'
}
([IOSimThreadId]
unblocked,
SimState s a
simstate') = forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads Bool
False VectorClock
vClock [IOSimThreadId]
wakeup SimState s a
simstate
forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef (forall s a. TVar s a -> STRef s VectorClock
tvarVClock TVar s TimeoutState
tvar) (VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock VectorClock
vClock)
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield Thread s a
thread' SimState s a
simstate' { timers :: Timeouts s
timers = Timeouts s
timers' }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (TimeoutId -> SimEventType
EventTimerCancelled TimeoutId
tmid)
forall a b. (a -> b) -> a -> b
$ forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany
[ (Time
time, IOSimThreadId
tid', (-Int
1), Maybe ThreadLabel
tlbl', [Labelled TVarId] -> SimEventType
EventTxWakeup [Labelled TVarId]
vids)
| IOSimThreadId
tid' <- [IOSimThreadId]
unblocked
, let tlbl' :: Maybe ThreadLabel
tlbl' = forall s a.
IOSimThreadId
-> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads
, let Just [Labelled TVarId]
vids = forall a. Set a -> [a]
Set.toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IOSimThreadId
tid' Map IOSimThreadId (Set (Labelled TVarId))
wokeby ]
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Yield)
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
CancelTimeout (NegativeTimeout TimeoutId
_tmid) SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
Fork IOSim s ()
a IOSimThreadId -> SimA s b
k -> do
let nextTId :: Int
nextTId = forall s a. Thread s a -> Int
threadNextTId Thread s a
thread
tid' :: IOSimThreadId
tid' | forall s a. Thread s a -> Bool
threadRacy Thread s a
thread = IOSimThreadId -> IOSimThreadId
setRacyThread forall a b. (a -> b) -> a -> b
$ IOSimThreadId -> Int -> IOSimThreadId
childThreadId IOSimThreadId
tid Int
nextTId
| Bool
otherwise = IOSimThreadId -> Int -> IOSimThreadId
childThreadId IOSimThreadId
tid Int
nextTId
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (IOSimThreadId -> SimA s b
k IOSimThreadId
tid') ControlStack s b a
ctl,
threadNextTId :: Int
threadNextTId = Int
nextTId forall a. Num a => a -> a -> a
+ Int
1,
threadEffect :: Effect
threadEffect = Effect
effect
forall a. Semigroup a => a -> a -> a
<> IOSimThreadId -> Effect
forkEffect IOSimThreadId
tid'
}
thread'' :: Thread s a
thread'' = Thread { threadId :: IOSimThreadId
threadId = IOSimThreadId
tid'
, threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. IOSim s a -> SimA s a
runIOSim IOSim s ()
a)
forall s a. ControlStack s () a
ForkFrame
, threadStatus :: ThreadStatus
threadStatus = ThreadStatus
ThreadRunning
, threadMasking :: MaskingState
threadMasking = forall s a. Thread s a -> MaskingState
threadMasking Thread s a
thread
, threadThrowTo :: [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = []
, threadClockId :: ClockId
threadClockId = forall s a. Thread s a -> ClockId
threadClockId Thread s a
thread
, threadLabel :: Maybe ThreadLabel
threadLabel = forall a. Maybe a
Nothing
, threadNextTId :: Int
threadNextTId = Int
1
, threadStep :: Int
threadStep = Int
0
, threadVClock :: VectorClock
threadVClock = IOSimThreadId -> Int -> VectorClock -> VectorClock
insertVClock IOSimThreadId
tid' Int
0
forall a b. (a -> b) -> a -> b
$ VectorClock
vClock
, threadEffect :: Effect
threadEffect = forall a. Monoid a => a
mempty
, threadRacy :: Bool
threadRacy = forall s a. Thread s a -> Bool
threadRacy Thread s a
thread
}
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid' Thread s a
thread'' Map IOSimThreadId (Thread s a)
threads
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield Thread s a
thread'
SimState s a
simstate { runqueue :: RunQueue
runqueue = forall s a. Thread s a -> RunQueue -> RunQueue
insertThread Thread s a
thread'' RunQueue
runqueue
, threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads' }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (IOSimThreadId -> SimEventType
EventThreadForked IOSimThreadId
tid')
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Yield)
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
Atomically STM s a
a a -> SimA s b
k -> forall s a c.
Time
-> IOSimThreadId
-> Maybe ThreadLabel
-> TVarId
-> StmA s a
-> (StmTxResult s a -> ST s (SimTrace c))
-> ST s (SimTrace c)
execAtomically Time
time IOSimThreadId
tid Maybe ThreadLabel
tlbl TVarId
nextVid (forall s a. STM s a -> StmA s a
runSTM STM s a
a) forall a b. (a -> b) -> a -> b
$ \StmTxResult s a
res ->
case StmTxResult s a
res of
StmTxCommitted a
x [SomeTVar s]
written [SomeTVar s]
read [SomeTVar s]
created
[Dynamic]
tvarDynamicTraces [ThreadLabel]
tvarStringTraces TVarId
nextVid' -> do
([IOSimThreadId]
wakeup, Map IOSimThreadId (Set (Labelled TVarId))
wokeby) <- forall s.
[SomeTVar s]
-> ST
s ([IOSimThreadId], Map IOSimThreadId (Set (Labelled TVarId)))
threadsUnblockedByWrites [SomeTVar s]
written
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s ()
unblockAllThreadsFromTVar TVar s a
tvar) [SomeTVar s]
written
VectorClock
vClockRead <- forall s. [SomeTVar s] -> ST s VectorClock
leastUpperBoundTVarVClocks [SomeTVar s]
read
let vClock' :: VectorClock
vClock' = VectorClock
vClock VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` VectorClock
vClockRead
effect' :: Effect
effect' = Effect
effect
forall a. Semigroup a => a -> a -> a
<> forall s. [SomeTVar s] -> Effect
readEffects [SomeTVar s]
read
forall a. Semigroup a => a -> a -> a
<> forall s. [SomeTVar s] -> Effect
writeEffects [SomeTVar s]
written
forall a. Semigroup a => a -> a -> a
<> [IOSimThreadId] -> Effect
wakeupEffects [IOSimThreadId]
unblocked
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (a -> SimA s b
k a
x) ControlStack s b a
ctl,
threadVClock :: VectorClock
threadVClock = VectorClock
vClock',
threadEffect :: Effect
threadEffect = Effect
effect' }
([IOSimThreadId]
unblocked,
SimState s a
simstate') = forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads Bool
True VectorClock
vClock' [IOSimThreadId]
wakeup SimState s a
simstate
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [ forall s a. STRef s a -> (a -> a) -> ST s ()
modifySTRef (forall s a. TVar s a -> STRef s VectorClock
tvarVClock TVar s a
r) (VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock VectorClock
vClock')
| SomeTVar TVar s a
r <- [SomeTVar s]
created forall a. [a] -> [a] -> [a]
++ [SomeTVar s]
written ]
[Labelled TVarId]
written' <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s (Labelled TVarId)
labelledTVarId TVar s a
tvar) [SomeTVar s]
written
[Labelled TVarId]
created' <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s (Labelled TVarId)
labelledTVarId TVar s a
tvar) [SomeTVar s]
created
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield Thread s a
thread' SimState s a
simstate' { nextVid :: TVarId
nextVid = TVarId
nextVid' }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl ([Labelled TVarId]
-> [Labelled TVarId] -> Maybe Effect -> SimEventType
EventTxCommitted [Labelled TVarId]
written' [Labelled TVarId]
created' (forall a. a -> Maybe a
Just Effect
effect')) forall a b. (a -> b) -> a -> b
$
forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany
[ (Time
time, IOSimThreadId
tid', (-Int
1), Maybe ThreadLabel
tlbl', [Labelled TVarId] -> SimEventType
EventTxWakeup [Labelled TVarId]
vids')
| IOSimThreadId
tid' <- [IOSimThreadId]
unblocked
, let tlbl' :: Maybe ThreadLabel
tlbl' = forall s a.
IOSimThreadId
-> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads
, let Just [Labelled TVarId]
vids' = forall a. Set a -> [a]
Set.toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IOSimThreadId
tid' Map IOSimThreadId (Set (Labelled TVarId))
wokeby ] forall a b. (a -> b) -> a -> b
$
forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany
[ (Time
time, IOSimThreadId
tid, Int
tstep, Maybe ThreadLabel
tlbl, Dynamic -> SimEventType
EventLog Dynamic
tr)
| Dynamic
tr <- [Dynamic]
tvarDynamicTraces
] forall a b. (a -> b) -> a -> b
$
forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany
[ (Time
time, IOSimThreadId
tid, Int
tstep, Maybe ThreadLabel
tlbl, ThreadLabel -> SimEventType
EventSay ThreadLabel
str)
| ThreadLabel
str <- [ThreadLabel]
tvarStringTraces
] forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl ([IOSimThreadId] -> SimEventType
EventUnblocked [IOSimThreadId]
unblocked) forall a b. (a -> b) -> a -> b
$
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Yield) forall a b. (a -> b) -> a -> b
$
SimTrace a
trace
StmTxAborted [SomeTVar s]
read SomeException
e -> do
VectorClock
vClockRead <- forall s. [SomeTVar s] -> ST s VectorClock
leastUpperBoundTVarVClocks [SomeTVar s]
read
let effect' :: Effect
effect' = Effect
effect forall a. Semigroup a => a -> a -> a
<> forall s. [SomeTVar s] -> Effect
readEffects [SomeTVar s]
read
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. SomeException -> SimA s a
Throw SomeException
e) ControlStack s b a
ctl,
threadVClock :: VectorClock
threadVClock = VectorClock
vClock VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` VectorClock
vClockRead,
threadEffect :: Effect
threadEffect = Effect
effect' }
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Maybe Effect -> SimEventType
EventTxAborted (forall a. a -> Maybe a
Just Effect
effect'))
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
StmTxBlocked [SomeTVar s]
read -> do
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(SomeTVar TVar s a
tvar) -> forall s a. IOSimThreadId -> TVar s a -> ST s ()
blockThreadOnTVar IOSimThreadId
tid TVar s a
tvar) [SomeTVar s]
read
[Labelled TVarId]
vids <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s (Labelled TVarId)
labelledTVarId TVar s a
tvar) [SomeTVar s]
read
VectorClock
vClockRead <- forall s. [SomeTVar s] -> ST s VectorClock
leastUpperBoundTVarVClocks [SomeTVar s]
read
let effect' :: Effect
effect' = Effect
effect forall a. Semigroup a => a -> a -> a
<> forall s. [SomeTVar s] -> Effect
readEffects [SomeTVar s]
read
thread' :: Thread s a
thread' = Thread s a
thread { threadVClock :: VectorClock
threadVClock = VectorClock
vClock VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` VectorClock
vClockRead,
threadEffect :: Effect
threadEffect = Effect
effect' }
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule (BlockedReason -> Deschedule
Blocked BlockedReason
BlockedOnSTM) Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl ([Labelled TVarId] -> Maybe Effect -> SimEventType
EventTxBlocked [Labelled TVarId]
vids (forall a. a -> Maybe a
Just Effect
effect'))
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule (BlockedReason -> Deschedule
Blocked BlockedReason
BlockedOnSTM))
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
GetThreadId IOSimThreadId -> SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (IOSimThreadId -> SimA s b
k IOSimThreadId
tid) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
LabelThread IOSimThreadId
tid' ThreadLabel
l SimA s b
k | IOSimThreadId
tid' forall a. Eq a => a -> a -> Bool
== IOSimThreadId
tid -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl
, threadLabel :: Maybe ThreadLabel
threadLabel = forall a. a -> Maybe a
Just ThreadLabel
l }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
LabelThread IOSimThreadId
tid' ThreadLabel
l SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (\Thread s a
t -> Thread s a
t { threadLabel :: Maybe ThreadLabel
threadLabel = forall a. a -> Maybe a
Just ThreadLabel
l }) IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate { threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads' }
ExploreRaces SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl
, threadRacy :: Bool
threadRacy = Bool
True }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
Fix x -> IOSim s x
f x -> SimA s b
k -> do
STRef s x
r <- forall a s. a -> ST s (STRef s a)
newSTRef (forall a e. Exception e => e -> a
throw NonTermination
NonTermination)
x
x <- forall s a. ST s a -> ST s a
unsafeInterleaveST forall a b. (a -> b) -> a -> b
$ forall s a. STRef s a -> ST s a
readSTRef STRef s x
r
let k' :: SimA s b
k' = forall s a. IOSim s a -> forall r. (a -> SimA s r) -> SimA s r
unIOSim (x -> IOSim s x
f x
x) forall a b. (a -> b) -> a -> b
$ \x
x' ->
forall s a b. ST s a -> (a -> SimA s b) -> SimA s b
LiftST (forall s a. ST s a -> ST s a
lazyToStrictST (forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s x
r x
x')) (\() -> x -> SimA s b
k x
x')
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k' ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
GetMaskState MaskingState -> SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (MaskingState -> SimA s b
k MaskingState
maskst) ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
SetMaskState MaskingState
maskst' IOSim s a
action' a -> SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl
(forall s a. IOSim s a -> SimA s a
runIOSim IOSim s a
action')
(forall b s a a.
(b -> SimA s a)
-> MaskingState -> ControlStack s a a -> ControlStack s b a
MaskFrame a -> SimA s b
k MaskingState
maskst ControlStack s b a
ctl)
, threadMasking :: MaskingState
threadMasking = MaskingState
maskst' }
SimTrace a
trace <-
case MaskingState
maskst' of
MaskingState
Unmasked -> forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Interruptable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Interruptable Thread s a
thread' SimState s a
simstate
MaskingState
_ -> forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (MaskingState -> SimEventType
EventMask MaskingState
maskst')
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
ThrowTo SomeException
e IOSimThreadId
tid' SimA s b
_ | IOSimThreadId
tid' forall a. Eq a => a -> a -> Bool
== IOSimThreadId
tid -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. SomeException -> SimA s a
Throw SomeException
e) ControlStack s b a
ctl
, threadEffect :: Effect
threadEffect = Effect
effect
}
SimTrace a
trace <- forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> IOSimThreadId -> SimEventType
EventThrowTo SomeException
e IOSimThreadId
tid) SimTrace a
trace)
ThrowTo SomeException
e IOSimThreadId
tid' SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl,
threadEffect :: Effect
threadEffect = Effect
effect forall a. Semigroup a => a -> a -> a
<> IOSimThreadId -> Effect
throwToEffect IOSimThreadId
tid'
forall a. Semigroup a => a -> a -> a
<> Effect
wakeUpEffect,
threadVClock :: VectorClock
threadVClock = VectorClock
vClock VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` VectorClock
vClockTgt
}
(VectorClock
vClockTgt,
Effect
wakeUpEffect,
Bool
willBlock) = (forall s a. Thread s a -> VectorClock
threadVClock Thread s a
t,
if forall s a. Thread s a -> Bool
isThreadBlocked Thread s a
t then [IOSimThreadId] -> Effect
wakeupEffects [IOSimThreadId
tid'] else forall a. Monoid a => a
mempty,
Bool -> Bool
not (forall s a. Thread s a -> Bool
threadInterruptible Thread s a
t Bool -> Bool -> Bool
|| forall s a. Thread s a -> Bool
isThreadDone Thread s a
t))
where Just Thread s a
t = forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads
if Bool
willBlock
then do
let adjustTarget :: Thread s a -> Thread s a
adjustTarget Thread s a
t =
Thread s a
t { threadThrowTo :: [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = (SomeException
e, forall a. a -> Maybe ThreadLabel -> Labelled a
Labelled IOSimThreadId
tid Maybe ThreadLabel
tlbl, VectorClock
vClock) forall a. a -> [a] -> [a]
: forall s a.
Thread s a
-> [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo Thread s a
t }
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust Thread s a -> Thread s a
adjustTarget IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads
SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule (BlockedReason -> Deschedule
Blocked BlockedReason
BlockedOnThrowTo) Thread s a
thread' SimState s a
simstate { threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads' }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> IOSimThreadId -> SimEventType
EventThrowTo SomeException
e IOSimThreadId
tid')
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl SimEventType
EventThrowToBlocked
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule (BlockedReason -> Deschedule
Blocked BlockedReason
BlockedOnThrowTo))
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
else do
let adjustTarget :: Thread s a -> Thread s a
adjustTarget t :: Thread s a
t@Thread{ threadControl :: forall s a. Thread s a -> ThreadControl s a
threadControl = ThreadControl SimA s b
_ ControlStack s b a
ctl',
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock' } =
Thread s a
t { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. SomeException -> SimA s a
Throw SomeException
e) ControlStack s b a
ctl'
, threadStatus :: ThreadStatus
threadStatus = if forall s a. Thread s a -> Bool
isThreadDone Thread s a
t
then forall s a. Thread s a -> ThreadStatus
threadStatus Thread s a
t
else ThreadStatus
ThreadRunning
, threadVClock :: VectorClock
threadVClock = VectorClock
vClock' VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` VectorClock
vClock }
([IOSimThreadId]
_unblocked, simstate' :: SimState s a
simstate'@SimState { threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads' }) = forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads Bool
False VectorClock
vClock [IOSimThreadId
tid'] SimState s a
simstate
threads'' :: Map IOSimThreadId (Thread s a)
threads'' = forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust Thread s a -> Thread s a
adjustTarget IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads'
simstate'' :: SimState s a
simstate'' = SimState s a
simstate' { threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads'' }
SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield Thread s a
thread' SimState s a
simstate''
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (SomeException -> IOSimThreadId -> SimEventType
EventThrowTo SomeException
e IOSimThreadId
tid')
forall a b. (a -> b) -> a -> b
$ SimTrace a
trace
YieldSim SimA s b
k -> do
let thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl SimA s b
k ControlStack s b a
ctl }
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread' SimState s a
simstate
threadInterruptible :: Thread s a -> Bool
threadInterruptible :: forall s a. Thread s a -> Bool
threadInterruptible Thread s a
thread =
case forall s a. Thread s a -> MaskingState
threadMasking Thread s a
thread of
MaskingState
Unmasked -> Bool
True
MaskingState
MaskedInterruptible
| forall s a. Thread s a -> Bool
isThreadBlocked Thread s a
thread -> Bool
True
| Bool
otherwise -> Bool
False
MaskingState
MaskedUninterruptible -> Bool
False
deschedule :: Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule :: forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield thread :: Thread s a
thread@Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep,
threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock }
simstate :: SimState s a
simstate@SimState{RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue,
Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads,
curTime :: forall s a. SimState s a -> Time
curTime = Time
time,
ScheduleControl
control :: ScheduleControl
control :: forall s a. SimState s a -> ScheduleControl
control } =
let (Thread s a
thread', Effect
eff) = forall s a. Thread s a -> (Thread s a, Effect)
stepThread Thread s a
thread
runqueue' :: RunQueue
runqueue' = forall s a. Thread s a -> RunQueue -> RunQueue
insertThread Thread s a
thread' RunQueue
runqueue
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid Thread s a
thread' Map IOSimThreadId (Thread s a)
threads
control' :: ScheduleControl
control' = StepId -> ScheduleControl -> ScheduleControl
advanceControl (forall s a. Thread s a -> StepId
threadStepId Thread s a
thread) ScheduleControl
control
races' :: Races
races' = forall s a. Thread s a -> SimState s a -> Races
updateRaces Thread s a
thread SimState s a
simstate in
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (VectorClock -> Effect -> SimEventType
EventEffect VectorClock
vClock Effect
eff) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Races -> SimEventType
EventRaces Races
races') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall s a. SimState s a -> ST s (SimTrace a)
reschedule SimState s a
simstate { runqueue :: RunQueue
runqueue = RunQueue
runqueue',
threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads',
races :: Races
races = Races
races',
control :: ScheduleControl
control = ScheduleControl
control' }
deschedule Deschedule
Interruptable thread :: Thread s a
thread@Thread {
threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep,
threadControl :: forall s a. Thread s a -> ThreadControl s a
threadControl = ThreadControl SimA s b
_ ControlStack s b a
ctl,
threadMasking :: forall s a. Thread s a -> MaskingState
threadMasking = MaskingState
Unmasked,
threadThrowTo :: forall s a.
Thread s a
-> [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = (SomeException
e, Labelled IOSimThreadId
tid', VectorClock
vClock') : [(SomeException, Labelled IOSimThreadId, VectorClock)]
etids,
threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock,
threadEffect :: forall s a. Thread s a -> Effect
threadEffect = Effect
effect
}
simstate :: SimState s a
simstate@SimState{ curTime :: forall s a. SimState s a -> Time
curTime = Time
time, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads } = do
let effect' :: Effect
effect' = Effect
effect forall a. Semigroup a => a -> a -> a
<> [IOSimThreadId] -> Effect
wakeupEffects [IOSimThreadId]
unblocked
thread' :: Thread s a
thread' = Thread s a
thread { threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. SomeException -> SimA s a
Throw SomeException
e) ControlStack s b a
ctl
, threadMasking :: MaskingState
threadMasking = MaskingState
MaskedInterruptible
, threadThrowTo :: [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = [(SomeException, Labelled IOSimThreadId, VectorClock)]
etids
, threadVClock :: VectorClock
threadVClock = VectorClock
vClock VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` VectorClock
vClock'
, threadEffect :: Effect
threadEffect = Effect
effect'
}
([IOSimThreadId]
unblocked,
SimState s a
simstate') = forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads Bool
False VectorClock
vClock [forall a. Labelled a -> a
l_labelled Labelled IOSimThreadId
tid'] SimState s a
simstate
!SimTrace a
trace <- forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Yield Thread s a
thread' SimState s a
simstate'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Labelled IOSimThreadId -> SimEventType
EventThrowToUnmasked Labelled IOSimThreadId
tid')
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (VectorClock -> Effect -> SimEventType
EventEffect VectorClock
vClock Effect
effect')
forall a b. (a -> b) -> a -> b
$ forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany [ (Time
time, IOSimThreadId
tid'', (-Int
1), Maybe ThreadLabel
tlbl'', SimEventType
EventThrowToWakeup)
| IOSimThreadId
tid'' <- [IOSimThreadId]
unblocked
, let tlbl'' :: Maybe ThreadLabel
tlbl'' = forall s a.
IOSimThreadId
-> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel IOSimThreadId
tid'' Map IOSimThreadId (Thread s a)
threads ]
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Yield)
SimTrace a
trace
deschedule Deschedule
Interruptable thread :: Thread s a
thread@Thread{threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep,
threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock}
simstate :: SimState s a
simstate@SimState{ ScheduleControl
control :: ScheduleControl
control :: forall s a. SimState s a -> ScheduleControl
control,
curTime :: forall s a. SimState s a -> Time
curTime = Time
time } =
let (Thread s a
thread', Effect
eff) = forall s a. Thread s a -> (Thread s a, Effect)
stepThread Thread s a
thread
races' :: Races
races' = forall s a. Thread s a -> SimState s a -> Races
updateRaces Thread s a
thread SimState s a
simstate in
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (VectorClock -> Effect -> SimEventType
EventEffect VectorClock
vClock Effect
eff) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Races -> SimEventType
EventRaces Races
races') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread'
SimState s a
simstate{ races :: Races
races = Races
races',
control :: ScheduleControl
control = StepId -> ScheduleControl -> ScheduleControl
advanceControl (forall s a. Thread s a -> StepId
threadStepId Thread s a
thread) ScheduleControl
control }
deschedule (Blocked BlockedReason
_blockedReason) thread :: Thread s a
thread@Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid
, threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep
, threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl
, threadThrowTo :: forall s a.
Thread s a
-> [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = (SomeException, Labelled IOSimThreadId, VectorClock)
_ : [(SomeException, Labelled IOSimThreadId, VectorClock)]
_
, threadMasking :: forall s a. Thread s a -> MaskingState
threadMasking = MaskingState
maskst
, threadEffect :: forall s a. Thread s a -> Effect
threadEffect = Effect
effect }
simstate :: SimState s a
simstate@SimState{ curTime :: forall s a. SimState s a -> Time
curTime = Time
time }
| MaskingState
maskst forall a. Eq a => a -> a -> Bool
/= MaskingState
MaskedUninterruptible =
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Deschedule -> SimEventType
EventDeschedule Deschedule
Interruptable) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall s a.
Deschedule -> Thread s a -> SimState s a -> ST s (SimTrace a)
deschedule Deschedule
Interruptable Thread s a
thread { threadMasking :: MaskingState
threadMasking = MaskingState
Unmasked } SimState s a
simstate
deschedule (Blocked BlockedReason
blockedReason) thread :: Thread s a
thread@Thread{ threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep,
threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock}
simstate :: SimState s a
simstate@SimState{ Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads,
curTime :: forall s a. SimState s a -> Time
curTime = Time
time,
ScheduleControl
control :: ScheduleControl
control :: forall s a. SimState s a -> ScheduleControl
control } =
let thread1 :: Thread s a
thread1 = Thread s a
thread { threadStatus :: ThreadStatus
threadStatus = BlockedReason -> ThreadStatus
ThreadBlocked BlockedReason
blockedReason }
(Thread s a
thread', Effect
eff) = forall s a. Thread s a -> (Thread s a, Effect)
stepThread Thread s a
thread1
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
thread') Thread s a
thread' Map IOSimThreadId (Thread s a)
threads
races' :: Races
races' = forall s a. Thread s a -> SimState s a -> Races
updateRaces Thread s a
thread1 SimState s a
simstate in
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (VectorClock -> Effect -> SimEventType
EventEffect VectorClock
vClock Effect
eff) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Races -> SimEventType
EventRaces Races
races') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall s a. SimState s a -> ST s (SimTrace a)
reschedule SimState s a
simstate { threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads',
races :: Races
races = Races
races',
control :: ScheduleControl
control = StepId -> ScheduleControl -> ScheduleControl
advanceControl (forall s a. Thread s a -> StepId
threadStepId Thread s a
thread1) ScheduleControl
control }
deschedule Deschedule
Terminated thread :: Thread s a
thread@Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid, threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep, threadLabel :: forall s a. Thread s a -> Maybe ThreadLabel
threadLabel = Maybe ThreadLabel
tlbl,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock, threadEffect :: forall s a. Thread s a -> Effect
threadEffect = Effect
effect }
simstate :: SimState s a
simstate@SimState{ curTime :: forall s a. SimState s a -> Time
curTime = Time
time, ScheduleControl
control :: ScheduleControl
control :: forall s a. SimState s a -> ScheduleControl
control } = do
let wakeup :: [IOSimThreadId]
wakeup = forall a b. (a -> b) -> [a] -> [b]
map (\(SomeException
_,Labelled IOSimThreadId
tid',VectorClock
_) -> forall a. Labelled a -> a
l_labelled Labelled IOSimThreadId
tid') (forall a. [a] -> [a]
reverse (forall s a.
Thread s a
-> [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo Thread s a
thread))
([IOSimThreadId]
unblocked,
simstate' :: SimState s a
simstate'@SimState{Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads}) =
forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads Bool
False VectorClock
vClock [IOSimThreadId]
wakeup SimState s a
simstate
effect' :: Effect
effect' = Effect
effect forall a. Semigroup a => a -> a -> a
<> [IOSimThreadId] -> Effect
wakeupEffects [IOSimThreadId]
unblocked
(Thread s a
thread', Effect
eff) = forall s a. Thread s a -> (Thread s a, Effect)
stepThread forall a b. (a -> b) -> a -> b
$ Thread s a
thread { threadStatus :: ThreadStatus
threadStatus = ThreadStatus
ThreadDone,
threadEffect :: Effect
threadEffect = Effect
effect' }
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid Thread s a
thread' Map IOSimThreadId (Thread s a)
threads
races' :: Races
races' = IOSimThreadId -> Races -> Races
threadTerminatesRaces IOSimThreadId
tid forall a b. (a -> b) -> a -> b
$ forall s a. Thread s a -> SimState s a -> Races
updateRaces Thread s a
thread { threadEffect :: Effect
threadEffect = Effect
effect' } SimState s a
simstate
!SimTrace a
trace <- forall s a. SimState s a -> ST s (SimTrace a)
reschedule SimState s a
simstate' { races :: Races
races = Races
races',
control :: ScheduleControl
control = StepId -> ScheduleControl -> ScheduleControl
advanceControl (forall s a. Thread s a -> StepId
threadStepId Thread s a
thread) ScheduleControl
control,
threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads' }
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany
[ (Time
time, IOSimThreadId
tid', (-Int
1), Maybe ThreadLabel
tlbl', SimEventType
EventThrowToWakeup)
| IOSimThreadId
tid' <- [IOSimThreadId]
unblocked
, let tlbl' :: Maybe ThreadLabel
tlbl' = forall s a.
IOSimThreadId
-> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads ]
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (VectorClock -> Effect -> SimEventType
EventEffect VectorClock
vClock Effect
eff)
forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl (Races -> SimEventType
EventRaces Races
races')
SimTrace a
trace
deschedule Deschedule
Sleep thread :: Thread s a
thread@Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid , threadEffect :: forall s a. Thread s a -> Effect
threadEffect = Effect
effect' }
simstate :: SimState s a
simstate@SimState{RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads} =
let runqueue' :: RunQueue
runqueue' = forall s a. Thread s a -> RunQueue -> RunQueue
insertThread Thread s a
thread RunQueue
runqueue
threads' :: Map IOSimThreadId (Thread s a)
threads' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid Thread s a
thread Map IOSimThreadId (Thread s a)
threads in
forall s a. SimState s a -> ST s (SimTrace a)
reschedule SimState s a
simstate { runqueue :: RunQueue
runqueue = RunQueue
runqueue', threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads' }
reschedule :: SimState s a -> ST s (SimTrace a)
reschedule :: forall s a. SimState s a -> ST s (SimTrace a)
reschedule simstate :: SimState s a
simstate@SimState { RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue, control :: forall s a. SimState s a -> ScheduleControl
control = control :: ScheduleControl
control@(ControlFollow ((IOSimThreadId
tid,Int
_):[StepId]
_) [ScheduleMod]
_) }
| Bool -> Bool
not (forall a. a -> Down a
Down IOSimThreadId
tid forall k p v. Ord k => k -> OrdPSQ k p v -> Bool
`PSQ.member` RunQueue
runqueue) =
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Trace a b
Trace.Nil (forall a. ThreadLabel -> SimResult a
InternalError (ThreadLabel
"assertion failure: " forall a. [a] -> [a] -> [a]
++ IOSimThreadId -> ThreadLabel
ppIOSimThreadId IOSimThreadId
tid forall a. [a] -> [a] -> [a]
++ ThreadLabel
" not runnable")))
reschedule simstate :: SimState s a
simstate@SimState { Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads, control :: forall s a. SimState s a -> ScheduleControl
control = control :: ScheduleControl
control@(ControlFollow ((IOSimThreadId
tid,Int
_):[StepId]
_) [ScheduleMod]
_) }
| Bool -> Bool
not (IOSimThreadId
tid forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map IOSimThreadId (Thread s a)
threads) =
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Trace a b
Trace.Nil (forall a. ThreadLabel -> SimResult a
InternalError (ThreadLabel
"assertion failure: " forall a. [a] -> [a] -> [a]
++ IOSimThreadId -> ThreadLabel
ppIOSimThreadId IOSimThreadId
tid forall a. [a] -> [a] -> [a]
++ ThreadLabel
" not in threads")))
reschedule simstate :: SimState s a
simstate@SimState { RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads,
control :: forall s a. SimState s a -> ScheduleControl
control = control :: ScheduleControl
control@(ControlFollow ((IOSimThreadId
tid,Int
tstep):[StepId]
_) [ScheduleMod]
_),
curTime :: forall s a. SimState s a -> Time
curTime = Time
time } =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep forall a. Maybe a
Nothing (ScheduleControl -> SimEventType
EventReschedule ScheduleControl
control)) forall a b. (a -> b) -> a -> b
$
forall s a x. Maybe (Thread s a) -> SimState s a -> x -> x
invariant forall a. Maybe a
Nothing SimState s a
simstate forall a b. (a -> b) -> a -> b
$
let thread :: Thread s a
thread = Map IOSimThreadId (Thread s a)
threads forall k a. Ord k => Map k a -> k -> a
Map.! IOSimThreadId
tid in
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
thread forall a. Eq a => a -> a -> Bool
== IOSimThreadId
tid) forall a b. (a -> b) -> a -> b
$
if forall s a. Thread s a -> Int
threadStep Thread s a
thread forall a. Eq a => a -> a -> Bool
/= Int
tstep then
forall a. (?callStack::CallStack) => ThreadLabel -> a
error forall a b. (a -> b) -> a -> b
$ ThreadLabel
"Thread step out of sync\n"
forall a. [a] -> [a] -> [a]
++ ThreadLabel
" runqueue: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> ThreadLabel
show RunQueue
runqueueforall a. [a] -> [a] -> [a]
++ThreadLabel
"\n"
forall a. [a] -> [a] -> [a]
++ ThreadLabel
" follows: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> ThreadLabel
show IOSimThreadId
tidforall a. [a] -> [a] -> [a]
++ThreadLabel
", step "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> ThreadLabel
show Int
tstepforall a. [a] -> [a] -> [a]
++ThreadLabel
"\n"
forall a. [a] -> [a] -> [a]
++ ThreadLabel
" actual step: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> ThreadLabel
show (forall s a. Thread s a -> Int
threadStep Thread s a
thread)forall a. [a] -> [a] -> [a]
++ThreadLabel
"\n"
forall a. [a] -> [a] -> [a]
++ ThreadLabel
"Thread:\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> ThreadLabel
show Thread s a
thread forall a. [a] -> [a] -> [a]
++ ThreadLabel
"\n"
else
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread SimState s a
simstate { runqueue :: RunQueue
runqueue = forall k p v. (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.delete (forall a. a -> Down a
Down IOSimThreadId
tid) RunQueue
runqueue
, threads :: Map IOSimThreadId (Thread s a)
threads = forall k a. Ord k => k -> Map k a -> Map k a
Map.delete IOSimThreadId
tid Map IOSimThreadId (Thread s a)
threads }
reschedule simstate :: SimState s a
simstate@SimState{ RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads }
| Just (Down !IOSimThreadId
tid, Down IOSimThreadId
_, ()
_, RunQueue
runqueue') <- forall k p v.
(Ord k, Ord p) =>
OrdPSQ k p v -> Maybe (k, p, v, OrdPSQ k p v)
PSQ.minView RunQueue
runqueue =
forall s a x. Maybe (Thread s a) -> SimState s a -> x -> x
invariant forall a. Maybe a
Nothing SimState s a
simstate forall a b. (a -> b) -> a -> b
$
let thread :: Thread s a
thread = Map IOSimThreadId (Thread s a)
threads forall k a. Ord k => Map k a -> k -> a
Map.! IOSimThreadId
tid in
forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
thread SimState s a
simstate { runqueue :: RunQueue
runqueue = RunQueue
runqueue'
, threads :: Map IOSimThreadId (Thread s a)
threads = forall k a. Ord k => k -> Map k a -> Map k a
Map.delete IOSimThreadId
tid Map IOSimThreadId (Thread s a)
threads }
reschedule simstate :: SimState s a
simstate@SimState{ Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads, Timeouts s
timers :: Timeouts s
timers :: forall s a. SimState s a -> Timeouts s
timers, curTime :: forall s a. SimState s a -> Time
curTime = Time
time, Races
races :: Races
races :: forall s a. SimState s a -> Races
races } =
forall s a x. Maybe (Thread s a) -> SimState s a -> x -> x
invariant forall a. Maybe a
Nothing SimState s a
simstate forall a b. (a -> b) -> a -> b
$
case forall k p a.
(Ord k, Ord p) =>
OrdPSQ k p a -> Maybe ([k], p, [a], OrdPSQ k p a)
removeMinimums Timeouts s
timers of
Maybe ([TimeoutId], Time, [TimerCompletionInfo s], Timeouts s)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. SimState s a -> SimTrace a -> SimTrace a
traceFinalRacesFound SimState s a
simstate forall a b. (a -> b) -> a -> b
$
forall a. Time -> [Labelled IOSimThreadId] -> SimTrace a
TraceDeadlock Time
time (forall s a.
Map IOSimThreadId (Thread s a) -> [Labelled IOSimThreadId]
labelledThreads Map IOSimThreadId (Thread s a)
threads))
Just ([TimeoutId]
tmids, Time
time', [TimerCompletionInfo s]
fired, Timeouts s
timers') -> forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Time
time' forall a. Ord a => a -> a -> Bool
>= Time
time) forall a b. (a -> b) -> a -> b
$ do
[SomeTVar s]
written <- forall s. StmA s () -> ST s [SomeTVar s]
execAtomically' (forall s a. STM s a -> StmA s a
runSTM forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall {m :: * -> *} {s}.
(TVar m ~ TVar s, MonadSTM m) =>
TimerCompletionInfo s -> STM m ()
timeoutAction [TimerCompletionInfo s]
fired)
![TraceValue]
ds <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(SomeTVar TVar s a
tvar) -> do
TraceValue
tr <- forall s a. TVar s a -> Bool -> ST s TraceValue
traceTVarST TVar s a
tvar Bool
False
!()
_ <- forall s a. TVar s a -> ST s ()
commitTVar TVar s a
tvar
forall (m :: * -> *) a. Monad m => a -> m a
return TraceValue
tr) [SomeTVar s]
written
([IOSimThreadId]
wakeupSTM, Map IOSimThreadId (Set (Labelled TVarId))
wokeby) <- forall s.
[SomeTVar s]
-> ST
s ([IOSimThreadId], Map IOSimThreadId (Set (Labelled TVarId)))
threadsUnblockedByWrites [SomeTVar s]
written
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s ()
unblockAllThreadsFromTVar TVar s a
tvar) [SomeTVar s]
written
let wakeupThreadDelay :: [(IOSimThreadId, TimeoutId)]
wakeupThreadDelay = [ (IOSimThreadId
tid, TimeoutId
tmid) | TimerThreadDelay IOSimThreadId
tid TimeoutId
tmid <- [TimerCompletionInfo s]
fired ]
wakeup :: [IOSimThreadId]
wakeup = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` [(IOSimThreadId, TimeoutId)]
wakeupThreadDelay forall a. [a] -> [a] -> [a]
++ [IOSimThreadId]
wakeupSTM
([IOSimThreadId]
_, !SimState s a
simstate') = forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads Bool
False VectorClock
bottomVClock [IOSimThreadId]
wakeup SimState s a
simstate
!timeoutExpired :: [(IOSimThreadId, TimeoutId, TMVarDefault (IOSim s) IOSimThreadId)]
timeoutExpired = [ (IOSimThreadId
tid, TimeoutId
tmid, TMVar (IOSim s) IOSimThreadId
lock)
| TimerTimeout IOSimThreadId
tid TimeoutId
tmid TMVar (IOSim s) IOSimThreadId
lock <- [TimerCompletionInfo s]
fired ]
!SimState s a
simstate'' <- forall s a.
[(IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)]
-> SimState s a -> ST s (SimState s a)
forkTimeoutInterruptThreads [(IOSimThreadId, TimeoutId, TMVarDefault (IOSim s) IOSimThreadId)]
timeoutExpired
SimState s a
simstate' { races :: Races
races = Races
noRaces }
!SimTrace a
trace <- forall s a. SimState s a -> ST s (SimTrace a)
reschedule SimState s a
simstate'' { curTime :: Time
curTime = Time
time'
, timers :: Timeouts s
timers = Timeouts s
timers' }
let traceEntries :: [(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
traceEntries =
[ ( Time
time', [Int] -> IOSimThreadId
ThreadId [-Int
1], -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"timer"
, TimeoutId -> SimEventType
EventTimerFired TimeoutId
tmid)
| (TimeoutId
tmid, Timer TVar s TimeoutState
_) <- forall a b. [a] -> [b] -> [(a, b)]
zip [TimeoutId]
tmids [TimerCompletionInfo s]
fired ]
forall a. [a] -> [a] -> [a]
++ [ ( Time
time', [Int] -> IOSimThreadId
ThreadId [-Int
1], -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"register delay timer"
, TimeoutId -> SimEventType
EventRegisterDelayFired TimeoutId
tmid)
| (TimeoutId
tmid, TimerRegisterDelay TVar s Bool
_) <- forall a b. [a] -> [b] -> [(a, b)]
zip [TimeoutId]
tmids [TimerCompletionInfo s]
fired ]
forall a. [a] -> [a] -> [a]
++ [ (Time
time', [Int] -> IOSimThreadId
ThreadId [-Int
1], -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"register delay timer", Dynamic -> SimEventType
EventLog (forall a. Typeable a => a -> Dynamic
toDyn tr
a))
| TraceValue { traceDynamic :: ()
traceDynamic = Just tr
a } <- [TraceValue]
ds ]
forall a. [a] -> [a] -> [a]
++ [ (Time
time', [Int] -> IOSimThreadId
ThreadId [-Int
1], -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"register delay timer", ThreadLabel -> SimEventType
EventSay ThreadLabel
a)
| TraceValue { traceString :: TraceValue -> Maybe ThreadLabel
traceString = Just ThreadLabel
a } <- [TraceValue]
ds ]
forall a. [a] -> [a] -> [a]
++ [ (Time
time', IOSimThreadId
tid', -Int
1, Maybe ThreadLabel
tlbl', [Labelled TVarId] -> SimEventType
EventTxWakeup [Labelled TVarId]
vids)
| IOSimThreadId
tid' <- [IOSimThreadId]
wakeupSTM
, let tlbl' :: Maybe ThreadLabel
tlbl' = forall s a.
IOSimThreadId
-> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel IOSimThreadId
tid' Map IOSimThreadId (Thread s a)
threads
, let Just [Labelled TVarId]
vids = forall a. Set a -> [a]
Set.toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IOSimThreadId
tid' Map IOSimThreadId (Set (Labelled TVarId))
wokeby ]
forall a. [a] -> [a] -> [a]
++ [ ( Time
time', IOSimThreadId
tid, -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"thread delay timer"
, TimeoutId -> SimEventType
EventThreadDelayFired TimeoutId
tmid)
| (IOSimThreadId
tid, TimeoutId
tmid) <- [(IOSimThreadId, TimeoutId)]
wakeupThreadDelay ]
forall a. [a] -> [a] -> [a]
++ [ ( Time
time', IOSimThreadId
tid, -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"timeout timer"
, TimeoutId -> SimEventType
EventTimeoutFired TimeoutId
tmid)
| (IOSimThreadId
tid, TimeoutId
tmid, TMVarDefault (IOSim s) IOSimThreadId
_) <- [(IOSimThreadId, TimeoutId, TMVarDefault (IOSim s) IOSimThreadId)]
timeoutExpired ]
forall a. [a] -> [a] -> [a]
++ [ ( Time
time', IOSimThreadId
tid, -Int
1, forall a. a -> Maybe a
Just ThreadLabel
"forked thread"
, IOSimThreadId -> SimEventType
EventThreadForked IOSimThreadId
tid)
| (IOSimThreadId
tid, TimeoutId
_, TMVarDefault (IOSim s) IOSimThreadId
_) <- [(IOSimThreadId, TimeoutId, TMVarDefault (IOSim s) IOSimThreadId)]
timeoutExpired ]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
forall s a. SimState s a -> SimTrace a -> SimTrace a
traceFinalRacesFound SimState s a
simstate forall a b. (a -> b) -> a -> b
$
forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany [(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
traceEntries SimTrace a
trace
where
timeoutAction :: TimerCompletionInfo s -> STM m ()
timeoutAction (Timer TVar s TimeoutState
var) = do
TimeoutState
x <- forall (m :: * -> *) a. MonadSTM m => TVar m a -> STM m a
readTVar TVar s TimeoutState
var
case TimeoutState
x of
TimeoutState
TimeoutPending -> forall (m :: * -> *) a. MonadSTM m => TVar m a -> a -> STM m ()
writeTVar TVar s TimeoutState
var TimeoutState
TimeoutFired
TimeoutState
TimeoutFired -> forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"MonadTimer(Sim): invariant violation"
TimeoutState
TimeoutCancelled -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
timeoutAction (TimerRegisterDelay TVar s Bool
var) = forall (m :: * -> *) a. MonadSTM m => TVar m a -> a -> STM m ()
writeTVar TVar s Bool
var Bool
True
timeoutAction (TimerThreadDelay IOSimThreadId
_ TimeoutId
_) = forall (m :: * -> *) a. Monad m => a -> m a
return ()
timeoutAction (TimerTimeout IOSimThreadId
_ TimeoutId
_ TMVar (IOSim s) IOSimThreadId
_) = forall (m :: * -> *) a. Monad m => a -> m a
return ()
unblockThreads :: forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads :: forall s a.
Bool
-> VectorClock
-> [IOSimThreadId]
-> SimState s a
-> ([IOSimThreadId], SimState s a)
unblockThreads !Bool
onlySTM VectorClock
vClock [IOSimThreadId]
wakeup simstate :: SimState s a
simstate@SimState {RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads} =
( [IOSimThreadId]
unblockedIds
, SimState s a
simstate { runqueue :: RunQueue
runqueue = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall s a. Thread s a -> RunQueue -> RunQueue
insertThread RunQueue
runqueue [Thread s a]
unblocked,
threads :: Map IOSimThreadId (Thread s a)
threads = Map IOSimThreadId (Thread s a)
threads'
})
where
unblocked :: [Thread s a]
!unblocked :: [Thread s a]
unblocked = [ Thread s a
thread
| IOSimThreadId
tid <- [IOSimThreadId]
wakeup
, Thread s a
thread <-
case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IOSimThreadId
tid Map IOSimThreadId (Thread s a)
threads of
Just Thread { threadStatus :: forall s a. Thread s a -> ThreadStatus
threadStatus = ThreadStatus
ThreadRunning }
-> [ ]
Just t :: Thread s a
t@Thread { threadStatus :: forall s a. Thread s a -> ThreadStatus
threadStatus = ThreadBlocked BlockedReason
BlockedOnSTM }
-> [Thread s a
t]
Just t :: Thread s a
t@Thread { threadStatus :: forall s a. Thread s a -> ThreadStatus
threadStatus = ThreadBlocked BlockedReason
_ }
| Bool
onlySTM
-> [ ]
| Bool
otherwise
-> [Thread s a
t]
Just Thread { threadStatus :: forall s a. Thread s a -> ThreadStatus
threadStatus = ThreadStatus
ThreadDone } -> [ ]
Maybe (Thread s a)
Nothing -> [ ]
]
unblockedIds :: [IOSimThreadId]
!unblockedIds :: [IOSimThreadId]
unblockedIds = forall a b. (a -> b) -> [a] -> [b]
map forall s a. Thread s a -> IOSimThreadId
threadId [Thread s a]
unblocked
!threads' :: Map IOSimThreadId (Thread s a)
threads' = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl'
(forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust
(\Thread s a
t -> Thread s a
t { threadStatus :: ThreadStatus
threadStatus = ThreadStatus
ThreadRunning,
threadVClock :: VectorClock
threadVClock = VectorClock
vClock VectorClock -> VectorClock -> VectorClock
`leastUpperBoundVClock` forall s a. Thread s a -> VectorClock
threadVClock Thread s a
t })))
Map IOSimThreadId (Thread s a)
threads [IOSimThreadId]
unblockedIds
forkTimeoutInterruptThreads :: forall s a.
[(IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)]
-> SimState s a
-> ST s (SimState s a)
forkTimeoutInterruptThreads :: forall s a.
[(IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)]
-> SimState s a -> ST s (SimState s a)
forkTimeoutInterruptThreads [(IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)]
timeoutExpired SimState s a
simState =
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM (\st :: SimState s a
st@SimState{ RunQueue
runqueue :: RunQueue
runqueue :: forall s a. SimState s a -> RunQueue
runqueue, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads }
(Thread s a
t, TMVar TVar (IOSim s) (Maybe IOSimThreadId)
lock)
-> do
Maybe IOSimThreadId
v <- forall s a. TVar s a -> ST s a
execReadTVar TVar (IOSim s) (Maybe IOSimThreadId)
lock
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Maybe IOSimThreadId
v of
Maybe IOSimThreadId
Nothing -> SimState s a
st { runqueue :: RunQueue
runqueue = forall s a. Thread s a -> RunQueue -> RunQueue
insertThread Thread s a
t RunQueue
runqueue,
threads :: Map IOSimThreadId (Thread s a)
threads = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
t) Thread s a
t Map IOSimThreadId (Thread s a)
threads
}
Just IOSimThreadId
_ -> SimState s a
st
)
SimState s a
simState'
[(Thread s a, TMVar (IOSim s) IOSimThreadId)]
throwToThread
where
throwToThread :: [(Thread s a, TMVar (IOSim s) IOSimThreadId)]
(SimState s a
simState', [(Thread s a, TMVar (IOSim s) IOSimThreadId)]
[(Thread s a, TMVarDefault (IOSim s) IOSimThreadId)]
throwToThread) = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
List.mapAccumR SimState s a
-> (IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)
-> (SimState s a, (Thread s a, TMVar (IOSim s) IOSimThreadId))
fn SimState s a
simState [(IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)]
timeoutExpired
where
fn :: SimState s a
-> (IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)
-> (SimState s a, (Thread s a, TMVar (IOSim s) IOSimThreadId))
fn :: SimState s a
-> (IOSimThreadId, TimeoutId, TMVar (IOSim s) IOSimThreadId)
-> (SimState s a, (Thread s a, TMVar (IOSim s) IOSimThreadId))
fn state :: SimState s a
state@SimState { Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads } (IOSimThreadId
tid, TimeoutId
tmid, TMVar (IOSim s) IOSimThreadId
lock) =
let t :: Thread s a
t = case IOSimThreadId
tid forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map IOSimThreadId (Thread s a)
threads of
Just Thread s a
t' -> Thread s a
t'
Maybe (Thread s a)
Nothing -> forall a. (?callStack::CallStack) => ThreadLabel -> a
error (ThreadLabel
"IOSimPOR: internal error: unknown thread " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> ThreadLabel
show IOSimThreadId
tid)
nextId :: Int
nextId = forall s a. Thread s a -> Int
threadNextTId Thread s a
t
tid' :: IOSimThreadId
tid' = IOSimThreadId -> Int -> IOSimThreadId
childThreadId IOSimThreadId
tid Int
nextId
in ( SimState s a
state { threads :: Map IOSimThreadId (Thread s a)
threads = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert IOSimThreadId
tid Thread s a
t { threadNextTId :: Int
threadNextTId = forall a. Enum a => a -> a
succ Int
nextId } Map IOSimThreadId (Thread s a)
threads }
, ( Thread { threadId :: IOSimThreadId
threadId = IOSimThreadId
tid',
threadControl :: ThreadControl s a
threadControl =
forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl
(forall s a. IOSim s a -> SimA s a
runIOSim forall a b. (a -> b) -> a -> b
$ do
IOSimThreadId
mtid <- forall (m :: * -> *). MonadThread m => m (ThreadId m)
myThreadId
Bool
v2 <- forall (m :: * -> *) a.
(MonadSTM m, ?callStack::CallStack) =>
STM m a -> m a
atomically forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadSTM m => TMVar m a -> a -> STM m Bool
tryPutTMVar TMVar (IOSim s) IOSimThreadId
lock IOSimThreadId
mtid
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
v2 forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) e.
(MonadFork m, Exception e) =>
ThreadId m -> e -> m ()
throwTo IOSimThreadId
tid (forall e. Exception e => e -> SomeException
toException (TimeoutId -> TimeoutException
TimeoutException TimeoutId
tmid)))
forall s a. ControlStack s () a
ForkFrame,
threadStatus :: ThreadStatus
threadStatus = ThreadStatus
ThreadRunning,
threadMasking :: MaskingState
threadMasking = MaskingState
Unmasked,
threadThrowTo :: [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = [],
threadClockId :: ClockId
threadClockId = forall s a. Thread s a -> ClockId
threadClockId Thread s a
t,
threadLabel :: Maybe ThreadLabel
threadLabel = forall a. a -> Maybe a
Just ThreadLabel
"timeout-forked-thread",
threadNextTId :: Int
threadNextTId = Int
1,
threadStep :: Int
threadStep = Int
0,
threadVClock :: VectorClock
threadVClock = IOSimThreadId -> Int -> VectorClock -> VectorClock
insertVClock IOSimThreadId
tid' Int
0
forall a b. (a -> b) -> a -> b
$ forall s a. Thread s a -> VectorClock
threadVClock Thread s a
t,
threadEffect :: Effect
threadEffect = forall a. Monoid a => a
mempty,
threadRacy :: Bool
threadRacy = forall s a. Thread s a -> Bool
threadRacy Thread s a
t
}
, TMVar (IOSim s) IOSimThreadId
lock
)
)
unwindControlStack :: forall s a.
SomeException
-> Thread s a
-> Timeouts s
-> ( Either Bool (Thread s a)
, Timeouts s
)
unwindControlStack :: forall s a.
SomeException
-> Thread s a
-> Timeouts s
-> (Either Bool (Thread s a), Timeouts s)
unwindControlStack SomeException
e Thread s a
thread = \Timeouts s
timeouts ->
case forall s a. Thread s a -> ThreadControl s a
threadControl Thread s a
thread of
ThreadControl SimA s b
_ ControlStack s b a
ctl -> forall s' c.
MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind (forall s a. Thread s a -> MaskingState
threadMasking Thread s a
thread) ControlStack s b a
ctl Timeouts s
timeouts
where
unwind :: forall s' c. MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind :: forall s' c.
MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind MaskingState
_ ControlStack s' c a
MainFrame Timeouts s
timers = (forall a b. a -> Either a b
Left Bool
True, Timeouts s
timers)
unwind MaskingState
_ ControlStack s' c a
ForkFrame Timeouts s
timers = (forall a b. a -> Either a b
Left Bool
False, Timeouts s
timers)
unwind MaskingState
_ (MaskFrame c -> SimA s' c
_k MaskingState
maskst' ControlStack s' c a
ctl) Timeouts s
timers = forall s' c.
MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind MaskingState
maskst' ControlStack s' c a
ctl Timeouts s
timers
unwind MaskingState
maskst (CatchFrame e -> SimA s' c
handler c -> SimA s' c
k ControlStack s' c a
ctl) Timeouts s
timers =
case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Maybe e
Nothing -> forall s' c.
MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind MaskingState
maskst ControlStack s' c a
ctl Timeouts s
timers
Just e
e' -> ( forall a b. b -> Either a b
Right Thread s a
thread {
threadControl :: ThreadControl s' a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (e -> SimA s' c
handler e
e')
(forall b s a a.
(b -> SimA s a)
-> MaskingState -> ControlStack s a a -> ControlStack s b a
MaskFrame c -> SimA s' c
k MaskingState
maskst ControlStack s' c a
ctl),
threadMasking :: MaskingState
threadMasking = MaskingState -> MaskingState
atLeastInterruptibleMask MaskingState
maskst
}
, Timeouts s
timers
)
unwind MaskingState
maskst (TimeoutFrame TimeoutId
tmid TMVar (IOSim s') IOSimThreadId
isLockedRef Maybe c -> SimA s' c
k ControlStack s' c a
ctl) Timeouts s
timers =
case forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just (TimeoutException TimeoutId
tmid') | TimeoutId
tmid forall a. Eq a => a -> a -> Bool
== TimeoutId
tmid' ->
(forall a b. b -> Either a b
Right Thread s a
thread { threadControl :: ThreadControl s' a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (Maybe c -> SimA s' c
k forall a. Maybe a
Nothing) ControlStack s' c a
ctl }, Timeouts s
timers')
Maybe TimeoutException
_ -> forall s' c.
MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind MaskingState
maskst ControlStack s' c a
ctl Timeouts s
timers'
where
timers' :: Timeouts s
timers' = forall k p v. (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.delete TimeoutId
tmid Timeouts s
timers
unwind MaskingState
maskst (DelayFrame TimeoutId
tmid SimA s' c
_k ControlStack s' c a
ctl) Timeouts s
timers =
forall s' c.
MaskingState
-> ControlStack s' c a
-> Timeouts s
-> (Either Bool (Thread s' a), Timeouts s)
unwind MaskingState
maskst ControlStack s' c a
ctl Timeouts s
timers'
where
timers' :: Timeouts s
timers' = forall k p v. (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
PSQ.delete TimeoutId
tmid Timeouts s
timers
atLeastInterruptibleMask :: MaskingState -> MaskingState
atLeastInterruptibleMask :: MaskingState -> MaskingState
atLeastInterruptibleMask MaskingState
Unmasked = MaskingState
MaskedInterruptible
atLeastInterruptibleMask MaskingState
ms = MaskingState
ms
removeMinimums :: (Ord k, Ord p)
=> OrdPSQ k p a
-> Maybe ([k], p, [a], OrdPSQ k p a)
removeMinimums :: forall k p a.
(Ord k, Ord p) =>
OrdPSQ k p a -> Maybe ([k], p, [a], OrdPSQ k p a)
removeMinimums = \OrdPSQ k p a
psq ->
case forall k p v.
(Ord k, Ord p) =>
OrdPSQ k p v -> Maybe (k, p, v, OrdPSQ k p v)
PSQ.minView OrdPSQ k p a
psq of
Maybe (k, p, a, OrdPSQ k p a)
Nothing -> forall a. Maybe a
Nothing
Just (k
k, p
p, a
x, OrdPSQ k p a
psq') -> forall a. a -> Maybe a
Just (forall {a} {b} {a}.
(Ord a, Ord b) =>
[a] -> b -> [a] -> OrdPSQ a b a -> ([a], b, [a], OrdPSQ a b a)
collectAll [k
k] p
p [a
x] OrdPSQ k p a
psq')
where
collectAll :: [a] -> b -> [a] -> OrdPSQ a b a -> ([a], b, [a], OrdPSQ a b a)
collectAll [a]
ks b
p [a]
xs OrdPSQ a b a
psq =
case forall k p v.
(Ord k, Ord p) =>
OrdPSQ k p v -> Maybe (k, p, v, OrdPSQ k p v)
PSQ.minView OrdPSQ a b a
psq of
Just (a
k, b
p', a
x, OrdPSQ a b a
psq')
| b
p forall a. Eq a => a -> a -> Bool
== b
p' -> [a] -> b -> [a] -> OrdPSQ a b a -> ([a], b, [a], OrdPSQ a b a)
collectAll (a
kforall a. a -> [a] -> [a]
:[a]
ks) b
p (a
xforall a. a -> [a] -> [a]
:[a]
xs) OrdPSQ a b a
psq'
Maybe (a, b, a, OrdPSQ a b a)
_ -> (forall a. [a] -> [a]
reverse [a]
ks, b
p, forall a. [a] -> [a]
reverse [a]
xs, OrdPSQ a b a
psq)
traceMany :: [(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany :: forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany [] SimTrace a
trace = SimTrace a
trace
traceMany ((Time
time, IOSimThreadId
tid, Int
tstep, Maybe ThreadLabel
tlbl, SimEventType
event):[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
ts) SimTrace a
trace =
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid Int
tstep Maybe ThreadLabel
tlbl SimEventType
event (forall a.
[(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
-> SimTrace a -> SimTrace a
traceMany [(Time, IOSimThreadId, Int, Maybe ThreadLabel, SimEventType)]
ts SimTrace a
trace)
lookupThreadLabel :: IOSimThreadId -> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel :: forall s a.
IOSimThreadId
-> Map IOSimThreadId (Thread s a) -> Maybe ThreadLabel
lookupThreadLabel IOSimThreadId
tid Map IOSimThreadId (Thread s a)
threads = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (forall s a. Thread s a -> Maybe ThreadLabel
threadLabel forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IOSimThreadId
tid Map IOSimThreadId (Thread s a)
threads)
runSimTraceST :: forall s a. IOSim s a -> ST s (SimTrace a)
runSimTraceST :: forall s a. IOSim s a -> ST s (SimTrace a)
runSimTraceST IOSim s a
mainAction = forall s a.
Maybe Int -> ScheduleControl -> IOSim s a -> ST s (SimTrace a)
controlSimTraceST forall a. Maybe a
Nothing ScheduleControl
ControlDefault IOSim s a
mainAction
controlSimTraceST :: Maybe Int -> ScheduleControl -> IOSim s a -> ST s (SimTrace a)
controlSimTraceST :: forall s a.
Maybe Int -> ScheduleControl -> IOSim s a -> ST s (SimTrace a)
controlSimTraceST Maybe Int
limit ScheduleControl
control IOSim s a
mainAction =
forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace (forall s a. SimState s a -> Time
curTime forall s a. SimState s a
initialState)
(forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
mainThread)
Int
0
(forall s a. Thread s a -> Maybe ThreadLabel
threadLabel Thread s a
mainThread)
(ScheduleControl -> SimEventType
EventSimStart ScheduleControl
control)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. Thread s a -> SimState s a -> ST s (SimTrace a)
schedule Thread s a
mainThread forall s a. SimState s a
initialState { control :: ScheduleControl
control = ScheduleControl
control,
control0 :: ScheduleControl
control0 = ScheduleControl
control,
perStepTimeLimit :: Maybe Int
perStepTimeLimit = Maybe Int
limit
}
where
mainThread :: Thread s a
mainThread =
Thread {
threadId :: IOSimThreadId
threadId = [Int] -> IOSimThreadId
ThreadId [],
threadControl :: ThreadControl s a
threadControl = forall s a a. SimA s a -> ControlStack s a a -> ThreadControl s a
ThreadControl (forall s a. IOSim s a -> SimA s a
runIOSim IOSim s a
mainAction) forall s a. ControlStack s a a
MainFrame,
threadStatus :: ThreadStatus
threadStatus = ThreadStatus
ThreadRunning,
threadMasking :: MaskingState
threadMasking = MaskingState
Unmasked,
threadThrowTo :: [(SomeException, Labelled IOSimThreadId, VectorClock)]
threadThrowTo = [],
threadClockId :: ClockId
threadClockId = [Int] -> ClockId
ClockId [],
threadLabel :: Maybe ThreadLabel
threadLabel = forall a. a -> Maybe a
Just ThreadLabel
"main",
threadNextTId :: Int
threadNextTId = Int
1,
threadStep :: Int
threadStep = Int
0,
threadVClock :: VectorClock
threadVClock = IOSimThreadId -> Int -> VectorClock -> VectorClock
insertVClock ([Int] -> IOSimThreadId
ThreadId []) Int
0 VectorClock
bottomVClock,
threadEffect :: Effect
threadEffect = forall a. Monoid a => a
mempty,
threadRacy :: Bool
threadRacy = Bool
False
}
execAtomically :: forall s a c.
Time
-> IOSimThreadId
-> Maybe ThreadLabel
-> TVarId
-> StmA s a
-> (StmTxResult s a -> ST s (SimTrace c))
-> ST s (SimTrace c)
execAtomically :: forall s a c.
Time
-> IOSimThreadId
-> Maybe ThreadLabel
-> TVarId
-> StmA s a
-> (StmTxResult s a -> ST s (SimTrace c))
-> ST s (SimTrace c)
execAtomically Time
time IOSimThreadId
tid Maybe ThreadLabel
tlbl TVarId
nextVid0 StmA s a
action0 StmTxResult s a -> ST s (SimTrace c)
k0 =
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go forall s a. StmStack s a a
AtomicallyFrame forall k a. Map k a
Map.empty forall k a. Map k a
Map.empty [] [] TVarId
nextVid0 StmA s a
action0
where
go :: forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go :: forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go !StmStack s b a
ctl !Map TVarId (SomeTVar s)
read !Map TVarId (SomeTVar s)
written ![SomeTVar s]
writtenSeq ![SomeTVar s]
createdSeq !TVarId
nextVid StmA s b
action = forall a. (?callStack::CallStack) => Bool -> a -> a
assert Bool
localInvariant forall a b. (a -> b) -> a -> b
$
case StmA s b
action of
ReturnStm b
x ->
{-# SCC "execAtomically.go.ReturnStm" #-}
case StmStack s b a
ctl of
StmStack s b a
AtomicallyFrame -> do
![TraceValue]
ds <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> Bool -> ST s TraceValue
traceTVarST TVar s a
tvar Bool
True) [SomeTVar s]
createdSeq
![TraceValue]
ds' <- forall k a. Map k a -> [a]
Map.elems forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
(\(SomeTVar TVar s a
tvar) -> do
TraceValue
tr <- forall s a. TVar s a -> Bool -> ST s TraceValue
traceTVarST TVar s a
tvar Bool
False
!()
_ <- forall s a. TVar s a -> ST s ()
commitTVar TVar s a
tvar
[a]
undos <- forall s a. TVar s a -> ST s [a]
readTVarUndos TVar s a
tvar
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
undos) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return TraceValue
tr
) Map TVarId (SomeTVar s)
written
StmTxResult s a -> ST s (SimTrace c)
k0 forall a b. (a -> b) -> a -> b
$ forall s a.
a
-> [SomeTVar s]
-> [SomeTVar s]
-> [SomeTVar s]
-> [Dynamic]
-> [ThreadLabel]
-> TVarId
-> StmTxResult s a
StmTxCommitted b
x (forall a. [a] -> [a]
reverse [SomeTVar s]
writtenSeq)
(forall k a. Map k a -> [a]
Map.elems Map TVarId (SomeTVar s)
read)
(forall a. [a] -> [a]
reverse [SomeTVar s]
createdSeq)
(forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\TraceValue { Maybe tr
traceDynamic :: Maybe tr
traceDynamic :: ()
traceDynamic }
-> forall a. Typeable a => a -> Dynamic
toDyn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe tr
traceDynamic)
forall a b. (a -> b) -> a -> b
$ [TraceValue]
ds forall a. [a] -> [a] -> [a]
++ [TraceValue]
ds')
(forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe TraceValue -> Maybe ThreadLabel
traceString forall a b. (a -> b) -> a -> b
$ [TraceValue]
ds forall a. [a] -> [a] -> [a]
++ [TraceValue]
ds')
TVarId
nextVid
BranchFrame BranchStmA s b
_b b -> StmA s b
k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl' -> do
!()
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s ()
commitTVar TVar s a
tvar)
(forall k a b. Ord k => Map k a -> Map k b -> Map k a
Map.intersection Map TVarId (SomeTVar s)
written Map TVarId (SomeTVar s)
writtenOuter)
let written' :: Map TVarId (SomeTVar s)
written' = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map TVarId (SomeTVar s)
written Map TVarId (SomeTVar s)
writtenOuter
writtenSeq' :: [SomeTVar s]
writtenSeq' = forall a. (a -> Bool) -> [a] -> [a]
filter (\(SomeTVar TVar s a
tvar) ->
forall s a. TVar s a -> TVarId
tvarId TVar s a
tvar forall k a. Ord k => k -> Map k a -> Bool
`Map.notMember` Map TVarId (SomeTVar s)
writtenOuter)
[SomeTVar s]
writtenSeq
forall a. [a] -> [a] -> [a]
++ [SomeTVar s]
writtenOuterSeq
createdSeq' :: [SomeTVar s]
createdSeq' = [SomeTVar s]
createdSeq forall a. [a] -> [a] -> [a]
++ [SomeTVar s]
createdOuterSeq
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl' Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written' [SomeTVar s]
writtenSeq' [SomeTVar s]
createdSeq' TVarId
nextVid (b -> StmA s b
k b
x)
ThrowStm SomeException
e ->
{-# SCC "execAtomically.go.ThrowStm" #-} do
!()
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s ()
revertTVar TVar s a
tvar) Map TVarId (SomeTVar s)
written
case StmStack s b a
ctl of
StmStack s b a
AtomicallyFrame -> do
StmTxResult s a -> ST s (SimTrace c)
k0 forall a b. (a -> b) -> a -> b
$ forall s a. [SomeTVar s] -> SomeException -> StmTxResult s a
StmTxAborted (forall k a. Map k a -> [a]
Map.elems Map TVarId (SomeTVar s)
read) (forall e. Exception e => e -> SomeException
toException SomeException
e)
BranchFrame (CatchStmA SomeException -> StmA s b
h) b -> StmA s b
k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl' ->
{-# SCC "execAtomically.go.BranchFrame" #-} do
let ctl'' :: StmStack s b a
ctl'' = forall s a a c.
BranchStmA s a
-> (a -> StmA s a)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> StmStack s a c
-> StmStack s a c
BranchFrame forall s a. BranchStmA s a
NoOpStmA b -> StmA s b
k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl'
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl'' Map TVarId (SomeTVar s)
read forall k a. Map k a
Map.empty [] [] TVarId
nextVid (SomeException -> StmA s b
h SomeException
e)
BranchFrame (OrElseStmA StmA s b
_r) b -> StmA s b
_k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl' ->
{-# SCC "execAtomically.go.BranchFrame" #-} do
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl' Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq TVarId
nextVid (forall s a. SomeException -> StmA s a
ThrowStm SomeException
e)
BranchFrame BranchStmA s b
NoOpStmA b -> StmA s b
_k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl' ->
{-# SCC "execAtomically.go.BranchFrame" #-} do
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl' Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq TVarId
nextVid (forall s a. SomeException -> StmA s a
ThrowStm SomeException
e)
CatchStm StmA s a
a SomeException -> StmA s a
h a -> StmA s b
k ->
{-# SCC "execAtomically.go.ThrowStm" #-} do
let ctl' :: StmStack s a a
ctl' = forall s a a c.
BranchStmA s a
-> (a -> StmA s a)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> StmStack s a c
-> StmStack s a c
BranchFrame (forall s a. (SomeException -> StmA s a) -> BranchStmA s a
CatchStmA SomeException -> StmA s a
h) a -> StmA s b
k Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq StmStack s b a
ctl
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s a a
ctl' Map TVarId (SomeTVar s)
read forall k a. Map k a
Map.empty [] [] TVarId
nextVid StmA s a
a
StmA s b
Retry ->
{-# SCC "execAtomically.go.Retry" #-} do
!()
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s ()
revertTVar TVar s a
tvar) Map TVarId (SomeTVar s)
written
case StmStack s b a
ctl of
StmStack s b a
AtomicallyFrame -> do
StmTxResult s a -> ST s (SimTrace c)
k0 forall a b. (a -> b) -> a -> b
$! forall s a. [SomeTVar s] -> StmTxResult s a
StmTxBlocked forall a b. (a -> b) -> a -> b
$! forall k a. Map k a -> [a]
Map.elems Map TVarId (SomeTVar s)
read
BranchFrame (OrElseStmA StmA s b
b) b -> StmA s b
k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl' ->
{-# SCC "execAtomically.go.BranchFrame.OrElseStmA" #-} do
let ctl'' :: StmStack s b a
ctl'' = forall s a a c.
BranchStmA s a
-> (a -> StmA s a)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> StmStack s a c
-> StmStack s a c
BranchFrame forall s a. BranchStmA s a
NoOpStmA b -> StmA s b
k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl'
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl'' Map TVarId (SomeTVar s)
read forall k a. Map k a
Map.empty [] [] TVarId
nextVid StmA s b
b
BranchFrame BranchStmA s b
_ b -> StmA s b
_k Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq StmStack s b a
ctl' ->
{-# SCC "execAtomically.go.BranchFrame" #-} do
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl' Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
writtenOuter [SomeTVar s]
writtenOuterSeq [SomeTVar s]
createdOuterSeq TVarId
nextVid forall s b. StmA s b
Retry
OrElse StmA s a
a StmA s a
b a -> StmA s b
k ->
{-# SCC "execAtomically.go.OrElse" #-} do
let ctl' :: StmStack s a a
ctl' = forall s a a c.
BranchStmA s a
-> (a -> StmA s a)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> StmStack s a c
-> StmStack s a c
BranchFrame (forall s a. StmA s a -> BranchStmA s a
OrElseStmA StmA s a
b) a -> StmA s b
k Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq StmStack s b a
ctl
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s a a
ctl' Map TVarId (SomeTVar s)
read forall k a. Map k a
Map.empty [] [] TVarId
nextVid StmA s a
a
NewTVar !Maybe ThreadLabel
mbLabel x
x TVar s x -> StmA s b
k ->
{-# SCC "execAtomically.go.NewTVar" #-} do
!TVar s x
v <- forall a s. TVarId -> Maybe ThreadLabel -> a -> ST s (TVar s a)
execNewTVar TVarId
nextVid Maybe ThreadLabel
mbLabel x
x
let written' :: Map TVarId (SomeTVar s)
written' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall s a. TVar s a -> TVarId
tvarId TVar s x
v) (forall s a. TVar s a -> SomeTVar s
SomeTVar TVar s x
v) Map TVarId (SomeTVar s)
written
!()
_ <- forall s a. TVar s a -> ST s ()
saveTVar TVar s x
v
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written' [SomeTVar s]
writtenSeq (forall s a. TVar s a -> SomeTVar s
SomeTVar TVar s x
v forall a. a -> [a] -> [a]
: [SomeTVar s]
createdSeq) (forall a. Enum a => a -> a
succ TVarId
nextVid) (TVar s x -> StmA s b
k TVar s x
v)
LabelTVar !ThreadLabel
label TVar s a
tvar StmA s b
k ->
{-# SCC "execAtomically.go.LabelTVar" #-} do
!()
_ <- forall s a. STRef s a -> a -> ST s ()
writeSTRef (forall s a. TVar s a -> STRef s (Maybe ThreadLabel)
tvarLabel TVar s a
tvar) forall a b. (a -> b) -> a -> b
$! (forall a. a -> Maybe a
Just ThreadLabel
label)
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k
TraceTVar TVar s a
tvar Maybe a -> a -> ST s TraceValue
f StmA s b
k ->
{-# SCC "execAtomically.go.TraceTVar" #-} do
!()
_ <- forall s a. STRef s a -> a -> ST s ()
writeSTRef (forall s a.
TVar s a -> STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace TVar s a
tvar) (forall a. a -> Maybe a
Just Maybe a -> a -> ST s TraceValue
f)
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k
ReadTVar TVar s a
v a -> StmA s b
k
| forall s a. TVar s a -> TVarId
tvarId TVar s a
v forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map TVarId (SomeTVar s)
read ->
{-# SCC "execAtomically.go.ReadTVar" #-} do
a
x <- forall s a. TVar s a -> ST s a
execReadTVar TVar s a
v
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid (a -> StmA s b
k a
x)
| Bool
otherwise ->
{-# SCC "execAtomically.go.ReadTVar" #-} do
a
x <- forall s a. TVar s a -> ST s a
execReadTVar TVar s a
v
let read' :: Map TVarId (SomeTVar s)
read' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall s a. TVar s a -> TVarId
tvarId TVar s a
v) (forall s a. TVar s a -> SomeTVar s
SomeTVar TVar s a
v) Map TVarId (SomeTVar s)
read
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read' Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid (a -> StmA s b
k a
x)
WriteTVar TVar s a
v a
x StmA s b
k
| forall s a. TVar s a -> TVarId
tvarId TVar s a
v forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map TVarId (SomeTVar s)
written ->
{-# SCC "execAtomically.go.WriteTVar" #-} do
!()
_ <- forall s a. TVar s a -> a -> ST s ()
execWriteTVar TVar s a
v a
x
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k
| Bool
otherwise ->
{-# SCC "execAtomically.go.WriteTVar" #-} do
!()
_ <- forall s a. TVar s a -> ST s ()
saveTVar TVar s a
v
!()
_ <- forall s a. TVar s a -> a -> ST s ()
execWriteTVar TVar s a
v a
x
let written' :: Map TVarId (SomeTVar s)
written' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall s a. TVar s a -> TVarId
tvarId TVar s a
v) (forall s a. TVar s a -> SomeTVar s
SomeTVar TVar s a
v) Map TVarId (SomeTVar s)
written
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written' (forall s a. TVar s a -> SomeTVar s
SomeTVar TVar s a
v forall a. a -> [a] -> [a]
: [SomeTVar s]
writtenSeq) [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k
SayStm ThreadLabel
msg StmA s b
k ->
{-# SCC "execAtomically.go.SayStm" #-} do
SimTrace c
trace <- forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid (-Int
1) Maybe ThreadLabel
tlbl (ThreadLabel -> SimEventType
EventSay ThreadLabel
msg) SimTrace c
trace
OutputStm Dynamic
x StmA s b
k ->
{-# SCC "execAtomically.go.OutputStm" #-} do
SimTrace c
trace <- forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
Time
-> IOSimThreadId
-> Int
-> Maybe ThreadLabel
-> SimEventType
-> SimTrace a
-> SimTrace a
SimPORTrace Time
time IOSimThreadId
tid (-Int
1) Maybe ThreadLabel
tlbl (Dynamic -> SimEventType
EventLog Dynamic
x) SimTrace c
trace
LiftSTStm ST s a
st a -> StmA s b
k ->
{-# SCC "schedule.LiftSTStm" #-} do
a
x <- forall s a. ST s a -> ST s a
strictToLazyST ST s a
st
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid (a -> StmA s b
k a
x)
FixStm x -> STM s x
f x -> StmA s b
k ->
{-# SCC "execAtomically.go.FixStm" #-} do
STRef s x
r <- forall a s. a -> ST s (STRef s a)
newSTRef (forall a e. Exception e => e -> a
throw NonTermination
NonTermination)
x
x <- forall s a. ST s a -> ST s a
unsafeInterleaveST forall a b. (a -> b) -> a -> b
$ forall s a. STRef s a -> ST s a
readSTRef STRef s x
r
let k' :: StmA s b
k' = forall s a. STM s a -> forall r. (a -> StmA s r) -> StmA s r
unSTM (x -> STM s x
f x
x) forall a b. (a -> b) -> a -> b
$ \x
x' ->
forall s a b. ST s a -> (a -> StmA s b) -> StmA s b
LiftSTStm (forall s a. ST s a -> ST s a
lazyToStrictST (forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s x
r x
x')) (\() -> x -> StmA s b
k x
x')
forall b.
StmStack s b a
-> Map TVarId (SomeTVar s)
-> Map TVarId (SomeTVar s)
-> [SomeTVar s]
-> [SomeTVar s]
-> TVarId
-> StmA s b
-> ST s (SimTrace c)
go StmStack s b a
ctl Map TVarId (SomeTVar s)
read Map TVarId (SomeTVar s)
written [SomeTVar s]
writtenSeq [SomeTVar s]
createdSeq TVarId
nextVid StmA s b
k'
where
localInvariant :: Bool
localInvariant =
forall k a. Map k a -> Set k
Map.keysSet Map TVarId (SomeTVar s)
written
forall a. Eq a => a -> a -> Bool
== forall a. Ord a => [a] -> Set a
Set.fromList ([ forall s a. TVar s a -> TVarId
tvarId TVar s a
tvar | SomeTVar TVar s a
tvar <- [SomeTVar s]
writtenSeq ]
forall a. [a] -> [a] -> [a]
++ [ forall s a. TVar s a -> TVarId
tvarId TVar s a
tvar | SomeTVar TVar s a
tvar <- [SomeTVar s]
createdSeq ])
execAtomically' :: StmA s () -> ST s [SomeTVar s]
execAtomically' :: forall s. StmA s () -> ST s [SomeTVar s]
execAtomically' = forall s. Map TVarId (SomeTVar s) -> StmA s () -> ST s [SomeTVar s]
go forall k a. Map k a
Map.empty
where
go :: Map TVarId (SomeTVar s)
-> StmA s ()
-> ST s [SomeTVar s]
go :: forall s. Map TVarId (SomeTVar s) -> StmA s () -> ST s [SomeTVar s]
go !Map TVarId (SomeTVar s)
written StmA s ()
action = case StmA s ()
action of
ReturnStm () -> do
!()
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\(SomeTVar TVar s a
tvar) -> forall s a. TVar s a -> ST s ()
commitTVar TVar s a
tvar) Map TVarId (SomeTVar s)
written
forall (m :: * -> *) a. Monad m => a -> m a
return (forall k a. Map k a -> [a]
Map.elems Map TVarId (SomeTVar s)
written)
ReadTVar TVar s a
v a -> StmA s ()
k -> do
a
x <- forall s a. TVar s a -> ST s a
execReadTVar TVar s a
v
forall s. Map TVarId (SomeTVar s) -> StmA s () -> ST s [SomeTVar s]
go Map TVarId (SomeTVar s)
written (a -> StmA s ()
k a
x)
WriteTVar TVar s a
v a
x StmA s ()
k
| forall s a. TVar s a -> TVarId
tvarId TVar s a
v forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map TVarId (SomeTVar s)
written -> do
!()
_ <- forall s a. TVar s a -> a -> ST s ()
execWriteTVar TVar s a
v a
x
forall s. Map TVarId (SomeTVar s) -> StmA s () -> ST s [SomeTVar s]
go Map TVarId (SomeTVar s)
written StmA s ()
k
| Bool
otherwise -> do
!()
_ <- forall s a. TVar s a -> ST s ()
saveTVar TVar s a
v
!()
_ <- forall s a. TVar s a -> a -> ST s ()
execWriteTVar TVar s a
v a
x
let written' :: Map TVarId (SomeTVar s)
written' = forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (forall s a. TVar s a -> TVarId
tvarId TVar s a
v) (forall s a. TVar s a -> SomeTVar s
SomeTVar TVar s a
v) Map TVarId (SomeTVar s)
written
forall s. Map TVarId (SomeTVar s) -> StmA s () -> ST s [SomeTVar s]
go Map TVarId (SomeTVar s)
written' StmA s ()
k
StmA s ()
_ -> forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"execAtomically': only for special case of reads and writes"
execNewTVar :: TVarId -> Maybe String -> a -> ST s (TVar s a)
execNewTVar :: forall a s. TVarId -> Maybe ThreadLabel -> a -> ST s (TVar s a)
execNewTVar TVarId
nextVid !Maybe ThreadLabel
mbLabel a
x = do
STRef s (Maybe ThreadLabel)
tvarLabel <- forall a s. a -> ST s (STRef s a)
newSTRef Maybe ThreadLabel
mbLabel
STRef s a
tvarCurrent <- forall a s. a -> ST s (STRef s a)
newSTRef a
x
STRef s [a]
tvarUndo <- forall a s. a -> ST s (STRef s a)
newSTRef []
STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked <- forall a s. a -> ST s (STRef s a)
newSTRef ([], forall a. Set a
Set.empty)
STRef s VectorClock
tvarVClock <- forall a s. a -> ST s (STRef s a)
newSTRef VectorClock
bottomVClock
STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace <- forall a s. a -> ST s (STRef s a)
newSTRef forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return TVar {tvarId :: TVarId
tvarId = TVarId
nextVid, STRef s (Maybe ThreadLabel)
tvarLabel :: STRef s (Maybe ThreadLabel)
tvarLabel :: STRef s (Maybe ThreadLabel)
tvarLabel,
STRef s a
tvarCurrent :: STRef s a
tvarCurrent :: STRef s a
tvarCurrent, STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo, STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked, STRef s VectorClock
tvarVClock :: STRef s VectorClock
tvarVClock :: STRef s VectorClock
tvarVClock,
STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace :: STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace :: STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace}
execWriteTVar :: TVar s a -> a -> ST s ()
execWriteTVar :: forall s a. TVar s a -> a -> ST s ()
execWriteTVar TVar{STRef s a
tvarCurrent :: STRef s a
tvarCurrent :: forall s a. TVar s a -> STRef s a
tvarCurrent} = forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s a
tvarCurrent
{-# INLINE execWriteTVar #-}
execTryPutTMVar :: TMVar (IOSim s) a -> a -> ST s Bool
execTryPutTMVar :: forall s a. TMVar (IOSim s) a -> a -> ST s Bool
execTryPutTMVar (TMVar TVar (IOSim s) (Maybe a)
var) a
a = do
Maybe a
v <- forall s a. TVar s a -> ST s a
execReadTVar TVar (IOSim s) (Maybe a)
var
case Maybe a
v of
Maybe a
Nothing -> forall s a. TVar s a -> a -> ST s ()
execWriteTVar TVar (IOSim s) (Maybe a)
var (forall a. a -> Maybe a
Just a
a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Just a
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
{-# INLINE execTryPutTMVar #-}
saveTVar :: TVar s a -> ST s ()
saveTVar :: forall s a. TVar s a -> ST s ()
saveTVar TVar{STRef s a
tvarCurrent :: STRef s a
tvarCurrent :: forall s a. TVar s a -> STRef s a
tvarCurrent, STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo :: forall s a. TVar s a -> STRef s [a]
tvarUndo} = do
a
v <- forall s a. STRef s a -> ST s a
readSTRef STRef s a
tvarCurrent
[a]
vs <- forall s a. STRef s a -> ST s a
readSTRef STRef s [a]
tvarUndo
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s [a]
tvarUndo (a
vforall a. a -> [a] -> [a]
:[a]
vs)
revertTVar :: TVar s a -> ST s ()
revertTVar :: forall s a. TVar s a -> ST s ()
revertTVar TVar{STRef s a
tvarCurrent :: STRef s a
tvarCurrent :: forall s a. TVar s a -> STRef s a
tvarCurrent, STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo :: forall s a. TVar s a -> STRef s [a]
tvarUndo} = do
[a]
vs <- forall s a. STRef s a -> ST s a
readSTRef STRef s [a]
tvarUndo
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s a
tvarCurrent (forall a. [a] -> a
head [a]
vs)
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s [a]
tvarUndo (forall a. [a] -> [a]
tail [a]
vs)
{-# INLINE revertTVar #-}
commitTVar :: TVar s a -> ST s ()
commitTVar :: forall s a. TVar s a -> ST s ()
commitTVar TVar{STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo :: forall s a. TVar s a -> STRef s [a]
tvarUndo} = do
[a]
vs <- forall s a. STRef s a -> ST s a
readSTRef STRef s [a]
tvarUndo
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s [a]
tvarUndo (forall a. [a] -> [a]
tail [a]
vs)
{-# INLINE commitTVar #-}
readTVarUndos :: TVar s a -> ST s [a]
readTVarUndos :: forall s a. TVar s a -> ST s [a]
readTVarUndos TVar{STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo :: forall s a. TVar s a -> STRef s [a]
tvarUndo} = forall s a. STRef s a -> ST s a
readSTRef STRef s [a]
tvarUndo
traceTVarST :: TVar s a
-> Bool
-> ST s TraceValue
traceTVarST :: forall s a. TVar s a -> Bool -> ST s TraceValue
traceTVarST TVar{STRef s a
tvarCurrent :: STRef s a
tvarCurrent :: forall s a. TVar s a -> STRef s a
tvarCurrent, STRef s [a]
tvarUndo :: STRef s [a]
tvarUndo :: forall s a. TVar s a -> STRef s [a]
tvarUndo, STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace :: STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace :: forall s a.
TVar s a -> STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace} Bool
new = do
Maybe (Maybe a -> a -> ST s TraceValue)
mf <- forall s a. STRef s a -> ST s a
readSTRef STRef s (Maybe (Maybe a -> a -> ST s TraceValue))
tvarTrace
case Maybe (Maybe a -> a -> ST s TraceValue)
mf of
Maybe (Maybe a -> a -> ST s TraceValue)
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return TraceValue { traceDynamic :: Maybe ()
traceDynamic = (forall a. Maybe a
Nothing :: Maybe ()), traceString :: Maybe ThreadLabel
traceString = forall a. Maybe a
Nothing }
Just Maybe a -> a -> ST s TraceValue
f -> do
[a]
vs <- forall s a. STRef s a -> ST s a
readSTRef STRef s [a]
tvarUndo
a
v <- forall s a. STRef s a -> ST s a
readSTRef STRef s a
tvarCurrent
case (Bool
new, [a]
vs) of
(Bool
True, [a]
_) -> Maybe a -> a -> ST s TraceValue
f forall a. Maybe a
Nothing a
v
(Bool
_, a
_:[a]
_) -> Maybe a -> a -> ST s TraceValue
f (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
last [a]
vs) a
v
(Bool, [a])
_ -> forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"traceTVarST: unexpected tvar state"
leastUpperBoundTVarVClocks :: [SomeTVar s] -> ST s VectorClock
leastUpperBoundTVarVClocks :: forall s. [SomeTVar s] -> ST s VectorClock
leastUpperBoundTVarVClocks [SomeTVar s]
tvars =
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr VectorClock -> VectorClock -> VectorClock
leastUpperBoundVClock VectorClock
bottomVClock forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [forall s a. STRef s a -> ST s a
readSTRef (forall s a. TVar s a -> STRef s VectorClock
tvarVClock TVar s a
r) | SomeTVar TVar s a
r <- [SomeTVar s]
tvars]
readTVarBlockedThreads :: TVar s a -> ST s [IOSimThreadId]
readTVarBlockedThreads :: forall s a. TVar s a -> ST s [IOSimThreadId]
readTVarBlockedThreads TVar{STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: forall s a.
TVar s a -> STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked} = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. STRef s a -> ST s a
readSTRef STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked
blockThreadOnTVar :: IOSimThreadId -> TVar s a -> ST s ()
blockThreadOnTVar :: forall s a. IOSimThreadId -> TVar s a -> ST s ()
blockThreadOnTVar IOSimThreadId
tid TVar{STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: forall s a.
TVar s a -> STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked} = do
([IOSimThreadId]
tids, Set IOSimThreadId
tidsSet) <- forall s a. STRef s a -> ST s a
readSTRef STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IOSimThreadId
tid forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set IOSimThreadId
tidsSet) forall a b. (a -> b) -> a -> b
$ do
let !tids' :: [IOSimThreadId]
tids' = IOSimThreadId
tid forall a. a -> [a] -> [a]
: [IOSimThreadId]
tids
!tidsSet' :: Set IOSimThreadId
tidsSet' = forall a. Ord a => a -> Set a -> Set a
Set.insert IOSimThreadId
tid Set IOSimThreadId
tidsSet
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked ([IOSimThreadId]
tids', Set IOSimThreadId
tidsSet')
unblockAllThreadsFromTVar :: TVar s a -> ST s ()
unblockAllThreadsFromTVar :: forall s a. TVar s a -> ST s ()
unblockAllThreadsFromTVar TVar{STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked :: forall s a.
TVar s a -> STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked} = do
forall s a. STRef s a -> a -> ST s ()
writeSTRef STRef s ([IOSimThreadId], Set IOSimThreadId)
tvarBlocked ([], forall a. Set a
Set.empty)
threadsUnblockedByWrites :: [SomeTVar s]
-> ST s ([IOSimThreadId], Map IOSimThreadId (Set (Labelled TVarId)))
threadsUnblockedByWrites :: forall s.
[SomeTVar s]
-> ST
s ([IOSimThreadId], Map IOSimThreadId (Set (Labelled TVarId)))
threadsUnblockedByWrites [SomeTVar s]
written = do
[(Labelled TVarId, [IOSimThreadId])]
tidss <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
[ (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s a. TVar s a -> ST s (Labelled TVarId)
labelledTVarId TVar s a
tvar forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall s a. TVar s a -> ST s [IOSimThreadId]
readTVarBlockedThreads TVar s a
tvar
| SomeTVar TVar s a
tvar <- [SomeTVar s]
written ]
let wakeup :: [IOSimThreadId]
wakeup = forall a. Ord a => [a] -> [a]
ordNub [ IOSimThreadId
tid | (Labelled TVarId
_vid, [IOSimThreadId]
tids) <- [(Labelled TVarId, [IOSimThreadId])]
tidss, IOSimThreadId
tid <- forall a. [a] -> [a]
reverse [IOSimThreadId]
tids ]
wokeby :: Map IOSimThreadId (Set (Labelled TVarId))
wokeby = forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. Ord a => Set a -> Set a -> Set a
Set.union
[ (IOSimThreadId
tid, forall a. a -> Set a
Set.singleton Labelled TVarId
vid)
| (Labelled TVarId
vid, [IOSimThreadId]
tids) <- [(Labelled TVarId, [IOSimThreadId])]
tidss
, IOSimThreadId
tid <- [IOSimThreadId]
tids ]
forall (m :: * -> *) a. Monad m => a -> m a
return ([IOSimThreadId]
wakeup, Map IOSimThreadId (Set (Labelled TVarId))
wokeby)
ordNub :: Ord a => [a] -> [a]
ordNub :: forall a. Ord a => [a] -> [a]
ordNub = forall {a}. Ord a => Set a -> [a] -> [a]
go forall a. Set a
Set.empty
where
go :: Set a -> [a] -> [a]
go !Set a
_ [] = []
go !Set a
s (a
x:[a]
xs)
| a
x forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
s = Set a -> [a] -> [a]
go Set a
s [a]
xs
| Bool
otherwise = a
x forall a. a -> [a] -> [a]
: Set a -> [a] -> [a]
go (forall a. Ord a => a -> Set a -> Set a
Set.insert a
x Set a
s) [a]
xs
racingSteps :: Step
-> Step
-> Bool
racingSteps :: Step -> Step -> Bool
racingSteps Step
s Step
s' =
IOSimThreadId -> Bool
isRacyThreadId (Step -> IOSimThreadId
stepThreadId Step
s)
Bool -> Bool -> Bool
&& Step -> IOSimThreadId
stepThreadId Step
s forall a. Eq a => a -> a -> Bool
/= Step -> IOSimThreadId
stepThreadId Step
s'
Bool -> Bool -> Bool
&& Bool -> Bool
not (Step -> IOSimThreadId
stepThreadId Step
s' forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Effect -> Set IOSimThreadId
effectWakeup (Step -> Effect
stepEffect Step
s))
Bool -> Bool -> Bool
&& ( Step -> Effect
stepEffect Step
s Effect -> Effect -> Bool
`racingEffects` Step -> Effect
stepEffect Step
s'
Bool -> Bool -> Bool
|| Step -> Step -> Bool
throwsTo Step
s Step
s'
Bool -> Bool -> Bool
|| Step -> Step -> Bool
throwsTo Step
s' Step
s
)
where throwsTo :: Step -> Step -> Bool
throwsTo Step
s1 Step
s2 =
Step -> IOSimThreadId
stepThreadId Step
s2 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Effect -> [IOSimThreadId]
effectThrows (Step -> Effect
stepEffect Step
s1)
Bool -> Bool -> Bool
&& Step -> Effect
stepEffect Step
s2 forall a. Eq a => a -> a -> Bool
/= forall a. Monoid a => a
mempty
currentStep :: Thread s a -> Step
currentStep :: forall s a. Thread s a -> Step
currentStep Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
stepThreadId,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
stepStep,
threadEffect :: forall s a. Thread s a -> Effect
threadEffect = Effect
stepEffect,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
stepVClock
} = Step {Int
VectorClock
IOSimThreadId
Effect
stepVClock :: VectorClock
stepEffect :: Effect
stepStep :: Int
stepThreadId :: IOSimThreadId
stepEffect :: Effect
stepVClock :: VectorClock
stepThreadId :: IOSimThreadId
stepStep :: Int
..}
stepThread :: Thread s a -> (Thread s a, Effect)
stepThread :: forall s a. Thread s a -> (Thread s a, Effect)
stepThread thread :: Thread s a
thread@Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid,
threadStep :: forall s a. Thread s a -> Int
threadStep = Int
tstep,
threadVClock :: forall s a. Thread s a -> VectorClock
threadVClock = VectorClock
vClock } =
( Thread s a
thread { threadStep :: Int
threadStep = Int
tstepforall a. Num a => a -> a -> a
+Int
1,
threadEffect :: Effect
threadEffect = forall a. Monoid a => a
mempty,
threadVClock :: VectorClock
threadVClock = IOSimThreadId -> Int -> VectorClock -> VectorClock
insertVClock IOSimThreadId
tid (Int
tstepforall a. Num a => a -> a -> a
+Int
1) VectorClock
vClock
},
forall s a. Thread s a -> Effect
threadEffect Thread s a
thread
)
updateRaces :: Thread s a -> SimState s a -> Races
updateRaces :: forall s a. Thread s a -> SimState s a -> Races
updateRaces thread :: Thread s a
thread@Thread { threadId :: forall s a. Thread s a -> IOSimThreadId
threadId = IOSimThreadId
tid }
SimState{ ScheduleControl
control :: ScheduleControl
control :: forall s a. SimState s a -> ScheduleControl
control, Map IOSimThreadId (Thread s a)
threads :: Map IOSimThreadId (Thread s a)
threads :: forall s a. SimState s a -> Map IOSimThreadId (Thread s a)
threads, races :: forall s a. SimState s a -> Races
races = races :: Races
races@Races { [StepInfo]
activeRaces :: Races -> [StepInfo]
activeRaces :: [StepInfo]
activeRaces } } =
let
newStep :: Step
newStep@Step{ stepEffect :: Step -> Effect
stepEffect = Effect
newEffect } = forall s a. Thread s a -> Step
currentStep Thread s a
thread
concurrent0 :: Set IOSimThreadId
concurrent0 =
forall k a. Map k a -> Set k
Map.keysSet (forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (\Thread s a
t -> Bool -> Bool
not (forall s a. Thread s a -> Bool
isThreadDone Thread s a
t)
Bool -> Bool -> Bool
&& forall s a. Thread s a -> IOSimThreadId
threadId Thread s a
t forall a. Ord a => a -> Set a -> Bool
`Set.notMember`
Effect -> Set IOSimThreadId
effectForks Effect
newEffect
) Map IOSimThreadId (Thread s a)
threads)
newStepInfo :: Maybe StepInfo
!newStepInfo :: Maybe StepInfo
newStepInfo | IOSimThreadId -> Bool
isNotRacyThreadId IOSimThreadId
tid = forall a. Maybe a
Nothing
| forall a. Set a -> Bool
Set.null Set IOSimThreadId
concurrent = forall a. Maybe a
Nothing
| Bool
isBlocking = forall a. Maybe a
Nothing
| Bool
otherwise =
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! StepInfo { stepInfoStep :: Step
stepInfoStep = Step
newStep,
stepInfoControl :: ScheduleControl
stepInfoControl = ScheduleControl
control,
stepInfoConcurrent :: Set IOSimThreadId
stepInfoConcurrent = Set IOSimThreadId
concurrent,
stepInfoNonDep :: [Step]
stepInfoNonDep = [],
stepInfoRaces :: [Step]
stepInfoRaces = []
}
where
concurrent :: Set IOSimThreadId
concurrent :: Set IOSimThreadId
concurrent = Set IOSimThreadId
concurrent0 forall a. Ord a => Set a -> Set a -> Set a
Set.\\ Effect -> Set IOSimThreadId
effectWakeup Effect
newEffect
isBlocking :: Bool
isBlocking :: Bool
isBlocking = forall s a. Thread s a -> Bool
isThreadBlocked Thread s a
thread Bool -> Bool -> Bool
&& Effect -> Bool
onlyReadEffect Effect
newEffect
updateStepInfo :: StepInfo -> StepInfo
updateStepInfo :: StepInfo -> StepInfo
updateStepInfo stepInfo :: StepInfo
stepInfo@StepInfo { stepInfoStep :: StepInfo -> Step
stepInfoStep = Step
step,
stepInfoConcurrent :: StepInfo -> Set IOSimThreadId
stepInfoConcurrent = Set IOSimThreadId
concurrent,
[Step]
stepInfoNonDep :: [Step]
stepInfoNonDep :: StepInfo -> [Step]
stepInfoNonDep,
[Step]
stepInfoRaces :: [Step]
stepInfoRaces :: StepInfo -> [Step]
stepInfoRaces } =
let !lessConcurrent :: Set IOSimThreadId
lessConcurrent = Set IOSimThreadId
concurrent forall a. Ord a => Set a -> Set a -> Set a
Set.\\ Effect -> Set IOSimThreadId
effectWakeup Effect
newEffect in
if IOSimThreadId
tid forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Set IOSimThreadId
concurrent
then StepInfo
stepInfo { stepInfoConcurrent :: Set IOSimThreadId
stepInfoConcurrent = Set IOSimThreadId
lessConcurrent }
else let theseStepsRace :: Bool
theseStepsRace = Step
step Step -> Step -> Bool
`racingSteps` Step
newStep
happensBefore :: Bool
happensBefore = Step
step Step -> Step -> Bool
`happensBeforeStep` Step
newStep
afterRacingStep :: Bool
afterRacingStep = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Step -> Step -> Bool
`happensBeforeStep` Step
newStep) [Step]
stepInfoRaces
!concurrent' :: Set IOSimThreadId
concurrent'
| Bool
happensBefore = forall a. Ord a => a -> Set a -> Set a
Set.delete IOSimThreadId
tid Set IOSimThreadId
lessConcurrent
| Bool
theseStepsRace = forall a. Ord a => a -> Set a -> Set a
Set.delete IOSimThreadId
tid Set IOSimThreadId
concurrent
| Bool
afterRacingStep = forall a. Ord a => a -> Set a -> Set a
Set.delete IOSimThreadId
tid Set IOSimThreadId
concurrent
| Bool
otherwise = Set IOSimThreadId
concurrent
!stepInfoNonDep' :: [Step]
stepInfoNonDep'
| Bool
happensBefore = [Step]
stepInfoNonDep
| Bool
otherwise = Step
newStep forall a. a -> [a] -> [a]
: [Step]
stepInfoNonDep
!stepInfoRaces' :: [Step]
stepInfoRaces'
| Bool
theseStepsRace Bool -> Bool -> Bool
&& ScheduleControl -> Bool
isDefaultSchedule ScheduleControl
control
= Step
newStep forall a. a -> [a] -> [a]
: [Step]
stepInfoRaces
| Bool
otherwise = [Step]
stepInfoRaces
in StepInfo
stepInfo { stepInfoConcurrent :: Set IOSimThreadId
stepInfoConcurrent = Effect -> Set IOSimThreadId
effectForks Effect
newEffect
forall a. Ord a => Set a -> Set a -> Set a
`Set.union` Set IOSimThreadId
concurrent',
stepInfoNonDep :: [Step]
stepInfoNonDep = [Step]
stepInfoNonDep',
stepInfoRaces :: [Step]
stepInfoRaces = [Step]
stepInfoRaces'
}
activeRaces' :: [StepInfo]
!activeRaces' :: [StepInfo]
activeRaces' =
case Maybe StepInfo
newStepInfo of
Maybe StepInfo
Nothing -> StepInfo -> StepInfo
updateStepInfo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [StepInfo]
activeRaces
Just StepInfo
si -> StepInfo
si forall a. a -> [a] -> [a]
: (StepInfo -> StepInfo
updateStepInfo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [StepInfo]
activeRaces)
in Races -> Races
normalizeRaces Races
races { activeRaces :: [StepInfo]
activeRaces = [StepInfo]
activeRaces' }
normalizeRaces :: Races -> Races
normalizeRaces :: Races -> Races
normalizeRaces Races{ [StepInfo]
activeRaces :: [StepInfo]
activeRaces :: Races -> [StepInfo]
activeRaces, [StepInfo]
completeRaces :: Races -> [StepInfo]
completeRaces :: [StepInfo]
completeRaces } =
let !activeRaces' :: [StepInfo]
activeRaces' = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. StepInfo -> Set IOSimThreadId
stepInfoConcurrent) [StepInfo]
activeRaces
!completeRaces' :: [StepInfo]
completeRaces' = ( forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. StepInfo -> [Step]
stepInfoRaces)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. StepInfo -> Set IOSimThreadId
stepInfoConcurrent)
forall a b. (a -> b) -> a -> b
$ [StepInfo]
activeRaces
)
forall a. [a] -> [a] -> [a]
++ [StepInfo]
completeRaces
in Races{ activeRaces :: [StepInfo]
activeRaces = [StepInfo]
activeRaces', completeRaces :: [StepInfo]
completeRaces = [StepInfo]
completeRaces' }
threadTerminatesRaces :: IOSimThreadId -> Races -> Races
threadTerminatesRaces :: IOSimThreadId -> Races -> Races
threadTerminatesRaces IOSimThreadId
tid races :: Races
races@Races{ [StepInfo]
activeRaces :: [StepInfo]
activeRaces :: Races -> [StepInfo]
activeRaces } =
let activeRaces' :: [StepInfo]
activeRaces' = [ StepInfo
s{stepInfoConcurrent :: Set IOSimThreadId
stepInfoConcurrent = forall a. Ord a => a -> Set a -> Set a
Set.delete IOSimThreadId
tid Set IOSimThreadId
stepInfoConcurrent}
| s :: StepInfo
s@StepInfo{ Set IOSimThreadId
stepInfoConcurrent :: Set IOSimThreadId
stepInfoConcurrent :: StepInfo -> Set IOSimThreadId
stepInfoConcurrent } <- [StepInfo]
activeRaces ]
in Races -> Races
normalizeRaces forall a b. (a -> b) -> a -> b
$ Races
races{ activeRaces :: [StepInfo]
activeRaces = [StepInfo]
activeRaces' }
quiescentRaces :: Races -> Races
quiescentRaces :: Races -> Races
quiescentRaces Races{ [StepInfo]
activeRaces :: [StepInfo]
activeRaces :: Races -> [StepInfo]
activeRaces, [StepInfo]
completeRaces :: [StepInfo]
completeRaces :: Races -> [StepInfo]
completeRaces } =
Races{ activeRaces :: [StepInfo]
activeRaces = [],
completeRaces :: [StepInfo]
completeRaces = [ StepInfo
s{stepInfoConcurrent :: Set IOSimThreadId
stepInfoConcurrent = forall a. Set a
Set.empty}
| StepInfo
s <- [StepInfo]
activeRaces
, Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null (StepInfo -> [Step]
stepInfoRaces StepInfo
s))
] forall a. [a] -> [a] -> [a]
++ [StepInfo]
completeRaces }
controlTargets :: StepId -> ScheduleControl -> Bool
controlTargets :: StepId -> ScheduleControl -> Bool
controlTargets StepId
stepId
(ControlAwait (ScheduleMod{ StepId
scheduleModTarget :: ScheduleMod -> StepId
scheduleModTarget :: StepId
scheduleModTarget }:[ScheduleMod]
_)) =
StepId
stepId forall a. Eq a => a -> a -> Bool
== StepId
scheduleModTarget
controlTargets StepId
_stepId ScheduleControl
_ = Bool
False
followControl :: ScheduleControl -> ScheduleControl
followControl :: ScheduleControl -> ScheduleControl
followControl (ControlAwait (ScheduleMod { [StepId]
scheduleModInsertion :: ScheduleMod -> [StepId]
scheduleModInsertion :: [StepId]
scheduleModInsertion } : [ScheduleMod]
mods)) =
[StepId] -> [ScheduleMod] -> ScheduleControl
ControlFollow [StepId]
scheduleModInsertion [ScheduleMod]
mods
followControl (ControlAwait []) = forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"Impossible: followControl (ControlAwait [])"
followControl ControlDefault{} = forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"Impossible: followControl ControlDefault{}"
followControl ControlFollow{} = forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"Impossible: followControl ControlFollow{}"
controlFollows :: StepId -> ScheduleControl -> Bool
controlFollows :: StepId -> ScheduleControl -> Bool
controlFollows StepId
_stepId ScheduleControl
ControlDefault = Bool
True
controlFollows StepId
_stepId (ControlFollow [] [ScheduleMod]
_) = Bool
True
controlFollows StepId
stepId (ControlFollow (StepId
stepId':[StepId]
_) [ScheduleMod]
_) = StepId
stepId forall a. Eq a => a -> a -> Bool
== StepId
stepId'
controlFollows StepId
stepId (ControlAwait (ScheduleMod
smod:[ScheduleMod]
_)) = StepId
stepId forall a. Eq a => a -> a -> Bool
/= ScheduleMod -> StepId
scheduleModTarget ScheduleMod
smod
controlFollows StepId
_ (ControlAwait []) = forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"Impossible: controlFollows _ (ControlAwait [])"
advanceControl :: StepId -> ScheduleControl -> ScheduleControl
advanceControl :: StepId -> ScheduleControl -> ScheduleControl
advanceControl (IOSimThreadId
tid,Int
step) control :: ScheduleControl
control@(ControlFollow ((IOSimThreadId
tid',Int
step'):[StepId]
sids') [ScheduleMod]
tgts)
| IOSimThreadId
tid forall a. Eq a => a -> a -> Bool
/= IOSimThreadId
tid' =
ScheduleControl
control
| Int
step forall a. Eq a => a -> a -> Bool
== Int
step' =
[StepId] -> [ScheduleMod] -> ScheduleControl
ControlFollow [StepId]
sids' [ScheduleMod]
tgts
| Bool
otherwise =
forall a. (?callStack::CallStack) => ThreadLabel -> a
error forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ ThreadLabel
"advanceControl ", forall a. Show a => a -> ThreadLabel
show (IOSimThreadId
tid,Int
step)
, ThreadLabel
" cannot follow step ", forall a. Show a => a -> ThreadLabel
show Int
step'
, ThreadLabel
"\n"
]
advanceControl StepId
stepId (ControlFollow [] []) =
ScheduleControl
ControlDefault
advanceControl StepId
stepId (ControlFollow [] [ScheduleMod]
tgts) =
[ScheduleMod] -> ScheduleControl
ControlAwait [ScheduleMod]
tgts
advanceControl StepId
stepId ScheduleControl
control =
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ StepId -> ScheduleControl -> Bool
controlTargets StepId
stepId ScheduleControl
control) forall a b. (a -> b) -> a -> b
$
ScheduleControl
control
stepStepId :: Step -> (IOSimThreadId, Int)
stepStepId :: Step -> StepId
stepStepId Step{ stepThreadId :: Step -> IOSimThreadId
stepThreadId = IOSimThreadId
tid, stepStep :: Step -> Int
stepStep = Int
n } = (IOSimThreadId
tid,Int
n)
stepInfoToScheduleMods :: StepInfo -> [ScheduleMod]
stepInfoToScheduleMods :: StepInfo -> [ScheduleMod]
stepInfoToScheduleMods
StepInfo{ stepInfoStep :: StepInfo -> Step
stepInfoStep = Step
step,
stepInfoControl :: StepInfo -> ScheduleControl
stepInfoControl = ScheduleControl
control,
stepInfoNonDep :: StepInfo -> [Step]
stepInfoNonDep = [Step]
nondep,
stepInfoRaces :: StepInfo -> [Step]
stepInfoRaces = [Step]
races
} =
[ ScheduleMod
{ scheduleModTarget :: StepId
scheduleModTarget = Step -> StepId
stepStepId Step
step
, scheduleModControl :: ScheduleControl
scheduleModControl = ScheduleControl
control
, scheduleModInsertion :: [StepId]
scheduleModInsertion = forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Eq a => a -> a -> Bool
/=Step -> StepId
stepStepId Step
step')
(Step -> StepId
stepStepId forall a b. (a -> b) -> [a] -> [b]
`map` forall a. [a] -> [a]
reverse [Step]
nondep)
forall a. [a] -> [a] -> [a]
++ [Step -> StepId
stepStepId Step
step']
}
| Step
step' <- [Step]
races ]
traceFinalRacesFound :: SimState s a -> SimTrace a -> SimTrace a
traceFinalRacesFound :: forall s a. SimState s a -> SimTrace a -> SimTrace a
traceFinalRacesFound SimState{ control0 :: forall s a. SimState s a -> ScheduleControl
control0 = ScheduleControl
control, Races
races :: Races
races :: forall s a. SimState s a -> Races
races } =
forall a. [ScheduleControl] -> SimTrace a -> SimTrace a
TraceRacesFound [ScheduleControl -> ScheduleMod -> ScheduleControl
extendScheduleControl ScheduleControl
control ScheduleMod
m | ScheduleMod
m <- [ScheduleMod]
scheduleMods]
where
scheduleMods :: [ScheduleMod]
scheduleMods :: [ScheduleMod]
scheduleMods =
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap StepInfo -> [ScheduleMod]
stepInfoToScheduleMods
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Races -> [StepInfo]
completeRaces
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Races -> Races
quiescentRaces
forall a b. (a -> b) -> a -> b
$ Races
races
extendScheduleControl' :: ScheduleControl -> ScheduleMod -> ScheduleControl
extendScheduleControl' :: ScheduleControl -> ScheduleMod -> ScheduleControl
extendScheduleControl' ScheduleControl
ControlDefault ScheduleMod
m = [ScheduleMod] -> ScheduleControl
ControlAwait [ScheduleMod
m]
extendScheduleControl' (ControlAwait [ScheduleMod]
mods) ScheduleMod
m =
case ScheduleMod -> ScheduleControl
scheduleModControl ScheduleMod
m of
ScheduleControl
ControlDefault -> [ScheduleMod] -> ScheduleControl
ControlAwait ([ScheduleMod]
modsforall a. [a] -> [a] -> [a]
++[ScheduleMod
m])
ControlAwait [ScheduleMod]
mods' ->
let common :: Int
common = forall (t :: * -> *) a. Foldable t => t a -> Int
length [ScheduleMod]
mods forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length [ScheduleMod]
mods' in
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
common forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& forall a. Int -> [a] -> [a]
drop Int
common [ScheduleMod]
modsforall a. Eq a => a -> a -> Bool
==[ScheduleMod]
mods') forall a b. (a -> b) -> a -> b
$
[ScheduleMod] -> ScheduleControl
ControlAwait (forall a. Int -> [a] -> [a]
take Int
common [ScheduleMod]
modsforall a. [a] -> [a] -> [a]
++[ScheduleMod
m{ scheduleModControl :: ScheduleControl
scheduleModControl = ScheduleControl
ControlDefault }])
ControlFollow [StepId]
stepIds [ScheduleMod]
mods' ->
let common :: Int
common = forall (t :: * -> *) a. Foldable t => t a -> Int
length [ScheduleMod]
mods forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length [ScheduleMod]
mods' forall a. Num a => a -> a -> a
- Int
1
m' :: ScheduleMod
m' = [ScheduleMod]
mods forall a. [a] -> Int -> a
!! Int
common
isUndo :: Bool
isUndo = ScheduleMod -> StepId
scheduleModTarget ScheduleMod
m' forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ScheduleMod -> [StepId]
scheduleModInsertion ScheduleMod
m
m'' :: ScheduleMod
m'' = ScheduleMod
m'{ scheduleModInsertion :: [StepId]
scheduleModInsertion =
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Eq a => a -> a -> Bool
/=ScheduleMod -> StepId
scheduleModTarget ScheduleMod
m)
(ScheduleMod -> [StepId]
scheduleModInsertion ScheduleMod
m')
forall a. [a] -> [a] -> [a]
++
ScheduleMod -> [StepId]
scheduleModInsertion ScheduleMod
m }
in
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
common forall a. Ord a => a -> a -> Bool
>= Int
0) forall a b. (a -> b) -> a -> b
$
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (forall a. Int -> [a] -> [a]
drop (Int
commonforall a. Num a => a -> a -> a
+Int
1) [ScheduleMod]
mods forall a. Eq a => a -> a -> Bool
== [ScheduleMod]
mods') forall a b. (a -> b) -> a -> b
$
if Bool
isUndo
then [ScheduleMod] -> ScheduleControl
ControlAwait [ScheduleMod]
mods
else [ScheduleMod] -> ScheduleControl
ControlAwait (forall a. Int -> [a] -> [a]
take Int
common [ScheduleMod]
modsforall a. [a] -> [a] -> [a]
++[ScheduleMod
m''])
extendScheduleControl' ControlFollow{} ScheduleMod{} =
forall a. (?callStack::CallStack) => ThreadLabel -> a
error ThreadLabel
"Impossible: extendScheduleControl' ControlFollow{} ScheduleMod{}"
extendScheduleControl :: ScheduleControl -> ScheduleMod -> ScheduleControl
extendScheduleControl :: ScheduleControl -> ScheduleMod -> ScheduleControl
extendScheduleControl ScheduleControl
control ScheduleMod
m =
let control' :: ScheduleControl
control' = ScheduleControl -> ScheduleMod -> ScheduleControl
extendScheduleControl' ScheduleControl
control ScheduleMod
m in
ScheduleControl
control'