io-sim-0.2.0.0: A pure simulator for monadic concurrency with STM
Safe HaskellNone
LanguageHaskell2010

Control.Monad.IOSim

Synopsis

Simulation monad

data IOSim s a Source #

Instances

Instances details
Monad (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

(>>=)IOSim s a → (a → IOSim s b) → IOSim s b Source #

(>>)IOSim s a → IOSim s b → IOSim s b Source #

return ∷ a → IOSim s a Source #

Functor (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

fmap ∷ (a → b) → IOSim s a → IOSim s b Source #

(<$) ∷ a → IOSim s b → IOSim s a Source #

MonadFix (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

mfix ∷ (a → IOSim s a) → IOSim s a Source #

MonadFail (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

failStringIOSim s a Source #

Applicative (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

pure ∷ a → IOSim s a Source #

(<*>)IOSim s (a → b) → IOSim s a → IOSim s b Source #

liftA2 ∷ (a → b → c) → IOSim s a → IOSim s b → IOSim s c Source #

(*>)IOSim s a → IOSim s b → IOSim s b Source #

(<*)IOSim s a → IOSim s b → IOSim s a Source #

MonadThrow (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

throwMException e ⇒ e → IOSim s a Source #

MonadCatch (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

catchException e ⇒ IOSim s a → (e → IOSim s a) → IOSim s a Source #

MonadMask (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

mask ∷ ((∀ a. IOSim s a → IOSim s a) → IOSim s b) → IOSim s b Source #

uninterruptibleMask ∷ ((∀ a. IOSim s a → IOSim s a) → IOSim s b) → IOSim s b Source #

generalBracketIOSim s a → (a → ExitCase b → IOSim s c) → (a → IOSim s b) → IOSim s (b, c) Source #

MonadAsync (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type Async (IOSim s) = (async ∷ TypeType) Source #

Methods

asyncIOSim s a → IOSim s (Async (IOSim s) a) Source #

asyncThreadIdAsync (IOSim s) a → ThreadId (IOSim s) Source #

withAsyncIOSim s a → (Async (IOSim s) a → IOSim s b) → IOSim s b Source #

waitSTMAsync (IOSim s) a → STM (IOSim s) a Source #

pollSTMAsync (IOSim s) a → STM (IOSim s) (Maybe (Either SomeException a)) Source #

waitCatchSTMAsync (IOSim s) a → STM (IOSim s) (Either SomeException a) Source #

waitAnySTM ∷ [Async (IOSim s) a] → STM (IOSim s) (Async (IOSim s) a, a) Source #

waitAnyCatchSTM ∷ [Async (IOSim s) a] → STM (IOSim s) (Async (IOSim s) a, Either SomeException a) Source #

waitEitherSTMAsync (IOSim s) a → Async (IOSim s) b → STM (IOSim s) (Either a b) Source #

waitEitherSTM_Async (IOSim s) a → Async (IOSim s) b → STM (IOSim s) () Source #

waitEitherCatchSTMAsync (IOSim s) a → Async (IOSim s) b → STM (IOSim s) (Either (Either SomeException a) (Either SomeException b)) Source #

waitBothSTMAsync (IOSim s) a → Async (IOSim s) b → STM (IOSim s) (a, b) Source #

waitAsync (IOSim s) a → IOSim s a Source #

pollAsync (IOSim s) a → IOSim s (Maybe (Either SomeException a)) Source #

waitCatchAsync (IOSim s) a → IOSim s (Either SomeException a) Source #

cancelAsync (IOSim s) a → IOSim s () Source #

cancelWithException e ⇒ Async (IOSim s) a → e → IOSim s () Source #

uninterruptibleCancelAsync (IOSim s) a → IOSim s () Source #

waitAny ∷ [Async (IOSim s) a] → IOSim s (Async (IOSim s) a, a) Source #

waitAnyCatch ∷ [Async (IOSim s) a] → IOSim s (Async (IOSim s) a, Either SomeException a) Source #

waitAnyCancel ∷ [Async (IOSim s) a] → IOSim s (Async (IOSim s) a, a) Source #

waitAnyCatchCancel ∷ [Async (IOSim s) a] → IOSim s (Async (IOSim s) a, Either SomeException a) Source #

waitEitherAsync (IOSim s) a → Async (IOSim s) b → IOSim s (Either a b) Source #

waitEitherCatchAsync (IOSim s) a → Async (IOSim s) b → IOSim s (Either (Either SomeException a) (Either SomeException b)) Source #

waitEitherCancelAsync (IOSim s) a → Async (IOSim s) b → IOSim s (Either a b) Source #

waitEitherCatchCancelAsync (IOSim s) a → Async (IOSim s) b → IOSim s (Either (Either SomeException a) (Either SomeException b)) Source #

waitEither_Async (IOSim s) a → Async (IOSim s) b → IOSim s () Source #

waitBothAsync (IOSim s) a → Async (IOSim s) b → IOSim s (a, b) Source #

raceIOSim s a → IOSim s b → IOSim s (Either a b) Source #

race_IOSim s a → IOSim s b → IOSim s () Source #

concurrentlyIOSim s a → IOSim s b → IOSim s (a, b) Source #

concurrently_IOSim s a → IOSim s b → IOSim s () Source #

asyncWithUnmask ∷ ((∀ b. IOSim s b → IOSim s b) → IOSim s a) → IOSim s (Async (IOSim s) a) Source #

MonadDelay (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

threadDelayDiffTimeIOSim s () Source #

MonadTimer (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

data Timeout (IOSim s) Source #

MonadMonotonicTime (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadTime (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadSTM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type STM (IOSim s) = (stm ∷ TypeType) Source #

type TVar (IOSim s) ∷ TypeType Source #

type TMVar (IOSim s) ∷ TypeType Source #

type TQueue (IOSim s) ∷ TypeType Source #

type TBQueue (IOSim s) ∷ TypeType Source #

Methods

atomicallyHasCallStackSTM (IOSim s) a → IOSim s a Source #

newTVar ∷ a → STM (IOSim s) (TVar (IOSim s) a) Source #

readTVarTVar (IOSim s) a → STM (IOSim s) a Source #

writeTVarTVar (IOSim s) a → a → STM (IOSim s) () Source #

retrySTM (IOSim s) a Source #

orElseSTM (IOSim s) a → STM (IOSim s) a → STM (IOSim s) a Source #

modifyTVarTVar (IOSim s) a → (a → a) → STM (IOSim s) () Source #

modifyTVar'TVar (IOSim s) a → (a → a) → STM (IOSim s) () Source #

stateTVarTVar (IOSim s) s0 → (s0 → (a, s0)) → STM (IOSim s) a Source #

swapTVarTVar (IOSim s) a → a → STM (IOSim s) a Source #

checkBoolSTM (IOSim s) () Source #

newTMVar ∷ a → STM (IOSim s) (TMVar (IOSim s) a) Source #

newEmptyTMVarSTM (IOSim s) (TMVar (IOSim s) a) Source #

takeTMVarTMVar (IOSim s) a → STM (IOSim s) a Source #

tryTakeTMVarTMVar (IOSim s) a → STM (IOSim s) (Maybe a) Source #

putTMVarTMVar (IOSim s) a → a → STM (IOSim s) () Source #

tryPutTMVarTMVar (IOSim s) a → a → STM (IOSim s) Bool Source #

readTMVarTMVar (IOSim s) a → STM (IOSim s) a Source #

tryReadTMVarTMVar (IOSim s) a → STM (IOSim s) (Maybe a) Source #

swapTMVarTMVar (IOSim s) a → a → STM (IOSim s) a Source #

isEmptyTMVarTMVar (IOSim s) a → STM (IOSim s) Bool Source #

newTQueueSTM (IOSim s) (TQueue (IOSim s) a) Source #

readTQueueTQueue (IOSim s) a → STM (IOSim s) a Source #

tryReadTQueueTQueue (IOSim s) a → STM (IOSim s) (Maybe a) Source #

peekTQueueTQueue (IOSim s) a → STM (IOSim s) a Source #

tryPeekTQueueTQueue (IOSim s) a → STM (IOSim s) (Maybe a) Source #

writeTQueueTQueue (IOSim s) a → a → STM (IOSim s) () Source #

isEmptyTQueueTQueue (IOSim s) a → STM (IOSim s) Bool Source #

newTBQueueNaturalSTM (IOSim s) (TBQueue (IOSim s) a) Source #

readTBQueueTBQueue (IOSim s) a → STM (IOSim s) a Source #

tryReadTBQueueTBQueue (IOSim s) a → STM (IOSim s) (Maybe a) Source #

peekTBQueueTBQueue (IOSim s) a → STM (IOSim s) a Source #

tryPeekTBQueueTBQueue (IOSim s) a → STM (IOSim s) (Maybe a) Source #

flushTBQueueTBQueue (IOSim s) a → STM (IOSim s) [a] Source #

writeTBQueueTBQueue (IOSim s) a → a → STM (IOSim s) () Source #

lengthTBQueueTBQueue (IOSim s) a → STM (IOSim s) Natural Source #

isEmptyTBQueueTBQueue (IOSim s) a → STM (IOSim s) Bool Source #

isFullTBQueueTBQueue (IOSim s) a → STM (IOSim s) Bool Source #

newTVarIO ∷ a → IOSim s (TVar (IOSim s) a) Source #

readTVarIOTVar (IOSim s) a → IOSim s a Source #

newTMVarIO ∷ a → IOSim s (TMVar (IOSim s) a) Source #

newEmptyTMVarIOIOSim s (TMVar (IOSim s) a) Source #

newTQueueIOIOSim s (TQueue (IOSim s) a) Source #

newTBQueueIONaturalIOSim s (TBQueue (IOSim s) a) Source #

MonadLabelledSTM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

labelTVarTVar (IOSim s) a → StringSTM (IOSim s) () Source #

labelTMVarTMVar (IOSim s) a → StringSTM (IOSim s) () Source #

labelTQueueTQueue (IOSim s) a → StringSTM (IOSim s) () Source #

labelTBQueueTBQueue (IOSim s) a → StringSTM (IOSim s) () Source #

labelTVarIOTVar (IOSim s) a → StringIOSim s () Source #

labelTMVarIOTMVar (IOSim s) a → StringIOSim s () Source #

labelTQueueIOTQueue (IOSim s) a → StringIOSim s () Source #

labelTBQueueIOTBQueue (IOSim s) a → StringIOSim s () Source #

MonadInspectSTM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type InspectMonad (IOSim s) ∷ TypeType Source #

Methods

inspectTVar ∷ proxy (IOSim s) → TVar (IOSim s) a → InspectMonad (IOSim s) a Source #

inspectTMVar ∷ proxy (IOSim s) → TMVar (IOSim s) a → InspectMonad (IOSim s) (Maybe a) Source #

MonadTraceSTM (IOSim s) Source #

This instance adds a trace when a variable was written, just after the stm transaction was committed.

Traces the first value using dynamic tracing, like traceM does, i.e. with EventDynamic; the string is traced using EventSay.

Instance details

Defined in Control.Monad.IOSim.Types

Methods

traceTVar ∷ proxy (IOSim s) → TVar (IOSim s) a → (Maybe a → a → InspectMonad (IOSim s) TraceValue) → STM (IOSim s) () Source #

traceTMVar ∷ proxy (IOSim s) → TMVar (IOSim s) a → (Maybe (Maybe a) → Maybe a → InspectMonad (IOSim s) TraceValue) → STM (IOSim s) () Source #

traceTQueue ∷ proxy (IOSim s) → TQueue (IOSim s) a → (Maybe [a] → [a] → InspectMonad (IOSim s) TraceValue) → STM (IOSim s) () Source #

traceTBQueue ∷ proxy (IOSim s) → TBQueue (IOSim s) a → (Maybe [a] → [a] → InspectMonad (IOSim s) TraceValue) → STM (IOSim s) () Source #

traceTVarIO ∷ proxy (IOSim s) → TVar (IOSim s) a → (Maybe a → a → InspectMonad (IOSim s) TraceValue) → IOSim s () Source #

traceTMVarIO ∷ proxy (IOSim s) → TMVar (IOSim s) a → (Maybe (Maybe a) → Maybe a → InspectMonad (IOSim s) TraceValue) → IOSim s () Source #

traceTQueueIO ∷ proxy (IOSim s) → TQueue (IOSim s) a → (Maybe [a] → [a] → InspectMonad (IOSim s) TraceValue) → IOSim s () Source #

traceTBQueueIO ∷ proxy (IOSim s) → TBQueue (IOSim s) a → (Maybe [a] → [a] → InspectMonad (IOSim s) TraceValue) → IOSim s () Source #

MonadThrow (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

throwIOException e ⇒ e → IOSim s a Source #

bracketIOSim s a → (a → IOSim s b) → (a → IOSim s c) → IOSim s c Source #

bracket_IOSim s a → IOSim s b → IOSim s c → IOSim s c Source #

finallyIOSim s a → IOSim s b → IOSim s a Source #

MonadCatch (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

catchException e ⇒ IOSim s a → (e → IOSim s a) → IOSim s a Source #

catchJustException e ⇒ (e → Maybe b) → IOSim s a → (b → IOSim s a) → IOSim s a Source #

tryException e ⇒ IOSim s a → IOSim s (Either e a) Source #

tryJustException e ⇒ (e → Maybe b) → IOSim s a → IOSim s (Either b a) Source #

handleException e ⇒ (e → IOSim s a) → IOSim s a → IOSim s a Source #

handleJustException e ⇒ (e → Maybe b) → (b → IOSim s a) → IOSim s a → IOSim s a Source #

onExceptionIOSim s a → IOSim s b → IOSim s a Source #

bracketOnErrorIOSim s a → (a → IOSim s b) → (a → IOSim s c) → IOSim s c Source #

generalBracketIOSim s a → (a → ExitCase b → IOSim s c) → (a → IOSim s b) → IOSim s (b, c) Source #

MonadMask (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

mask ∷ ((∀ a. IOSim s a → IOSim s a) → IOSim s b) → IOSim s b Source #

uninterruptibleMask ∷ ((∀ a. IOSim s a → IOSim s a) → IOSim s b) → IOSim s b Source #

mask_IOSim s a → IOSim s a Source #

uninterruptibleMask_IOSim s a → IOSim s a Source #

MonadMaskingState (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadEvaluate (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

evaluate ∷ a → IOSim s a Source #

MonadTest (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

exploreRacesIOSim s () Source #

MonadSay (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

sayStringIOSim s () Source #

MonadST (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

withLiftST ∷ (∀ s0. (∀ a. ST s0 a → IOSim s a) → b) → b Source #

MonadThread (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type ThreadId (IOSim s) Source #

MonadFork (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

forkIOIOSim s () → IOSim s (ThreadId (IOSim s)) Source #

forkIOWithUnmask ∷ ((∀ a. IOSim s a → IOSim s a) → IOSim s ()) → IOSim s (ThreadId (IOSim s)) Source #

throwToException e ⇒ ThreadId (IOSim s) → e → IOSim s () Source #

killThreadThreadId (IOSim s) → IOSim s () Source #

yieldIOSim s () Source #

MonadEventlog (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

traceEventIOStringIOSim s () Source #

traceMarkerIOStringIOSim s () Source #

Semigroup a ⇒ Semigroup (IOSim s a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

(<>)IOSim s a → IOSim s a → IOSim s a Source #

sconcatNonEmpty (IOSim s a) → IOSim s a Source #

stimesIntegral b ⇒ b → IOSim s a → IOSim s a Source #

Monoid a ⇒ Monoid (IOSim s a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

memptyIOSim s a Source #

mappendIOSim s a → IOSim s a → IOSim s a Source #

mconcat ∷ [IOSim s a] → IOSim s a Source #

type Async (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type Async (IOSim s)
data Timeout (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TBQueue (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TQueue (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TMVar (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TMVar (IOSim s) = TMVarDefault (IOSim s)
type TVar (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TVar (IOSim s) = TVar s
type STM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type STM (IOSim s) = STM s
type InspectMonad (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type InspectMonad (IOSim s) = ST s
type ThreadId (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Run simulation

runSim ∷ ∀ a. (∀ s. IOSim s a) → Either Failure a Source #

IOSim is a pure monad.

runSimOrThrow ∷ ∀ a. (∀ s. IOSim s a) → a Source #

For quick experiments and tests it is often appropriate and convenient to simply throw failures as exceptions.

runSimStrictShutdown ∷ ∀ a. (∀ 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.

data Failure Source #

Simulation termination with failure

Constructors

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 runSimStrictShutdown

Instances

Instances details
Show Failure Source # 
Instance details

Defined in Control.Monad.IOSim

Exception Failure Source # 
Instance details

Defined in Control.Monad.IOSim

runSimTrace ∷ ∀ a. (∀ s. IOSim s a) → SimTrace a Source #

See runSimTraceST below.

controlSimTrace Source #

Arguments

∷ ∀ a. Maybe Int 
ScheduleControl

note: must be either ControlDefault or ControlAwait.

→ (∀ s. IOSim s a) 
SimTrace a 

exploreSimTrace ∷ ∀ a test. Testable test ⇒ (ExplorationOptionsExplorationOptions) → (∀ s. IOSim s a) → (Maybe (SimTrace a) → SimTrace a → test) → Property Source #

data ScheduleMod Source #

Constructors

ScheduleMod 

Fields

data ScheduleControl Source #

Constructors

ControlDefault

default scheduling mode

ControlAwait [ScheduleMod]

if the current control is ControlAwait, the normal scheduling will proceed, until the thread found in the first ScheduleMod reaches the given step. At this point the thread is put to sleep, until after all the steps are followed.

ControlFollow [StepId] [ScheduleMod]

follow the steps then continue with schedule modifications. This control is set by followControl when controlTargets returns true.

runSimTraceST ∷ ∀ 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 SimEventTypes generated by the computation with traceEvents. A slightly more convenient way is exposed by runSimTrace.

liftSTST s a → IOSim s a Source #

traceMTypeable a ⇒ a → IOSim s () Source #

traceSTMTypeable a ⇒ a → STMSim s () Source #

Simulation time

setCurrentTimeUTCTimeIOSim s () Source #

Set the current wall clock time for the thread's clock domain.

unshareClockIOSim 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

data Trace a b Source #

A cons list with polymorphic nil, thus an octopus.

  • Trace Void a is an infinite stream
  • Trace () a is isomorphic to [a]

Usually used with a being a non empty sum type.

Constructors

Cons b (Trace a b) 
Nil a 

Bundled Patterns

pattern TraceTimeThreadIdMaybe ThreadLabelSimEventTypeSimTrace a → SimTrace a

Deprecated: Use SimTrace instead.

pattern SimTraceTimeThreadIdMaybe ThreadLabelSimEventTypeSimTrace a → SimTrace a 
pattern SimPORTraceTimeThreadIdIntMaybe ThreadLabelSimEventTypeSimTrace a → SimTrace a 
pattern TraceDeadlockTime → [Labelled ThreadId] → SimTrace a 
pattern TraceLoopSimTrace a 
pattern TraceMainReturnTime → a → [Labelled ThreadId] → SimTrace a 
pattern TraceMainExceptionTimeSomeException → [Labelled ThreadId] → SimTrace a 
pattern TraceRacesFound ∷ [ScheduleControl] → SimTrace a → SimTrace a 

Instances

Instances details
Bitraversable Trace Source # 
Instance details

Defined in Data.List.Trace

Methods

bitraverseApplicative f ⇒ (a → f c) → (b → f d) → Trace a b → f (Trace c d) Source #

Bifoldable Trace Source # 
Instance details

Defined in Data.List.Trace

Methods

bifoldMonoid m ⇒ Trace m m → m Source #

bifoldMapMonoid m ⇒ (a → m) → (b → m) → Trace a b → m Source #

bifoldr ∷ (a → c → c) → (b → c → c) → c → Trace a b → c Source #

bifoldl ∷ (c → a → c) → (c → b → c) → c → Trace a b → c Source #

Bifunctor Trace Source # 
Instance details

Defined in Data.List.Trace

Methods

bimap ∷ (a → b) → (c → d) → Trace a c → Trace b d Source #

first ∷ (a → b) → Trace a c → Trace b c Source #

second ∷ (b → c) → Trace a b → Trace a c Source #

Monoid a ⇒ Monad (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

(>>=)Trace a a0 → (a0 → Trace a b) → Trace a b Source #

(>>)Trace a a0 → Trace a b → Trace a b Source #

return ∷ a0 → Trace a a0 Source #

Functor (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

fmap ∷ (a0 → b) → Trace a a0 → Trace a b Source #

(<$) ∷ a0 → Trace a b → Trace a a0 Source #

Monoid a ⇒ MonadFix (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

mfix ∷ (a0 → Trace a a0) → Trace a a0 Source #

Monoid a ⇒ MonadFail (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

failStringTrace a a0 Source #

Monoid a ⇒ Applicative (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

pure ∷ a0 → Trace a a0 Source #

(<*>)Trace a (a0 → b) → Trace a a0 → Trace a b Source #

liftA2 ∷ (a0 → b → c) → Trace a a0 → Trace a b → Trace a c Source #

(*>)Trace a a0 → Trace a b → Trace a b Source #

(<*)Trace a a0 → Trace a b → Trace a a0 Source #

Eq a ⇒ Eq1 (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

liftEq ∷ (a0 → b → Bool) → Trace a a0 → Trace a b → Bool Source #

Ord a ⇒ Ord1 (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

liftCompare ∷ (a0 → b → Ordering) → Trace a a0 → Trace a b → Ordering Source #

Show a ⇒ Show1 (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

liftShowsPrec ∷ (Int → a0 → ShowS) → ([a0] → ShowS) → IntTrace a a0 → ShowS Source #

liftShowList ∷ (Int → a0 → ShowS) → ([a0] → ShowS) → [Trace a a0] → ShowS Source #

Monoid a ⇒ Alternative (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

emptyTrace a a0 Source #

(<|>)Trace a a0 → Trace a a0 → Trace a a0 Source #

someTrace a a0 → Trace a [a0] Source #

manyTrace a a0 → Trace a [a0] Source #

Monoid a ⇒ MonadPlus (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

mzeroTrace a a0 Source #

mplusTrace a a0 → Trace a a0 → Trace a a0 Source #

(Eq b, Eq a) ⇒ Eq (Trace a b) Source # 
Instance details

Defined in Data.List.Trace

Methods

(==)Trace a b → Trace a b → Bool Source #

(/=)Trace a b → Trace a b → Bool Source #

(Ord b, Ord a) ⇒ Ord (Trace a b) Source # 
Instance details

Defined in Data.List.Trace

Methods

compareTrace a b → Trace a b → Ordering Source #

(<)Trace a b → Trace a b → Bool Source #

(<=)Trace a b → Trace a b → Bool Source #

(>)Trace a b → Trace a b → Bool Source #

(>=)Trace a b → Trace a b → Bool Source #

maxTrace a b → Trace a b → Trace a b Source #

minTrace a b → Trace a b → Trace a b Source #

(Show b, Show a) ⇒ Show (Trace a b) Source # 
Instance details

Defined in Data.List.Trace

Methods

showsPrecIntTrace a b → ShowS Source #

showTrace a b → String Source #

showList ∷ [Trace a b] → ShowS Source #

Semigroup a ⇒ Semigroup (Trace a b) Source # 
Instance details

Defined in Data.List.Trace

Methods

(<>)Trace a b → Trace a b → Trace a b Source #

sconcatNonEmpty (Trace a b) → Trace a b Source #

stimesIntegral b0 ⇒ b0 → Trace a b → Trace a b Source #

Monoid a ⇒ Monoid (Trace a b) Source # 
Instance details

Defined in Data.List.Trace

Methods

memptyTrace a b Source #

mappendTrace a b → Trace a b → Trace a b Source #

mconcat ∷ [Trace a b] → Trace a b Source #

data SimResult a Source #

Instances

Instances details
Show a ⇒ Show (SimResult a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

data SimEvent Source #

Trace is a recursive data type, it is the trace of a IOSim computation. The trace will contain information about thread sheduling, blocking on TVars, 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.

Instances

Instances details
Show SimEvent Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Generic SimEvent Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type Rep SimEventTypeType Source #

type Rep SimEvent Source # 
Instance details

Defined in Control.Monad.IOSim.Types

data Labelled a Source #

Constructors

Labelled 

Fields

Instances

Instances details
Eq a ⇒ Eq (Labelled a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

(==)Labelled a → Labelled a → Bool Source #

(/=)Labelled a → Labelled a → Bool Source #

Ord a ⇒ Ord (Labelled a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

compareLabelled 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 #

maxLabelled a → Labelled a → Labelled a Source #

minLabelled a → Labelled a → Labelled a Source #

Show a ⇒ Show (Labelled a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Generic (Labelled a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type Rep (Labelled a) ∷ TypeType Source #

Methods

fromLabelled a → Rep (Labelled a) x Source #

toRep (Labelled a) x → Labelled a Source #

type Rep (Labelled a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type Rep (Labelled a) = D1 ('MetaData "Labelled" "Control.Monad.IOSim.Types" "io-sim-0.2.0.0-inplace" '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

ppTraceShow a ⇒ SimTrace a → String Source #

Pretty print simulation trace.

ppTrace_SimTrace a → String Source #

Like ppTrace but does not show the result value.

ppSimEvent Source #

Arguments

Int

width of the time

Int

width of thread id

Int

width of thread label

SimEvent 
String 

ppDebugSimTrace 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

list selectors

selectTraceEventsDynamic ∷ ∀ 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' ∷ ∀ a b. Typeable b ⇒ SimTrace a → [b] Source #

Like selectTraceEventsDynamic but returns partial trace if an exception is found in it.

selectTraceEventsSaySimTrace 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.

trace selectors

traceSelectTraceEvents ∷ (SimEventTypeMaybe b) → SimTrace a → Trace (SimResult a) b Source #

The most general select function. It is a _total_ function.

traceSelectTraceEventsDynamic ∷ ∀ a b. Typeable b ⇒ SimTrace a → Trace (SimResult a) b Source #

Select dynamic events. It is a _total_ function.

traceSelectTraceEventsSay ∷ ∀ a. SimTrace a → Trace (SimResult a) String Source #

Select say events. It is a _total_ function.

IO printer

printTraceEventsSaySimTrace a → IO () Source #

Print all EventSay to the console.

For convenience, this throws exceptions for abnormal sim termination.

Exploration options

Eventlog

newtype EventlogEvent Source #

Wrapper for Eventlog events so they can be retrieved from the trace with selectTraceEventsDynamic.

Constructors

EventlogEvent String 

newtype EventlogMarker Source #

Wrapper for Eventlog markers so they can be retrieved from the trace with selectTraceEventsDynamic.

Constructors

EventlogMarker String 

Low-level API

execReadTVarTVar s a → ST s a Source #

Deprecated interfaces

type SimM s = IOSim s Source #

Deprecated: Use IOSim

type SimSTM = STM Source #

Deprecated: Use STMSim

type TraceEvent = SimEventType Source #

Deprecated: Use SimEventType instead.