io-sim-0.2.0.0: A pure simulator for monadic concurrency with STM
Safe Haskell None
Language Haskell2010

Control.Monad.IOSim.Types

Synopsis

Documentation

newtype IOSim s a Source #

Constructors

IOSim

Fields

Instances

Instances details
Monad ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

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

Applicative ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadThrow ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadCatch ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Methods

catch :: Exception 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 :: (( forall a. IOSim s a -> IOSim s a) -> IOSim s b) -> IOSim s b Source #

uninterruptibleMask :: (( forall a. IOSim s a -> IOSim s a) -> IOSim s b) -> IOSim s b Source #

generalBracket :: IOSim 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 :: Type -> Type ) Source #

Methods

async :: IOSim s a -> IOSim s ( Async ( IOSim s) a) Source #

asyncThreadId :: Async ( IOSim s) a -> ThreadId ( IOSim s) Source #

withAsync :: IOSim s a -> ( Async ( IOSim s) a -> IOSim s b) -> IOSim s b Source #

waitSTM :: Async ( IOSim s) a -> STM ( IOSim s) a Source #

pollSTM :: Async ( IOSim s) a -> STM ( IOSim s) ( Maybe ( Either SomeException a)) Source #

waitCatchSTM :: Async ( 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 #

waitEitherSTM :: Async ( 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 #

waitEitherCatchSTM :: Async ( IOSim s) a -> Async ( IOSim s) b -> STM ( IOSim s) ( Either ( Either SomeException a) ( Either SomeException b)) Source #

waitBothSTM :: Async ( IOSim s) a -> Async ( IOSim s) b -> STM ( IOSim s) (a, b) Source #

wait :: Async ( IOSim s) a -> IOSim s a Source #

poll :: Async ( IOSim s) a -> IOSim s ( Maybe ( Either SomeException a)) Source #

waitCatch :: Async ( IOSim s) a -> IOSim s ( Either SomeException a) Source #

cancel :: Async ( IOSim s) a -> IOSim s () Source #

cancelWith :: Exception e => Async ( IOSim s) a -> e -> IOSim s () Source #

uninterruptibleCancel :: Async ( 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 #

waitEither :: Async ( IOSim s) a -> Async ( IOSim s) b -> IOSim s ( Either a b) Source #

waitEitherCatch :: Async ( IOSim s) a -> Async ( IOSim s) b -> IOSim s ( Either ( Either SomeException a) ( Either SomeException b)) Source #

waitEitherCancel :: Async ( IOSim s) a -> Async ( IOSim s) b -> IOSim s ( Either a b) Source #

waitEitherCatchCancel :: Async ( 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 #

waitBoth :: Async ( IOSim s) a -> Async ( IOSim s) b -> IOSim s (a, b) Source #

race :: IOSim s a -> IOSim s b -> IOSim s ( Either a b) Source #

race_ :: IOSim s a -> IOSim s b -> IOSim s () Source #

concurrently :: IOSim s a -> IOSim s b -> IOSim s (a, b) Source #

concurrently_ :: IOSim s a -> IOSim s b -> IOSim s () Source #

asyncWithUnmask :: (( forall 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

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

Methods

atomically :: HasCallStack => STM ( IOSim s) a -> IOSim s a Source #

newTVar :: a -> STM ( IOSim s) ( TVar ( IOSim s) a) Source #

readTVar :: TVar ( IOSim s) a -> STM ( IOSim s) a Source #

writeTVar :: TVar ( IOSim s) a -> a -> STM ( IOSim s) () Source #

retry :: STM ( IOSim s) a Source #

orElse :: STM ( IOSim s) a -> STM ( IOSim s) a -> STM ( IOSim s) a Source #

modifyTVar :: TVar ( IOSim s) a -> (a -> a) -> STM ( IOSim s) () Source #

modifyTVar' :: TVar ( IOSim s) a -> (a -> a) -> STM ( IOSim s) () Source #

stateTVar :: TVar ( IOSim s) s0 -> (s0 -> (a, s0)) -> STM ( IOSim s) a Source #

swapTVar :: TVar ( IOSim s) a -> a -> STM ( IOSim s) a Source #

check :: Bool -> STM ( IOSim s) () Source #

newTMVar :: a -> STM ( IOSim s) ( TMVar ( IOSim s) a) Source #

newEmptyTMVar :: STM ( IOSim s) ( TMVar ( IOSim s) a) Source #

takeTMVar :: TMVar ( IOSim s) a -> STM ( IOSim s) a Source #

tryTakeTMVar :: TMVar ( IOSim s) a -> STM ( IOSim s) ( Maybe a) Source #

putTMVar :: TMVar ( IOSim s) a -> a -> STM ( IOSim s) () Source #

tryPutTMVar :: TMVar ( IOSim s) a -> a -> STM ( IOSim s) Bool Source #

readTMVar :: TMVar ( IOSim s) a -> STM ( IOSim s) a Source #

tryReadTMVar :: TMVar ( IOSim s) a -> STM ( IOSim s) ( Maybe a) Source #

swapTMVar :: TMVar ( IOSim s) a -> a -> STM ( IOSim s) a Source #

isEmptyTMVar :: TMVar ( IOSim s) a -> STM ( IOSim s) Bool Source #

newTQueue :: STM ( IOSim s) ( TQueue ( IOSim s) a) Source #

readTQueue :: TQueue ( IOSim s) a -> STM ( IOSim s) a Source #

tryReadTQueue :: TQueue ( IOSim s) a -> STM ( IOSim s) ( Maybe a) Source #

peekTQueue :: TQueue ( IOSim s) a -> STM ( IOSim s) a Source #

tryPeekTQueue :: TQueue ( IOSim s) a -> STM ( IOSim s) ( Maybe a) Source #

writeTQueue :: TQueue ( IOSim s) a -> a -> STM ( IOSim s) () Source #

isEmptyTQueue :: TQueue ( IOSim s) a -> STM ( IOSim s) Bool Source #

newTBQueue :: Natural -> STM ( IOSim s) ( TBQueue ( IOSim s) a) Source #

readTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) a Source #

tryReadTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) ( Maybe a) Source #

peekTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) a Source #

tryPeekTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) ( Maybe a) Source #

flushTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) [a] Source #

writeTBQueue :: TBQueue ( IOSim s) a -> a -> STM ( IOSim s) () Source #

lengthTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) Natural Source #

isEmptyTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) Bool Source #

isFullTBQueue :: TBQueue ( IOSim s) a -> STM ( IOSim s) Bool Source #

newTVarIO :: a -> IOSim s ( TVar ( IOSim s) a) Source #

readTVarIO :: TVar ( IOSim s) a -> IOSim s a Source #

newTMVarIO :: a -> IOSim s ( TMVar ( IOSim s) a) Source #

newEmptyTMVarIO :: IOSim s ( TMVar ( IOSim s) a) Source #

newTQueueIO :: IOSim s ( TQueue ( IOSim s) a) Source #

newTBQueueIO :: Natural -> IOSim s ( TBQueue ( IOSim s) a) Source #

MonadLabelledSTM ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadInspectSTM ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

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

MonadThrow ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadCatch ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadMask ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadMaskingState ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadEvaluate ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadTest ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadSay ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadST ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Methods

withLiftST :: ( forall s0. ( forall 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

MonadEventlog ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Semigroup a => Semigroup ( IOSim s a) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Monoid a => Monoid ( IOSim s a) Source #
Instance details

Defined in Control.Monad.IOSim.Types

type Async ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

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 TVar ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

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 ThreadId ( IOSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

newtype STM s a Source #

Constructors

STM

Fields

Instances

Instances details
Monad ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Functor ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Methods

fmap :: (a -> b) -> STM s a -> STM s b Source #

(<$) :: a -> STM s b -> STM s a Source #

MonadFail ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Applicative ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Alternative ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadPlus ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadThrow ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadThrow ( STM s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

MonadSay ( STMSim s) Source #
Instance details

Defined in Control.Monad.IOSim.Types

data StmA s a where Source #

Constructors

ReturnStm :: a -> StmA s a
ThrowStm :: SomeException -> StmA s a
NewTVar :: Maybe String -> x -> ( TVar s x -> StmA s b) -> StmA s b
LabelTVar :: String -> TVar s a -> StmA s b -> StmA s b
ReadTVar :: TVar s a -> (a -> StmA s b) -> StmA s b
WriteTVar :: TVar s a -> a -> StmA s b -> StmA s b
Retry :: StmA s b
OrElse :: StmA s a -> StmA s a -> (a -> StmA s b) -> StmA s b
SayStm :: String -> StmA s b -> StmA s b
OutputStm :: Dynamic -> StmA s b -> StmA s b
TraceTVar :: forall s a b. TVar s a -> ( Maybe a -> a -> ST s TraceValue ) -> StmA s b -> StmA s b

data StmTxResult s a Source #

Constructors

StmTxCommitted

A committed transaction reports the vars that were written (in order of first write) so that the scheduler can unblock other threads that were blocked in STM transactions that read any of these vars.

It reports the vars that were read, so we can update vector clocks appropriately.

The third list of vars is ones that were created during this transaction. This is useful for an implementation of traceTVar .

It also includes the updated TVarId name supply.

Fields

StmTxBlocked [ SomeTVar s]

A blocked transaction reports the vars that were read so that the scheduler can block the thread on those vars.

StmTxAborted [ SomeTVar s] SomeException

An aborted transaction reports the vars that were read so that the vector clock can be updated.

data StmStack s b a where Source #

Constructors

AtomicallyFrame :: StmStack s a a

Executing in the context of a top level atomically .

OrElseLeftFrame :: StmA s a -> (a -> StmA s b) -> Map TVarId ( SomeTVar s) -> [ SomeTVar s] -> [ SomeTVar s] -> StmStack s b c -> StmStack s a c

Executing in the context of the left hand side of an orElse

OrElseRightFrame :: (a -> StmA s b) -> Map TVarId ( SomeTVar s) -> [ SomeTVar s] -> [ SomeTVar s] -> StmStack s b c -> StmStack s a c

Executing in the context of the right hand side of an orElse

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.

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.

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 .

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

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

type Rep SimEvent Source #
Instance details

Defined in Control.Monad.IOSim.Types

data Trace a b where Source #

A cons list with polymorphic nil , thus an octopus.

Usually used with a being a non empty sum type.

Instances

Instances details
Bitraversable Trace Source #
Instance details

Defined in Data.List.Trace

Methods

bitraverse :: Applicative 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

bifold :: Monoid m => Trace m m -> m Source #

bifoldMap :: Monoid 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

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

Monoid a => Applicative ( Trace a) Source #
Instance details

Defined in Data.List.Trace

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

Show a => Show1 ( Trace a) Source #
Instance details

Defined in Data.List.Trace

Monoid a => Alternative ( Trace a) Source #
Instance details

Defined in Data.List.Trace

Monoid a => MonadPlus ( Trace a) Source #
Instance details

Defined in Data.List.Trace

( Eq b, Eq a) => Eq ( Trace a b) Source #
Instance details

Defined in Data.List.Trace

( Ord b, Ord a) => Ord ( Trace a b) Source #
Instance details

Defined in Data.List.Trace

( Show b, Show a) => Show ( Trace a b) Source #
Instance details

Defined in Data.List.Trace

Semigroup a => Semigroup ( Trace a b) Source #
Instance details

Defined in Data.List.Trace

Monoid a => Monoid ( Trace a b) Source #
Instance details

Defined in Data.List.Trace

ppTrace :: Show 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

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.

data Labelled a Source #

Instances

Instances details
Eq a => Eq ( Labelled a) Source #
Instance details

Defined in Control.Monad.IOSim.Types

Ord a => Ord ( Labelled a) Source #
Instance details

Defined in Control.Monad.IOSim.Types

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) :: Type -> Type 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-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 ))))

data TVar s a Source #

Constructors

TVar

Fields

Instances

Instances details
Eq ( TVar s a) Source #
Instance details

Defined in Control.Monad.IOSim.CommonTypes

data SomeTVar s where Source #

Constructors

SomeTVar :: !( TVar s a) -> SomeTVar s

type SimM s = IOSim s Source #

Deprecated: Use IOSim

type SimSTM = STM Source #

Deprecated: Use STMSim