Skip to content

Commit 669d6b2

Browse files
MaximilianAlgehedcoot
authored andcommitted
ThreadStatus in IOSim and IOSimPOR
1 parent df25229 commit 669d6b2

File tree

8 files changed

+308
-88
lines changed

8 files changed

+308
-88
lines changed

io-sim/src/Control/Monad/IOSim/CommonTypes.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,5 +80,10 @@ instance Eq (TVar s a) where
8080
data SomeTVar s where
8181
SomeTVar :: !(TVar s a) -> SomeTVar s
8282

83-
data Deschedule = Yield | Interruptable | Blocked | Terminated | Sleep
83+
-- | The reason a thread finished running
84+
data FinishedReason = FinishedNormally
85+
| FinishedDied
86+
deriving (Ord, Eq, Show, Enum, Bounded)
87+
88+
data Deschedule = Yield | Interruptable | Blocked | Terminated FinishedReason | Sleep
8489
deriving Show

io-sim/src/Control/Monad/IOSim/Internal.hs

Lines changed: 40 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
{-# LANGUAGE RankNTypes #-}
1515
{-# LANGUAGE ScopedTypeVariables #-}
1616
{-# LANGUAGE TypeFamilies #-}
17+
{-# LANGUAGE RecordWildCards #-}
1718

1819
{-# OPTIONS_GHC -Wno-orphans #-}
1920
-- incomplete uni patterns in 'schedule' (when interpreting 'StmTxCommitted')
@@ -69,6 +70,7 @@ import Deque.Strict (Deque)
6970
import qualified Deque.Strict as Deque
7071

7172
import GHC.Exts (fromList)
73+
import GHC.Conc (ThreadStatus(..), BlockReason(..))
7274

7375
import Control.Exception (NonTermination (..), assert, throw)
7476
import Control.Monad (join)
@@ -123,14 +125,15 @@ labelledThreads threadMap =
123125
--
124126
data TimerVars s = TimerVars !(TVar s TimeoutState) !(TVar s Bool)
125127

126-
127128
-- | Internal state.
128129
--
129130
data SimState s a = SimState {
130131
runqueue :: !(Deque ThreadId),
131132
-- | All threads other than the currently running thread: both running
132133
-- and blocked threads.
133134
threads :: !(Map ThreadId (Thread s a)),
135+
-- | Keep track of the reason threads finished for 'threadStatus'
136+
finished :: !(Map ThreadId FinishedReason),
134137
-- | current time
135138
curTime :: !Time,
136139
-- | ordered list of timers
@@ -146,6 +149,7 @@ initialState =
146149
SimState {
147150
runqueue = mempty,
148151
threads = Map.empty,
152+
finished = Map.empty,
149153
curTime = Time 0,
150154
timers = PSQ.empty,
151155
clocks = Map.singleton (ClockId []) epoch1970,
@@ -190,6 +194,7 @@ schedule !thread@Thread{
190194
!simstate@SimState {
191195
runqueue,
192196
threads,
197+
finished,
193198
timers,
194199
clocks,
195200
nextVid, nextTmid,
@@ -208,9 +213,9 @@ schedule !thread@Thread{
208213

209214
ForkFrame -> do
210215
-- this thread is done
211-
!trace <- deschedule Terminated thread simstate
216+
!trace <- deschedule (Terminated FinishedNormally) thread simstate
212217
return $ SimTrace time tid tlbl EventThreadFinished
213-
$ SimTrace time tid tlbl (EventDeschedule Terminated)
218+
$ SimTrace time tid tlbl (EventDeschedule $ Terminated FinishedNormally)
214219
$ trace
215220

216221
MaskFrame k maskst' ctl' -> do
@@ -228,7 +233,7 @@ schedule !thread@Thread{
228233
let thread' = thread { threadControl = ThreadControl (k x) ctl' }
229234
schedule thread' simstate
230235

231-
Throw e -> {-# SCC "schedule.Throw" #-}
236+
Throw thrower e -> {-# SCC "schedule.Throw" #-}
232237
case unwindControlStack e thread of
233238
Right thread'@Thread { threadMasking = maskst' } -> do
234239
-- We found a suitable exception handler, continue with that
@@ -247,10 +252,12 @@ schedule !thread@Thread{
247252

248253
| otherwise -> do
249254
-- An unhandled exception in any other thread terminates the thread
250-
!trace <- deschedule Terminated thread simstate
255+
let reason | ThrowSelf <- thrower = FinishedNormally
256+
| otherwise = FinishedDied
257+
!trace <- deschedule (Terminated reason) thread simstate
251258
return $ SimTrace time tid tlbl (EventThrow e)
252259
$ SimTrace time tid tlbl (EventThreadUnhandled e)
253-
$ SimTrace time tid tlbl (EventDeschedule Terminated)
260+
$ SimTrace time tid tlbl (EventDeschedule $ Terminated reason)
254261
$ trace
255262

256263
Catch action' handler k ->
@@ -266,7 +273,7 @@ schedule !thread@Thread{
266273
case mbWHNF of
267274
Left e -> do
268275
-- schedule this thread to immediately raise the exception
269-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
276+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
270277
schedule thread' simstate
271278
Right whnf -> do
272279
-- continue with the resulting WHNF
@@ -466,7 +473,7 @@ schedule !thread@Thread{
466473

467474
StmTxAborted _read e -> do
468475
-- schedule this thread to immediately raise the exception
469-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
476+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
470477
!trace <- schedule thread' simstate
471478
return $ SimTrace time tid tlbl (EventTxAborted Nothing) trace
472479

@@ -495,6 +502,19 @@ schedule !thread@Thread{
495502
threads' = Map.adjust (\t -> t { threadLabel = Just l }) tid' threads
496503
schedule thread' simstate { threads = threads' }
497504

505+
ThreadStatus tid' k ->
506+
{-# SCC "schedule.ThreadStatus" #-} do
507+
let result | Just r <- Map.lookup tid' finished = reasonToStatus r
508+
| Just t <- Map.lookup tid' threads = threadStatus t
509+
| otherwise = error "The impossible happened - tried to loookup thread in state."
510+
reasonToStatus FinishedNormally = ThreadFinished
511+
reasonToStatus FinishedDied = ThreadDied
512+
threadStatus Thread{..} | threadBlocked = ThreadBlocked BlockedOnOther
513+
| otherwise = ThreadRunning
514+
515+
thread' = thread { threadControl = ThreadControl (k result) ctl }
516+
schedule thread' simstate
517+
498518
GetMaskState k ->
499519
{-# SCC "schedule.GetMaskState" #-} do
500520
let thread' = thread { threadControl = ThreadControl (k maskst) ctl }
@@ -519,7 +539,7 @@ schedule !thread@Thread{
519539
{-# SCC "schedule.ThrowTo" #-} do
520540
-- Throw to ourself is equivalent to a synchronous throw,
521541
-- and works irrespective of masking state since it does not block.
522-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl }
542+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl }
523543
trace <- schedule thread' simstate
524544
return (SimTrace time tid tlbl (EventThrowTo e tid) trace)
525545

@@ -549,8 +569,11 @@ schedule !thread@Thread{
549569
-- be resolved if the thread terminates or if it leaves the exception
550570
-- handler (when restoring the masking state would trigger the any
551571
-- new pending async exception).
552-
let adjustTarget t@Thread{ threadControl = ThreadControl _ ctl' } =
553-
t { threadControl = ThreadControl (Throw e) ctl'
572+
let thrower = case threadMasking <$> Map.lookup tid' threads of
573+
Just Unmasked -> ThrowOther
574+
_ -> ThrowSelf
575+
adjustTarget t@Thread{ threadControl = ThreadControl _ ctl' } =
576+
t { threadControl = ThreadControl (Throw thrower e) ctl'
554577
, threadBlocked = False
555578
}
556579
simstate'@SimState { threads = threads' }
@@ -619,7 +642,7 @@ deschedule Interruptable !thread@Thread {
619642
-- So immediately raise the exception and unblock the blocked thread
620643
-- if possible.
621644
{-# SCC "deschedule.Interruptable.Unmasked" #-}
622-
let thread' = thread { threadControl = ThreadControl (Throw e) ctl
645+
let thread' = thread { threadControl = ThreadControl (Throw ThrowSelf e) ctl
623646
, threadMasking = MaskedInterruptible
624647
, threadThrowTo = etids }
625648
(unblocked,
@@ -654,13 +677,16 @@ deschedule Blocked !thread !simstate@SimState{threads} =
654677
threads' = Map.insert (threadId thread') thread' threads in
655678
reschedule simstate { threads = threads' }
656679

657-
deschedule Terminated !thread !simstate@SimState{ curTime = time, threads } =
680+
deschedule (Terminated reason) !thread !simstate@SimState{ curTime = time, threads } =
658681
-- This thread is done. If there are other threads blocked in a
659682
-- ThrowTo targeted at this thread then we can wake them up now.
660683
{-# SCC "deschedule.Terminated" #-}
661684
let !wakeup = map (l_labelled . snd) (reverse (threadThrowTo thread))
662685
(unblocked,
663-
!simstate') = unblockThreads wakeup simstate
686+
!simstate') = unblockThreads wakeup
687+
simstate { finished = Map.insert (threadId thread)
688+
reason
689+
(finished simstate) }
664690
in do
665691
!trace <- reschedule simstate'
666692
return $ traceMany

io-sim/src/Control/Monad/IOSim/Types.hs

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ module Control.Monad.IOSim.Types
5959
, module Control.Monad.IOSim.CommonTypes
6060
, SimM
6161
, SimSTM
62+
, Thrower (..)
6263
) where
6364

6465
import Control.Applicative
@@ -113,6 +114,8 @@ import Control.Monad.IOSim.CommonTypes
113114
import Control.Monad.IOSim.STM
114115
import Control.Monad.IOSimPOR.Types
115116

117+
import GHC.Conc (ThreadStatus)
118+
116119

117120
import qualified System.IO.Error as IO.Error (userError)
118121

@@ -131,6 +134,8 @@ traceM x = IOSim $ oneShot $ \k -> Output (toDyn x) (k ())
131134
traceSTM :: Typeable a => a -> STMSim s ()
132135
traceSTM x = STM $ oneShot $ \k -> OutputStm (toDyn x) (k ())
133136

137+
data Thrower = ThrowSelf | ThrowOther deriving (Ord, Eq, Show)
138+
134139
data SimA s a where
135140
Return :: a -> SimA s a
136141

@@ -148,14 +153,15 @@ data SimA s a where
148153
UpdateTimeout:: Timeout (IOSim s) -> DiffTime -> SimA s b -> SimA s b
149154
CancelTimeout:: Timeout (IOSim s) -> SimA s b -> SimA s b
150155

151-
Throw :: SomeException -> SimA s a
156+
Throw :: Thrower -> SomeException -> SimA s a
152157
Catch :: Exception e =>
153158
SimA s a -> (e -> SimA s a) -> (a -> SimA s b) -> SimA s b
154159
Evaluate :: a -> (a -> SimA s b) -> SimA s b
155160

156161
Fork :: IOSim s () -> (ThreadId -> SimA s b) -> SimA s b
157162
GetThreadId :: (ThreadId -> SimA s b) -> SimA s b
158163
LabelThread :: ThreadId -> String -> SimA s b -> SimA s b
164+
ThreadStatus :: ThreadId -> (ThreadStatus -> SimA s b) -> SimA s b
159165

160166
Atomically :: STM s a -> (a -> SimA s b) -> SimA s b
161167

@@ -242,7 +248,7 @@ instance Monoid a => Monoid (IOSim s a) where
242248
#endif
243249

244250
instance Fail.MonadFail (IOSim s) where
245-
fail msg = IOSim $ oneShot $ \_ -> Throw (toException (IO.Error.userError msg))
251+
fail msg = IOSim $ oneShot $ \_ -> Throw ThrowSelf (toException (IO.Error.userError msg))
246252

247253
instance MonadFix (IOSim s) where
248254
mfix f = IOSim $ oneShot $ \k -> Fix f k
@@ -289,7 +295,7 @@ instance MonadSay (IOSim s) where
289295
say msg = IOSim $ oneShot $ \k -> Say msg (k ())
290296

291297
instance MonadThrow (IOSim s) where
292-
throwIO e = IOSim $ oneShot $ \_ -> Throw (toException e)
298+
throwIO e = IOSim $ oneShot $ \_ -> Throw ThrowSelf (toException e)
293299

294300
instance MonadEvaluate (IOSim s) where
295301
evaluate a = IOSim $ oneShot $ \k -> Evaluate a k
@@ -373,6 +379,7 @@ instance MonadThread (IOSim s) where
373379
type ThreadId (IOSim s) = ThreadId
374380
myThreadId = IOSim $ oneShot $ \k -> GetThreadId k
375381
labelThread t l = IOSim $ oneShot $ \k -> LabelThread t l (k ())
382+
threadStatus t = IOSim $ oneShot $ \k -> ThreadStatus t k
376383

377384
instance MonadFork (IOSim s) where
378385
forkIO task = IOSim $ oneShot $ \k -> Fork task k
@@ -802,6 +809,7 @@ data SimEventType
802809
| EventPerformAction StepId
803810
| EventReschedule ScheduleControl
804811
| EventUnblocked [ThreadId]
812+
| EventThreadStatus ThreadId ThreadId
805813
deriving Show
806814

807815
type TraceEvent = SimEventType

0 commit comments

Comments
 (0)