Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data IOSim s a
- type STMSim = STM
- runSim :: forall a. (forall s. IOSim s a) -> Either Failure a
- runSimOrThrow :: forall a. (forall s. IOSim s a) -> a
- runSimStrictShutdown :: forall a. (forall s. IOSim s a) -> Either Failure a
- data Failure
- runSimTrace :: forall a. (forall s. IOSim s a) -> SimTrace a
- runSimTraceST :: forall s a. IOSim s a -> ST s (SimTrace a)
- monadicIOSim_ :: Testable a => (forall s. PropertyM (IOSim s) a) -> Property
- monadicIOSim :: (Testable a, forall s. Monad (m s)) => (SimTrace Property -> Property) -> (forall s a. m s a -> IOSim s a) -> (forall s. PropertyM (m s) a) -> Property
- runIOSimGen :: (SimTrace a -> Property) -> (forall s. Gen (IOSim s a)) -> Gen Property
- exploreSimTrace :: forall a test. Testable test => (ExplorationOptions -> ExplorationOptions) -> (forall s. IOSim s a) -> (Maybe (SimTrace a) -> SimTrace a -> test) -> Property
- exploreSimTraceST :: forall s a test. Testable test => (ExplorationOptions -> ExplorationOptions) -> (forall s. IOSim s a) -> (Maybe (SimTrace a) -> SimTrace a -> ST s test) -> ST s Property
- controlSimTrace :: forall a. Maybe Int -> ScheduleControl -> (forall s. IOSim s a) -> SimTrace a
- controlSimTraceST :: Maybe Int -> ScheduleControl -> IOSim s a -> ST s (SimTrace a)
- data ScheduleMod = ScheduleMod {
- scheduleModTarget :: StepId
- scheduleModControl :: ScheduleControl
- scheduleModInsertion :: [StepId]
- data ScheduleControl
- = ControlDefault
- | ControlAwait [ScheduleMod]
- | ControlFollow [StepId] [ScheduleMod]
- type ExplorationSpec = ExplorationOptions -> ExplorationOptions
- data ExplorationOptions = ExplorationOptions {}
- stdExplorationOptions :: ExplorationOptions
- withScheduleBound :: Int -> ExplorationSpec
- withBranching :: Int -> ExplorationSpec
- withStepTimelimit :: Int -> ExplorationSpec
- withReplay :: ScheduleControl -> ExplorationSpec
- liftST :: ST s a -> IOSim s a
- setCurrentTime :: UTCTime -> IOSim s ()
- unshareClock :: IOSim s ()
- type SimTrace a = Trace (SimResult a) SimEvent
- data Trace a b where
- Cons b (Trace a b)
- Nil a
- pattern SimTrace :: Time -> IOSimThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a
- pattern SimPORTrace :: Time -> IOSimThreadId -> Int -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a
- pattern TraceDeadlock :: Time -> [Labelled IOSimThreadId] -> SimTrace a
- pattern TraceLoop :: SimTrace a
- pattern TraceMainReturn :: Time -> Labelled IOSimThreadId -> a -> [Labelled IOSimThreadId] -> SimTrace a
- pattern TraceMainException :: Time -> Labelled IOSimThreadId -> SomeException -> [Labelled IOSimThreadId] -> SimTrace a
- pattern TraceRacesFound :: [ScheduleControl] -> SimTrace a -> SimTrace a
- pattern TraceInternalError :: String -> SimTrace a
- data SimResult a
- data SimEvent
- = SimEvent {
- seTime :: !Time
- seThreadId :: !IOSimThreadId
- seThreadLabel :: !(Maybe ThreadLabel)
- seType :: !SimEventType
- | SimPOREvent {
- seTime :: !Time
- seThreadId :: !IOSimThreadId
- seStep :: !Int
- seThreadLabel :: !(Maybe ThreadLabel)
- seType :: !SimEventType
- | SimRacesFound [ScheduleControl]
- = SimEvent {
- data SimEventType
- = EventSay String
- | EventLog Dynamic
- | EventMask MaskingState
- | EventThrow SomeException
- | EventThrowTo SomeException IOSimThreadId
- | EventThrowToBlocked
- | EventThrowToWakeup
- | EventThrowToUnmasked (Labelled IOSimThreadId)
- | EventThreadForked IOSimThreadId
- | EventThreadFinished
- | EventThreadUnhandled SomeException
- | EventTxCommitted [Labelled TVarId] [Labelled TVarId] (Maybe Effect)
- | EventTxAborted (Maybe Effect)
- | EventTxBlocked [Labelled TVarId] (Maybe Effect)
- | EventTxWakeup [Labelled TVarId]
- | EventUnblocked [IOSimThreadId]
- | EventThreadDelay TimeoutId Time
- | EventThreadDelayFired TimeoutId
- | EventTimeoutCreated TimeoutId IOSimThreadId Time
- | EventTimeoutFired TimeoutId
- | EventRegisterDelayCreated TimeoutId TVarId Time
- | EventRegisterDelayFired TimeoutId
- | EventTimerCreated TimeoutId TVarId Time
- | EventTimerCancelled TimeoutId
- | EventTimerFired TimeoutId
- | EventThreadStatus IOSimThreadId IOSimThreadId
- | EventSimStart ScheduleControl
- | EventThreadSleep
- | EventThreadWake
- | EventDeschedule Deschedule
- | EventFollowControl ScheduleControl
- | EventAwaitControl StepId ScheduleControl
- | EventPerformAction StepId
- | EventReschedule ScheduleControl
- | EventEffect VectorClock Effect
- | EventRaces Races
- type ThreadLabel = String
- data IOSimThreadId
- = RacyThreadId [Int]
- | ThreadId [Int]
- data Labelled a = Labelled {
- l_labelled :: !a
- l_label :: !(Maybe String)
- traceM :: Typeable a => a -> IOSim s ()
- traceSTM :: Typeable a => a -> STMSim s ()
- ppTrace :: Show a => SimTrace a -> String
- ppTrace_ :: SimTrace a -> String
- ppEvents :: [(Time, IOSimThreadId, Maybe ThreadLabel, SimEventType)] -> String
- ppSimEvent :: Int -> Int -> Int -> SimEvent -> String
- ppDebug :: SimTrace a -> x -> x
- traceEvents :: SimTrace a -> [(Time, IOSimThreadId, Maybe ThreadLabel, SimEventType)]
- traceResult :: Bool -> SimTrace a -> Either Failure a
- selectTraceEvents :: (Time -> SimEventType -> Maybe b) -> SimTrace a -> [b]
- selectTraceEvents' :: (Time -> SimEventType -> Maybe b) -> SimTrace a -> [b]
- selectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> [b]
- selectTraceEventsDynamicWithTime :: forall a b. Typeable b => SimTrace a -> [(Time, b)]
- selectTraceEventsDynamic' :: forall a b. Typeable b => SimTrace a -> [b]
- selectTraceEventsDynamicWithTime' :: forall a b. Typeable b => SimTrace a -> [(Time, b)]
- selectTraceEventsSay :: SimTrace a -> [String]
- selectTraceEventsSayWithTime :: SimTrace a -> [(Time, String)]
- selectTraceEventsSay' :: SimTrace a -> [String]
- selectTraceEventsSayWithTime' :: SimTrace a -> [(Time, String)]
- selectTraceRaces :: SimTrace a -> [ScheduleControl]
- traceSelectTraceEvents :: (Time -> SimEventType -> Maybe b) -> SimTrace a -> Trace (SimResult a) b
- traceSelectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> Trace (SimResult a) b
- traceSelectTraceEventsSay :: forall a. SimTrace a -> Trace (SimResult a) String
- printTraceEventsSay :: SimTrace a -> IO ()
- newtype EventlogEvent = EventlogEvent String
- newtype EventlogMarker = EventlogMarker String
- data Timeout s
- newTimeout :: DiffTime -> IOSim s (Timeout s)
- readTimeout :: Timeout s -> STM s TimeoutState
- cancelTimeout :: Timeout s -> IOSim s ()
- awaitTimeout :: Timeout s -> STM s Bool
Simulation monad
Instances
Run simulation
runSimOrThrow :: forall a. (forall s. IOSim s a) -> a Source #
For quick experiments and tests it is often appropriate and convenient to simply throw failures as exceptions.
runSimStrictShutdown :: forall a. (forall s. IOSim s a) -> Either Failure a Source #
Like runSim
but fail when the main thread terminates if there are other
threads still running or blocked. If one is trying to follow a strict thread
clean-up policy then this helps testing for that.
Simulation terminated a failure.
FailureException SomeException | The main thread terminated with an exception. |
FailureDeadlock ![Labelled IOSimThreadId] | The threads all deadlocked. |
FailureSloppyShutdown [Labelled IOSimThreadId] | The main thread terminated normally but other threads were still
alive, and strict shutdown checking was requested.
See |
FailureEvaluation SomeException | An exception was thrown while evaluation the trace. This could be an internal assertion failure of `io-sim` or an unhandled exception in the simulation. |
FailureInternal String | An internal failure of the simulator. Please open an issue at https://github.com/input-output-hk/io-sim/issues. |
Instances
Exception Failure Source # | |
Defined in Control.Monad.IOSim toException :: Failure -> SomeException # fromException :: SomeException -> Maybe Failure # displayException :: Failure -> String # | |
Show Failure Source # | |
runSimTrace :: forall a. (forall s. IOSim s a) -> SimTrace a Source #
See runSimTraceST
below.
runSimTraceST :: forall s a. IOSim s a -> ST s (SimTrace a) Source #
The most general method of running IOSim
is in the lazy ST
monad. One
can recover failures or the result from SimTrace
with
traceResult
, or access SimEventType
s generated by
the computation with traceEvents
. A slightly more
convenient way is exposed by runSimTrace
.
QuickCheck Monadic combinators
monadicIOSim_ :: Testable a => (forall s. PropertyM (IOSim s) a) -> Property Source #
Like https://hackage.haskell.org/package/QuickCheck-2.14.3/docs/Test-QuickCheck-Monadic.html#v:monadicST.
Note: it calls traceResult
in non-strict mode, e.g. leaked threads do not
cause failures.
Since: 1.4.1.0
:: (Testable a, forall s. Monad (m s)) | |
=> (SimTrace Property -> Property) | Allows to trace either (\e -> counterexample (show e) False) id . traceResult False as |
-> (forall s a. m s a -> IOSim s a) | natural transformation from |
-> (forall s. PropertyM (m s) a) | |
-> Property |
A more general version of monadicIOSim_
, which:
- allows to run in monad stacks build on top of
IOSim
; - gives more control how to attach debugging information to failed tests.
Note, to use this combinator your monad needs to be defined as:
newtype M s a = M s { runM :: ReaderT State (IOSim s) a }
It's important that `M s` is a monad. For such a monad one you'll need provide
a natural transformation:
-- the state could also be created as an
IOSim
computation.
nat :: forall s a. State -> M s a -> IOSim
s a
nat state m = runStateT (runM m) state
Since: 1.4.1.0
runIOSimGen :: (SimTrace a -> Property) -> (forall s. Gen (IOSim s a)) -> Gen Property Source #
Like <runSTGen https://hackage.haskell.org/package/QuickCheck-2.14.3/docs/Test-QuickCheck-Monadic.html#v:runSTGen>.
Since: 1.4.1.0
Explore races using IOSimPOR
IOSimPOR is a different interpreter of IOSim
which has the ability to
discover race conditions and replay the simulation using a schedule which
reverts them. For extended documentation how to use it see
here.
IOSimPOR only discovers races between events which happen in the same time
slot. In IOSim and IOSimPOR time only moves explicitly through timer
events, e.g. things like threadDelay
,
registerDelay
or the
NonStandard
API. The usual
QuickCheck techniques can help explore different schedules of
threads too.
:: forall a test. Testable test | |
=> (ExplorationOptions -> ExplorationOptions) | modify default exploration options |
-> (forall s. IOSim s a) | a simulation to run |
-> (Maybe (SimTrace a) -> SimTrace a -> test) | a callback which receives the previous trace (e.g. before reverting a race condition) and current trace |
-> Property |
Execute a simulation, discover & revert races. Note that this will execute
the simulation multiple times with different schedules, and thus it's much
more costly than a simple runSimTrace
(also the simulation environments has
much more state to track and hence it is slower).
On property failure it will show the failing schedule (ScheduleControl
)
which can be passed to controlSimTrace
to reproduce the failure without
discovering the schedule.
exploreSimTraceST :: forall s a test. Testable test => (ExplorationOptions -> ExplorationOptions) -> (forall s. IOSim s a) -> (Maybe (SimTrace a) -> SimTrace a -> ST s test) -> ST s Property Source #
An ST
version of exploreSimTrace
. The callback also receives
ScheduleControl
. This is mostly useful for testing IOSimPOR itself.
:: forall a. Maybe Int | limit on the computation time allowed per scheduling step, for catching infinite loops etc. |
-> ScheduleControl | a schedule to replay note: must be either |
-> (forall s. IOSim s a) | a simulation to run |
-> SimTrace a |
Run a simulation using a given schedule. This is useful to reproduce failing cases without exploring the races.
controlSimTraceST :: Maybe Int -> ScheduleControl -> IOSim s a -> ST s (SimTrace a) Source #
data ScheduleMod Source #
A schedule modification inserted at given execution step.
ScheduleMod | |
|
Instances
Show ScheduleMod Source # | |
Defined in Control.Monad.IOSimPOR.Types showsPrec :: Int -> ScheduleMod -> ShowS # show :: ScheduleMod -> String # showList :: [ScheduleMod] -> ShowS # | |
Eq ScheduleMod Source # | |
Defined in Control.Monad.IOSimPOR.Types (==) :: ScheduleMod -> ScheduleMod -> Bool # (/=) :: ScheduleMod -> ScheduleMod -> Bool # | |
Ord ScheduleMod Source # | |
Defined in Control.Monad.IOSimPOR.Types compare :: ScheduleMod -> ScheduleMod -> Ordering # (<) :: ScheduleMod -> ScheduleMod -> Bool # (<=) :: ScheduleMod -> ScheduleMod -> Bool # (>) :: ScheduleMod -> ScheduleMod -> Bool # (>=) :: ScheduleMod -> ScheduleMod -> Bool # max :: ScheduleMod -> ScheduleMod -> ScheduleMod # min :: ScheduleMod -> ScheduleMod -> ScheduleMod # |
data ScheduleControl Source #
Modified execution schedule.
ControlDefault | default scheduling mode |
ControlAwait [ScheduleMod] | if the current control is |
ControlFollow [StepId] [ScheduleMod] | follow the steps then continue with schedule
modifications. This control is set by |
Instances
Show ScheduleControl Source # | |
Defined in Control.Monad.IOSimPOR.Types showsPrec :: Int -> ScheduleControl -> ShowS # show :: ScheduleControl -> String # showList :: [ScheduleControl] -> ShowS # | |
Eq ScheduleControl Source # | |
Defined in Control.Monad.IOSimPOR.Types (==) :: ScheduleControl -> ScheduleControl -> Bool # (/=) :: ScheduleControl -> ScheduleControl -> Bool # | |
Ord ScheduleControl Source # | |
Defined in Control.Monad.IOSimPOR.Types compare :: ScheduleControl -> ScheduleControl -> Ordering # (<) :: ScheduleControl -> ScheduleControl -> Bool # (<=) :: ScheduleControl -> ScheduleControl -> Bool # (>) :: ScheduleControl -> ScheduleControl -> Bool # (>=) :: ScheduleControl -> ScheduleControl -> Bool # max :: ScheduleControl -> ScheduleControl -> ScheduleControl # min :: ScheduleControl -> ScheduleControl -> ScheduleControl # |
Exploration options
data ExplorationOptions Source #
Race exploration options.
ExplorationOptions | |
|
Instances
Show ExplorationOptions Source # | |
Defined in Control.Monad.IOSim.Types showsPrec :: Int -> ExplorationOptions -> ShowS # show :: ExplorationOptions -> String # showList :: [ExplorationOptions] -> ShowS # |
withBranching :: Int -> ExplorationSpec Source #
Lift ST computations
Simulation time
setCurrentTime :: UTCTime -> IOSim s () Source #
Set the current wall clock time for the thread's clock domain.
unshareClock :: IOSim s () Source #
Put the thread into a new wall clock domain, not shared with the parent thread. Changing the wall clock time in the new clock domain will not affect the other clock of other threads. All threads forked by this thread from this point onwards will share the new clock domain.
Simulation trace
type SimTrace a = Trace (SimResult a) SimEvent Source #
A type alias for IOSim
simulation trace. It comes with useful pattern
synonyms.
A cons
list with polymorphic nil
.
Usually used with a
being a non empty sum type.
pattern SimTrace :: Time -> IOSimThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a | |
pattern SimPORTrace :: Time -> IOSimThreadId -> Int -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a | |
pattern TraceDeadlock :: Time -> [Labelled IOSimThreadId] -> SimTrace a | |
pattern TraceLoop :: SimTrace a | |
pattern TraceMainReturn :: Time -> Labelled IOSimThreadId -> a -> [Labelled IOSimThreadId] -> SimTrace a | |
pattern TraceMainException :: Time -> Labelled IOSimThreadId -> SomeException -> [Labelled IOSimThreadId] -> SimTrace a | |
pattern TraceRacesFound :: [ScheduleControl] -> SimTrace a -> SimTrace a | |
pattern TraceInternalError :: String -> SimTrace a |
Instances
Bifoldable Trace Source # | |
Bifunctor Trace Source # | |
Bitraversable Trace Source # | |
Defined in Data.List.Trace bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Trace a b -> f (Trace c d) # | |
Monoid a => MonadFail (Trace a) Source # | |
Defined in Data.List.Trace | |
Monoid a => MonadFix (Trace a) Source # | |
Defined in Data.List.Trace | |
Eq a => Eq1 (Trace a) Source # | |
Ord a => Ord1 (Trace a) Source # | |
Defined in Data.List.Trace | |
Show a => Show1 (Trace a) Source # | |
Monoid a => Alternative (Trace a) Source # | |
Monoid a => Applicative (Trace a) Source # | |
Functor (Trace a) Source # | |
Monoid a => Monad (Trace a) Source # | |
Monoid a => MonadPlus (Trace a) Source # | |
Monoid a => Monoid (Trace a b) Source # | |
Semigroup a => Semigroup (Trace a b) Source # | |
(Show b, Show a) => Show (Trace a b) Source # | |
(Eq b, Eq a) => Eq (Trace a b) Source # | |
(Ord b, Ord a) => Ord (Trace a b) Source # | |
Defined in Data.List.Trace |
A result type of a simulation.
MainReturn !Time !(Labelled IOSimThreadId) a ![Labelled IOSimThreadId] | Return value of the main thread. |
MainException !Time !(Labelled IOSimThreadId) SomeException ![Labelled IOSimThreadId] | Exception thrown by the main thread. |
Deadlock !Time ![Labelled IOSimThreadId] | Deadlock discovered in the simulation. Deadlocks are discovered if simply the simulation cannot do any progress in a given time slot and there's no event which would advance the time. |
Loop | Only returned by IOSimPOR when a step execution took longer than
|
InternalError String | An |
Trace
is a recursive data type, it is the trace of a IOSim
computation. The trace will contain information about thread scheduling,
blocking on TVar
s, and other internal state changes of IOSim
. More
importantly it also supports traces generated by the computation with say
(which corresponds to using putStrLn
in IO
), traceEventM
, or
dynamically typed traces with traceM
(which generalise the base
library
traceM
)
It also contains information on discovered races.
See also: traceEvents
,
traceResult
, selectTraceEvents
,
selectTraceEventsDynamic
and
printTraceEventsSay
.
SimEvent | Used when using |
| |
SimPOREvent | Only used for IOSimPOR |
| |
SimRacesFound [ScheduleControl] | Only used for IOSimPOR |
Instances
data SimEventType Source #
Events recorded by the simulation.
EventSay String | hold value of |
EventLog Dynamic | hold a dynamic value of |
EventMask MaskingState | masking state changed |
EventThrow SomeException | throw exception |
EventThrowTo SomeException IOSimThreadId | throw asynchronous exception ( |
EventThrowToBlocked | the thread which executed |
EventThrowToWakeup | the thread which executed |
EventThrowToUnmasked (Labelled IOSimThreadId) | a target thread of |
EventThreadForked IOSimThreadId | forked a thread |
EventThreadFinished | thread terminated normally |
EventThreadUnhandled SomeException | thread terminated by an unhandled exception |
EventTxCommitted | committed STM transaction |
EventTxAborted (Maybe Effect) | |
EventTxBlocked | STM transaction blocked (due to |
EventTxWakeup [Labelled TVarId] | changed vars causing retry |
EventUnblocked [IOSimThreadId] | unblocked threads by a committed STM transaction |
EventThreadDelay TimeoutId Time | thread delayed |
EventThreadDelayFired TimeoutId | thread woken up after a delay |
EventTimeoutCreated TimeoutId IOSimThreadId Time | new timeout created (via |
EventTimeoutFired TimeoutId | timeout fired |
EventRegisterDelayCreated TimeoutId TVarId Time | registered delay (via |
EventRegisterDelayFired TimeoutId | registered delay fired |
EventTimerCreated TimeoutId TVarId Time | a new |
EventTimerCancelled TimeoutId | a |
EventTimerFired TimeoutId | a |
EventThreadStatus | event traced when |
| |
EventSimStart ScheduleControl | IOSimPOR event: new execution started exploring the given schedule. |
EventThreadSleep | IOSimPOR event: the labelling thread was runnable, but its execution
was delayed, until Event inserted to mark a difference between a failed trace and a similar passing trace. |
EventThreadWake | IOSimPOR event: marks when the thread was rescheduled by IOSimPOR |
EventDeschedule Deschedule | IOSim and IOSimPOR event: a thread was descheduled |
EventFollowControl ScheduleControl | IOSimPOR event: following given schedule |
EventAwaitControl StepId ScheduleControl | IOSimPOR event: thread delayed to follow the given schedule |
EventPerformAction StepId | IOSimPOR event: perform action of the given step |
EventReschedule ScheduleControl | IOSimPOR event: reschedule a thread following the given
|
EventEffect VectorClock Effect | IOSimPOR event: executed effect; Useful for debugging IOSimPOR or showing compact information about thread execution. |
EventRaces Races | IOSimPOR event: races. Races are updated while we execute a simulation. Useful for debugging IOSimPOR. |
Instances
Show SimEventType Source # | |
Defined in Control.Monad.IOSim.Types showsPrec :: Int -> SimEventType -> ShowS # show :: SimEventType -> String # showList :: [SimEventType] -> ShowS # |
type ThreadLabel = String Source #
data IOSimThreadId Source #
A thread id.
IOSimPOR: RacyThreadId
indicates that this thread is taken into account
when discovering races. A thread is marked as racy iff
exploreRaces
was
executed in it or it's a thread forked by a racy thread.
RacyThreadId [Int] | A racy thread ( |
ThreadId [Int] | A non racy thread. They have higher priority than racy threads in
|
Instances
A labelled value.
For example labelThread
or labelTVar
will insert a label to IOSimThreadId
(or TVarId
).
Labelled | |
|
Instances
Generic (Labelled a) Source # | |
Show a => Show (Labelled a) Source # | |
Eq a => Eq (Labelled a) Source # | |
Ord a => Ord (Labelled a) Source # | |
type Rep (Labelled a) Source # | |
Defined in Control.Monad.IOSim.Types type Rep (Labelled a) = D1 ('MetaData "Labelled" "Control.Monad.IOSim.Types" "io-sim-1.4.1.0-8TDmmXymLpaCSqpkcl2TeS" 'False) (C1 ('MetaCons "Labelled" 'PrefixI 'True) (S1 ('MetaSel ('Just "l_labelled") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "l_label") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe String)))) |
Dynamic Tracing
traceSTM :: Typeable a => a -> STMSim s () Source #
Trace a value, in the same was as traceM
does, but from the STM
monad.
This is primarily useful for debugging.
Pretty printers
ppTrace :: Show a => SimTrace a -> String Source #
Pretty print simulation trace.
Note: this is not a streaming function, it will evaluate the whole trace before printing it. If you need to print a very large trace, you might want to use
ppTrace
show (ppSimEvent
0 0 0)
ppEvents :: [(Time, IOSimThreadId, Maybe ThreadLabel, SimEventType)] -> String Source #
Pretty print a timestamped event.
Pretty print a SimEvent
.
ppDebug :: SimTrace a -> x -> x Source #
Trace each event using trace
; this is useful when a trace ends with
a pure error, e.g. an assertion.
Selectors
traceEvents :: SimTrace a -> [(Time, IOSimThreadId, Maybe ThreadLabel, SimEventType)] Source #
Turn SimTrace
into a list of timestamped events.
:: Bool | if True the simulation will fail if there are any threads which didn't terminated when the main thread terminated. |
-> SimTrace a | simulation trace |
-> Either Failure a |
Fold through the trace and return either Failure
or a simulation
result, i.e. the return value of the main thread.
list selectors
selectTraceEvents :: (Time -> SimEventType -> Maybe b) -> SimTrace a -> [b] Source #
Select events according to the predicate function. It throws an error if
the simulation ends with Failure
.
selectTraceEvents' :: (Time -> SimEventType -> Maybe b) -> SimTrace a -> [b] Source #
Like selectTraceEvents
, but it returns even if the simulation trace ends
with Failure
.
selectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> [b] Source #
Select all the traced values matching the expected type. It relies on the sim's dynamic trace facility.
For convenience, it throws exceptions for abnormal sim termination.
selectTraceEventsDynamicWithTime :: forall a b. Typeable b => SimTrace a -> [(Time, b)] Source #
Like selectTraceEventsDynamic
but it also captures time of the trace
event.
selectTraceEventsDynamic' :: forall a b. Typeable b => SimTrace a -> [b] Source #
Like selectTraceEventsDynamic
but it returns even if the simulation trace
ends with Failure
.
selectTraceEventsDynamicWithTime' :: forall a b. Typeable b => SimTrace a -> [(Time, b)] Source #
Like selectTraceEventsDynamic'
but it also captures time of the trace
event.
selectTraceEventsSay :: SimTrace a -> [String] Source #
Get a trace of EventSay
.
For convenience, it throws exceptions for abnormal sim termination.
selectTraceEventsSayWithTime :: SimTrace a -> [(Time, String)] Source #
Like selectTraceEventsSay
but it also captures time of the trace event.
selectTraceEventsSay' :: SimTrace a -> [String] Source #
Like selectTraceEventsSay
but it returns even if the simulation trace
ends with Failure
.
selectTraceEventsSayWithTime' :: SimTrace a -> [(Time, String)] Source #
Like selectTraceEventsSay'
but it also captures time of the trace event.
selectTraceRaces :: SimTrace a -> [ScheduleControl] Source #
trace selectors
traceSelectTraceEvents :: (Time -> SimEventType -> Maybe b) -> SimTrace a -> Trace (SimResult a) b Source #
The most general select function. It is a total function.
traceSelectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> Trace (SimResult a) b Source #
Select dynamic events. It is a total function.
traceSelectTraceEventsSay :: forall a. SimTrace a -> Trace (SimResult a) String Source #
Select say events. It is a total function.
IO printer
printTraceEventsSay :: SimTrace a -> IO () Source #
Print all EventSay
to the console.
For convenience, it throws exceptions for abnormal sim termination.
Eventlog
newtype EventlogEvent Source #
Wrapper for Eventlog events so they can be retrieved from the trace with
selectTraceEventsDynamic
.
newtype EventlogMarker Source #
Wrapper for Eventlog markers so they can be retrieved from the trace with
selectTraceEventsDynamic
.
Low-level API
readTimeout :: Timeout s -> STM s TimeoutState Source #
cancelTimeout :: Timeout s -> IOSim s () Source #
awaitTimeout :: Timeout s -> STM s Bool Source #