Safe Haskell | None |
---|---|
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
- controlSimTrace :: forall a. Maybe Int -> ScheduleControl -> ( forall s. IOSim s a) -> SimTrace a
- exploreSimTrace :: forall a test. Testable test => ( ExplorationOptions -> ExplorationOptions ) -> ( forall s. IOSim s a) -> ( Maybe ( SimTrace a) -> SimTrace a -> test) -> Property
- data ScheduleMod = ScheduleMod { }
-
data
ScheduleControl
- = ControlDefault
- | ControlAwait [ ScheduleMod ]
- | ControlFollow [ StepId ] [ ScheduleMod ]
- runSimTraceST :: forall s a. IOSim s a -> ST s ( SimTrace a)
- liftST :: ST s a -> IOSim s a
- traceM :: Typeable a => a -> IOSim s ()
- traceSTM :: Typeable a => a -> STMSim s ()
- 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 Trace :: Time -> ThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a
- pattern SimTrace :: Time -> ThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a
- pattern SimPORTrace :: Time -> ThreadId -> Int -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a
- pattern TraceDeadlock :: Time -> [ Labelled ThreadId ] -> SimTrace a
- pattern TraceLoop :: SimTrace a
- pattern TraceMainReturn :: Time -> a -> [ Labelled ThreadId ] -> SimTrace a
- pattern TraceMainException :: Time -> SomeException -> [ Labelled ThreadId ] -> SimTrace a
- pattern TraceRacesFound :: [ ScheduleControl ] -> SimTrace a -> SimTrace a
-
data
SimResult
a
- = MainReturn ! Time a ![ Labelled ThreadId ]
- | MainException ! Time SomeException ![ Labelled ThreadId ]
- | Deadlock ! Time ![ Labelled ThreadId ]
- | Loop
-
data
SimEvent
-
=
SimEvent
{
- seTime :: ! Time
- seThreadId :: ! ThreadId
- seThreadLabel :: !( Maybe ThreadLabel )
- seType :: ! SimEventType
-
|
SimPOREvent
{
- seTime :: ! Time
- seThreadId :: ! ThreadId
- seStep :: ! Int
- seThreadLabel :: !( Maybe ThreadLabel )
- seType :: ! SimEventType
- | SimRacesFound [ ScheduleControl ]
-
=
SimEvent
{
-
data
SimEventType
- = EventSimStart ScheduleControl
- | EventSay String
- | EventLog Dynamic
- | EventMask MaskingState
- | EventThrow SomeException
- | EventThrowTo SomeException ThreadId
- | EventThrowToBlocked
- | EventThrowToWakeup
- | EventThrowToUnmasked ( Labelled ThreadId )
- | EventThreadForked ThreadId
- | EventThreadFinished
- | EventThreadUnhandled SomeException
- | EventTxCommitted [ Labelled TVarId ] [ Labelled TVarId ] ( Maybe Effect)
- | EventTxAborted ( Maybe Effect)
- | EventTxBlocked [ Labelled TVarId ] ( Maybe Effect)
- | EventTxWakeup [ Labelled TVarId ]
- | EventTimerCreated TimeoutId TVarId Time
- | EventTimerUpdated TimeoutId Time
- | EventTimerCancelled TimeoutId
- | EventTimerExpired TimeoutId
- | EventThreadSleep
- | EventThreadWake
- | EventDeschedule Deschedule
- | EventFollowControl ScheduleControl
- | EventAwaitControl StepId ScheduleControl
- | EventPerformAction StepId
- | EventReschedule ScheduleControl
- | EventUnblocked [ ThreadId ]
- type ThreadLabel = String
-
data
Labelled
a =
Labelled
{
- l_labelled :: !a
- l_label :: !( Maybe String )
- ppTrace :: Show a => SimTrace a -> String
- ppTrace_ :: SimTrace a -> String
- ppEvents :: [( Time , ThreadId , Maybe ThreadLabel , SimEventType )] -> String
- ppSimEvent :: Int -> Int -> Int -> SimEvent -> String
- ppDebug :: SimTrace a -> x -> x
- traceEvents :: SimTrace a -> [( Time , ThreadId , Maybe ThreadLabel , SimEventType )]
- traceResult :: Bool -> SimTrace a -> Either Failure a
- selectTraceEvents :: ( SimEventType -> Maybe b) -> SimTrace a -> [b]
- selectTraceEvents' :: ( SimEventType -> Maybe b) -> SimTrace a -> [b]
- selectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> [b]
- selectTraceEventsDynamic' :: forall a b. Typeable b => SimTrace a -> [b]
- selectTraceEventsSay :: SimTrace a -> [ String ]
- selectTraceEventsSay' :: SimTrace a -> [ String ]
- selectTraceRaces :: SimTrace a -> [ ScheduleControl ]
- traceSelectTraceEvents :: ( 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 ()
- type ExplorationSpec = ExplorationOptions -> ExplorationOptions
- data ExplorationOptions = ExplorationOptions { }
- stdExplorationOptions :: ExplorationOptions
- withScheduleBound :: Int -> ExplorationSpec
- withBranching :: Int -> ExplorationSpec
- withStepTimelimit :: Int -> ExplorationSpec
- withReplay :: ScheduleControl -> ExplorationSpec
- newtype EventlogEvent = EventlogEvent String
- newtype EventlogMarker = EventlogMarker String
- execReadTVar :: TVar s a -> ST s a
- type SimM s = IOSim s
- type SimSTM = STM
- type TraceEvent = SimEventType
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 also fail if when the main thread terminates, there
are other threads still running or blocked. If one is trying to follow
a strict thread cleanup policy then this helps testing for that.
Simulation termination with failure
FailureException SomeException |
The main thread terminated with an exception |
FailureDeadlock ![ Labelled ThreadId ] |
The threads all deadlocked |
FailureSloppyShutdown [ Labelled ThreadId ] |
The main thread terminated normally but other threads were still
alive, and strict shutdown checking was requested.
See
|
Instances
Show Failure Source # | |
Exception Failure Source # | |
Defined in Control.Monad.IOSim toException :: Failure -> SomeException Source # fromException :: SomeException -> Maybe Failure Source # displayException :: Failure -> String Source # |
runSimTrace :: forall a. ( forall s. IOSim s a) -> SimTrace a Source #
See
runSimTraceST
below.
:: forall a. Maybe Int | |
-> ScheduleControl |
note: must be either
|
-> ( forall s. IOSim s a) | |
-> SimTrace a |
exploreSimTrace :: forall a test. Testable test => ( ExplorationOptions -> ExplorationOptions ) -> ( forall s. IOSim s a) -> ( Maybe ( SimTrace a) -> SimTrace a -> test) -> Property Source #
data ScheduleMod Source #
ScheduleMod | |
|
Instances
Eq ScheduleMod Source # | |
Defined in Control.Monad.IOSim.Types (==) :: ScheduleMod -> ScheduleMod -> Bool Source # (/=) :: ScheduleMod -> ScheduleMod -> Bool Source # |
|
Ord ScheduleMod Source # | |
Defined in Control.Monad.IOSim.Types compare :: ScheduleMod -> ScheduleMod -> Ordering Source # (<) :: ScheduleMod -> ScheduleMod -> Bool Source # (<=) :: ScheduleMod -> ScheduleMod -> Bool Source # (>) :: ScheduleMod -> ScheduleMod -> Bool Source # (>=) :: ScheduleMod -> ScheduleMod -> Bool Source # max :: ScheduleMod -> ScheduleMod -> ScheduleMod Source # min :: ScheduleMod -> ScheduleMod -> ScheduleMod Source # |
|
Show ScheduleMod Source # | |
Defined in Control.Monad.IOSim.Types |
data ScheduleControl Source #
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
Eq ScheduleControl Source # | |
Defined in Control.Monad.IOSim.Types (==) :: ScheduleControl -> ScheduleControl -> Bool Source # (/=) :: ScheduleControl -> ScheduleControl -> Bool Source # |
|
Ord ScheduleControl Source # | |
Defined in Control.Monad.IOSim.Types compare :: ScheduleControl -> ScheduleControl -> Ordering Source # (<) :: ScheduleControl -> ScheduleControl -> Bool Source # (<=) :: ScheduleControl -> ScheduleControl -> Bool Source # (>) :: ScheduleControl -> ScheduleControl -> Bool Source # (>=) :: ScheduleControl -> ScheduleControl -> Bool Source # max :: ScheduleControl -> ScheduleControl -> ScheduleControl Source # min :: ScheduleControl -> ScheduleControl -> ScheduleControl Source # |
|
Show ScheduleControl Source # | |
Defined in Control.Monad.IOSim.Types |
runSimTraceST :: forall s a. IOSim s a -> ST s ( SimTrace a) Source #
The most general method of running
IOSim
is in
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
.
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
A
cons
list with polymorphic
nil
, thus an octopus.
Usually used with
a
being a non empty sum type.
pattern Trace :: Time -> ThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a |
Deprecated: Use
|
pattern SimTrace :: Time -> ThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a | |
pattern SimPORTrace :: Time -> ThreadId -> Int -> Maybe ThreadLabel -> SimEventType -> SimTrace a -> SimTrace a | |
pattern TraceDeadlock :: Time -> [ Labelled ThreadId ] -> SimTrace a | |
pattern TraceLoop :: SimTrace a | |
pattern TraceMainReturn :: Time -> a -> [ Labelled ThreadId ] -> SimTrace a | |
pattern TraceMainException :: Time -> SomeException -> [ Labelled ThreadId ] -> SimTrace a | |
pattern TraceRacesFound :: [ ScheduleControl ] -> SimTrace a -> SimTrace a |
Instances
Bitraversable Trace Source # | |
Defined in Data.List.Trace bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Trace a b -> f ( Trace c d) Source # |
|
Bifoldable Trace Source # | |
Bifunctor Trace Source # | |
Monoid a => Monad ( Trace a) Source # | |
Functor ( Trace a) Source # | |
Monoid a => MonadFix ( Trace a) Source # | |
Monoid a => MonadFail ( Trace a) Source # | |
Monoid a => Applicative ( 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 => MonadPlus ( Trace a) Source # | |
( Eq b, Eq a) => Eq ( Trace a b) Source # | |
( Ord b, Ord a) => Ord ( Trace a b) Source # | |
Defined in Data.List.Trace |
|
( Show b, Show a) => Show ( Trace a b) Source # | |
Semigroup a => Semigroup ( Trace a b) Source # | |
Monoid a => Monoid ( Trace a b) Source # | |
MainReturn ! Time a ![ Labelled ThreadId ] | |
MainException ! Time SomeException ![ Labelled ThreadId ] | |
Deadlock ! Time ![ Labelled ThreadId ] | |
Loop |
Trace
is a recursive data type, it is the trace of a
IOSim
computation.
The trace will contain information about thread sheduling, 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 races discovered.
See also:
traceEvents
,
traceResult
,
selectTraceEvents
,
selectTraceEventsDynamic
and
printTraceEventsSay
.
SimEvent | |
|
|
SimPOREvent | |
|
|
SimRacesFound [ ScheduleControl ] |
Instances
data SimEventType Source #
Instances
Show SimEventType Source # | |
Defined in Control.Monad.IOSim.Types |
type ThreadLabel = String Source #
Labelled | |
|
Instances
Eq a => Eq ( Labelled a) Source # | |
Ord a => Ord ( Labelled a) Source # | |
Defined in Control.Monad.IOSim.Types compare :: Labelled a -> Labelled a -> Ordering Source # (<) :: Labelled a -> Labelled a -> Bool Source # (<=) :: Labelled a -> Labelled a -> Bool Source # (>) :: Labelled a -> Labelled a -> Bool Source # (>=) :: Labelled a -> Labelled a -> Bool Source # |
|
Show a => Show ( Labelled a) Source # | |
Generic ( 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-0.2.0.0-G47lzFOFdKi874hOfjQqmW" '
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
))))
|
Pretty printers
ppEvents :: [( Time , ThreadId , Maybe ThreadLabel , SimEventType )] -> String Source #
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 , ThreadId , Maybe ThreadLabel , SimEventType )] Source #
list selectors
selectTraceEvents :: ( SimEventType -> Maybe b) -> SimTrace a -> [b] Source #
selectTraceEvents' :: ( SimEventType -> Maybe b) -> SimTrace a -> [b] Source #
selectTraceEventsDynamic :: forall a b. Typeable b => SimTrace a -> [b] Source #
Select all the traced values matching the expected type. This relies on the sim's dynamic trace facility.
For convenience, this throws exceptions for abnormal sim termination.
selectTraceEventsDynamic' :: forall a b. Typeable b => SimTrace a -> [b] Source #
Like
selectTraceEventsDynamic
but returns partial trace if an exception
is found in it.
selectTraceEventsSay :: SimTrace a -> [ String ] Source #
Get a trace of
EventSay
.
For convenience, this throws exceptions for abnormal sim termination.
selectTraceEventsSay' :: SimTrace a -> [ String ] Source #
Like
selectTraceEventsSay
but return partial trace if an exception is
found in it.
selectTraceRaces :: SimTrace a -> [ ScheduleControl ] Source #
trace selectors
traceSelectTraceEvents :: ( 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, this throws exceptions for abnormal sim termination.
Exploration options
data ExplorationOptions Source #
Instances
Show ExplorationOptions Source # | |
Defined in Control.Monad.IOSim.Types |
withBranching :: Int -> ExplorationSpec Source #
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
execReadTVar :: TVar s a -> ST s a Source #
Deprecated interfaces
type TraceEvent = SimEventType Source #
Deprecated: Use
SimEventType
instead.