Skip to content

Commit 997c174

Browse files
committed
io-sim: Data.List.Trace.Trace type
Trace is a cons list with polymorphic `Nil` constructor.
1 parent e9749f9 commit 997c174

File tree

5 files changed

+311
-90
lines changed

5 files changed

+311
-90
lines changed

io-sim/io-sim.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ source-repository head
2525

2626
library
2727
hs-source-dirs: src
28-
exposed-modules: Control.Monad.IOSim
28+
exposed-modules: Data.List.Trace
29+
, Control.Monad.IOSim
2930
other-modules: Control.Monad.IOSim.Internal
3031
default-language: Haskell2010
3132
other-extensions: BangPatterns,

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

Lines changed: 84 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ExplicitNamespaces #-}
12
{-# LANGUAGE RankNTypes #-}
23
{-# LANGUAGE ScopedTypeVariables #-}
34

@@ -19,8 +20,11 @@ module Control.Monad.IOSim (
1920
setCurrentTime,
2021
unshareClock,
2122
-- * Simulation trace
22-
Trace(..),
23-
TraceEvent(..),
23+
type SimTrace,
24+
Trace (Cons, Nil, Trace, SimTrace, TraceMainReturn, TraceMainException, TraceDeadlock),
25+
SimResult(..),
26+
SimEvent(..),
27+
SimEventType(..),
2428
ThreadLabel,
2529
Labelled (..),
2630
traceEvents,
@@ -31,6 +35,9 @@ module Control.Monad.IOSim (
3135
selectTraceEventsDynamic',
3236
selectTraceEventsSay,
3337
selectTraceEventsSay',
38+
traceSelectTraceEvents,
39+
traceSelectTraceEventsDynamic,
40+
traceSelectTraceEventsSay,
3441
printTraceEventsSay,
3542
-- * Eventlog
3643
EventlogEvent(..),
@@ -39,15 +46,19 @@ module Control.Monad.IOSim (
3946
execReadTVar,
4047
-- * Deprecated interfaces
4148
SimM,
42-
SimSTM
49+
SimSTM,
50+
TraceEvent
4351
) where
4452

4553
import Prelude
4654

4755
import Data.Dynamic (fromDynamic)
4856
import Data.List (intercalate)
57+
import Data.Bifoldable
4958
import Data.Typeable (Typeable)
5059

60+
import Data.List.Trace
61+
5162
import Control.Exception (throw)
5263

5364
import Control.Monad.ST.Lazy
@@ -59,81 +70,115 @@ import Control.Monad.IOSim.Internal
5970

6071

6172
selectTraceEvents
62-
:: (TraceEvent -> Maybe b)
63-
-> Trace a
73+
:: (SimEventType -> Maybe b)
74+
-> SimTrace a
6475
-> [b]
65-
selectTraceEvents fn = go
66-
where
67-
go (Trace _ _ _ ev trace) = case fn ev of
68-
Just x -> x : go trace
69-
Nothing -> go trace
70-
go (TraceMainException _ e _) = throw (FailureException e)
71-
go (TraceDeadlock _ threads) = throw (FailureDeadlock threads)
72-
go (TraceMainReturn _ _ _) = []
76+
selectTraceEvents fn =
77+
bifoldr ( \ v _
78+
-> case v of
79+
MainException _ e _ -> throw (FailureException e)
80+
Deadlock _ threads -> throw (FailureDeadlock threads)
81+
MainReturn _ _ _ -> []
82+
)
83+
( \ b acc -> b : acc )
84+
[]
85+
. traceSelectTraceEvents fn
7386

7487
selectTraceEvents'
75-
:: (TraceEvent -> Maybe b)
76-
-> Trace a
88+
:: (SimEventType -> Maybe b)
89+
-> SimTrace a
7790
-> [b]
78-
selectTraceEvents' fn = go
79-
where
80-
go (Trace _ _ _ ev trace) = case fn ev of
81-
Just x -> x : go trace
82-
Nothing -> go trace
83-
go (TraceMainException _ _ _) = []
84-
go (TraceDeadlock _ _) = []
85-
go (TraceMainReturn _ _ _) = []
91+
selectTraceEvents' fn =
92+
bifoldr ( \ _ _ -> [] )
93+
( \ b acc -> b : acc )
94+
[]
95+
. traceSelectTraceEvents fn
8696

8797
-- | Select all the traced values matching the expected type. This relies on
8898
-- the sim's dynamic trace facility.
8999
--
90100
-- For convenience, this throws exceptions for abnormal sim termination.
91101
--
92-
selectTraceEventsDynamic :: forall a b. Typeable b => Trace a -> [b]
102+
selectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> [b]
93103
selectTraceEventsDynamic = selectTraceEvents fn
94104
where
95-
fn :: TraceEvent -> Maybe b
105+
fn :: SimEventType -> Maybe b
96106
fn (EventLog dyn) = fromDynamic dyn
97107
fn _ = Nothing
98108

99109
-- | Like 'selectTraceEventsDynamic' but returns partial trace if an excpetion
100110
-- is found in it.
101111
--
102-
selectTraceEventsDynamic' :: forall a b. Typeable b => Trace a -> [b]
112+
selectTraceEventsDynamic' :: forall a b. Typeable b => SimTrace a -> [b]
103113
selectTraceEventsDynamic' = selectTraceEvents' fn
104114
where
105-
fn :: TraceEvent -> Maybe b
115+
fn :: SimEventType -> Maybe b
106116
fn (EventLog dyn) = fromDynamic dyn
107117
fn _ = Nothing
108118

109119
-- | Get a trace of 'EventSay'.
110120
--
111121
-- For convenience, this throws exceptions for abnormal sim termination.
112122
--
113-
selectTraceEventsSay :: Trace a -> [String]
123+
selectTraceEventsSay :: SimTrace a -> [String]
114124
selectTraceEventsSay = selectTraceEvents fn
115125
where
116-
fn :: TraceEvent -> Maybe String
126+
fn :: SimEventType -> Maybe String
117127
fn (EventSay s) = Just s
118128
fn _ = Nothing
119129

120130
-- | Like 'selectTraceEventsSay' but return partial trace if an exception is
121131
-- found in it.
122132
--
123-
selectTraceEventsSay' :: Trace a -> [String]
133+
selectTraceEventsSay' :: SimTrace a -> [String]
124134
selectTraceEventsSay' = selectTraceEvents' fn
125135
where
126-
fn :: TraceEvent -> Maybe String
136+
fn :: SimEventType -> Maybe String
127137
fn (EventSay s) = Just s
128138
fn _ = Nothing
129139

130140
-- | Print all 'EventSay' to the console.
131141
--
132142
-- For convenience, this throws exceptions for abnormal sim termination.
133143
--
134-
printTraceEventsSay :: Trace a -> IO ()
144+
printTraceEventsSay :: SimTrace a -> IO ()
135145
printTraceEventsSay = mapM_ print . selectTraceEventsSay
136146

147+
148+
-- | The most general select function. It is a _total_ function.
149+
--
150+
traceSelectTraceEvents
151+
:: (SimEventType -> Maybe b)
152+
-> SimTrace a
153+
-> Trace (SimResult a) b
154+
traceSelectTraceEvents fn = bifoldr ( \ v _acc -> Nil v )
155+
( \ eventCtx acc
156+
-> case fn (seType eventCtx) of
157+
Nothing -> acc
158+
Just b -> Cons b acc
159+
)
160+
undefined -- it is ignored
161+
162+
-- | Select dynamic events. It is a _total_ function.
163+
--
164+
traceSelectTraceEventsDynamic :: forall a b. Typeable b
165+
=> SimTrace a -> Trace (SimResult a) b
166+
traceSelectTraceEventsDynamic = traceSelectTraceEvents fn
167+
where
168+
fn :: SimEventType -> Maybe b
169+
fn (EventLog dyn) = fromDynamic dyn
170+
fn _ = Nothing
171+
172+
173+
-- | Select say events. It is a _total_ function.
174+
--
175+
traceSelectTraceEventsSay :: forall a. SimTrace a -> Trace (SimResult a) String
176+
traceSelectTraceEventsSay = traceSelectTraceEvents fn
177+
where
178+
fn :: SimEventType -> Maybe String
179+
fn (EventSay s) = Just s
180+
fn _ = Nothing
181+
137182
-- | Simulation termination with failure
138183
--
139184
data Failure =
@@ -183,24 +228,24 @@ runSimOrThrow mainAction =
183228
runSimStrictShutdown :: forall a. (forall s. IOSim s a) -> Either Failure a
184229
runSimStrictShutdown mainAction = traceResult True (runSimTrace mainAction)
185230

186-
traceResult :: Bool -> Trace a -> Either Failure a
231+
traceResult :: Bool -> SimTrace a -> Either Failure a
187232
traceResult strict = go
188233
where
189-
go (Trace _ _ _ _ t) = go t
234+
go (SimTrace _ _ _ _ t) = go t
190235
go (TraceMainReturn _ _ tids@(_:_))
191236
| strict = Left (FailureSloppyShutdown tids)
192237
go (TraceMainReturn _ x _) = Right x
193238
go (TraceMainException _ e _) = Left (FailureException e)
194239
go (TraceDeadlock _ threads) = Left (FailureDeadlock threads)
195240

196-
traceEvents :: Trace a -> [(Time, ThreadId, Maybe ThreadLabel, TraceEvent)]
197-
traceEvents (Trace time tid tlbl event t) = (time, tid, tlbl, event)
198-
: traceEvents t
199-
traceEvents _ = []
241+
traceEvents :: SimTrace a -> [(Time, ThreadId, Maybe ThreadLabel, SimEventType)]
242+
traceEvents (SimTrace time tid tlbl event t) = (time, tid, tlbl, event)
243+
: traceEvents t
244+
traceEvents _ = []
200245

201246

202247

203248
-- | See 'runSimTraceST' below.
204249
--
205-
runSimTrace :: forall a. (forall s. IOSim s a) -> Trace a
250+
runSimTrace :: forall a. (forall s. IOSim s a) -> SimTrace a
206251
runSimTrace mainAction = runST (runSimTraceST mainAction)

0 commit comments

Comments
 (0)