io-sim-1.0.0.0: A pure simulator for monadic concurrency with STM.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.IOSim

Synopsis

Simulation monad

data IOSim s a Source #

Instances

Instances details
MonadFail (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

fail :: String -> IOSim s a #

MonadFix (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

mfix :: (a -> IOSim s a) -> IOSim s a #

Applicative (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

pure :: a -> IOSim s a #

(<*>) :: IOSim s (a -> b) -> IOSim s a -> IOSim s b #

liftA2 :: (a -> b -> c) -> IOSim s a -> IOSim s b -> IOSim s c #

(*>) :: IOSim s a -> IOSim s b -> IOSim s b #

(<*) :: IOSim s a -> IOSim s b -> IOSim s a #

Functor (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

fmap :: (a -> b) -> IOSim s a -> IOSim s b #

(<$) :: a -> IOSim s b -> IOSim s a #

Monad (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

(>>=) :: IOSim s a -> (a -> IOSim s b) -> IOSim s b #

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

return :: a -> IOSim s a #

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 #

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 #

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

generalBracket :: IOSim s a -> (a -> ExitCase b -> IOSim s c) -> (a -> IOSim s b) -> IOSim s (b, c) #

MonadThrow (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

throwM :: Exception e => e -> IOSim s a #

MonadAsync (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type Async (IOSim s) = (async :: Type -> Type) #

Methods

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

asyncBound :: IOSim s a -> IOSim s (Async (IOSim s) a) #

asyncOn :: Int -> IOSim s a -> IOSim s (Async (IOSim s) a) #

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

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

withAsyncBound :: IOSim s a -> (Async (IOSim s) a -> IOSim s b) -> IOSim s b #

withAsyncOn :: Int -> IOSim s a -> (Async (IOSim s) a -> IOSim s b) -> IOSim s b #

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

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

waitCatchSTM :: Async (IOSim s) a -> STM (IOSim s) (Either SomeException a) #

waitAnySTM :: [Async (IOSim s) a] -> STM (IOSim s) (Async (IOSim s) a, a) #

waitAnyCatchSTM :: [Async (IOSim s) a] -> STM (IOSim s) (Async (IOSim s) a, Either SomeException a) #

waitEitherSTM :: Async (IOSim s) a -> Async (IOSim s) b -> STM (IOSim s) (Either a b) #

waitEitherSTM_ :: Async (IOSim s) a -> Async (IOSim s) b -> STM (IOSim s) () #

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

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

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

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

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

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

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

uninterruptibleCancel :: Async (IOSim s) a -> IOSim s () #

waitAny :: [Async (IOSim s) a] -> IOSim s (Async (IOSim s) a, a) #

waitAnyCatch :: [Async (IOSim s) a] -> IOSim s (Async (IOSim s) a, Either SomeException a) #

waitAnyCancel :: [Async (IOSim s) a] -> IOSim s (Async (IOSim s) a, a) #

waitAnyCatchCancel :: [Async (IOSim s) a] -> IOSim s (Async (IOSim s) a, Either SomeException a) #

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

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

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

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

waitEither_ :: Async (IOSim s) a -> Async (IOSim s) b -> IOSim s () #

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

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

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

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

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

asyncWithUnmask :: ((forall b. IOSim s b -> IOSim s b) -> IOSim s a) -> IOSim s (Async (IOSim s) a) #

asyncOnWithUnmask :: Int -> ((forall b. IOSim s b -> IOSim s b) -> IOSim s a) -> IOSim s (Async (IOSim s) a) #

withAsyncWithUnmask :: ((forall c. IOSim s c -> IOSim s c) -> IOSim s a) -> (Async (IOSim s) a -> IOSim s b) -> IOSim s b #

withAsyncOnWithUnmask :: Int -> ((forall c. IOSim s c -> IOSim s c) -> IOSim s a) -> (Async (IOSim s) a -> IOSim s b) -> IOSim s b #

compareAsyncs :: Async (IOSim s) a -> Async (IOSim s) b -> Ordering #

MonadEventlog (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

traceEventIO :: String -> IOSim s () #

traceMarkerIO :: String -> IOSim s () #

MonadFork (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

forkIO :: IOSim s () -> IOSim s (ThreadId (IOSim s)) #

forkOn :: Int -> IOSim s () -> IOSim s (ThreadId (IOSim s)) #

forkIOWithUnmask :: ((forall a. IOSim s a -> IOSim s a) -> IOSim s ()) -> IOSim s (ThreadId (IOSim s)) #

throwTo :: Exception e => ThreadId (IOSim s) -> e -> IOSim s () #

killThread :: ThreadId (IOSim s) -> IOSim s () #

yield :: IOSim s () #

MonadThread (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type ThreadId (IOSim s) #

Methods

myThreadId :: IOSim s (ThreadId (IOSim s)) #

labelThread :: ThreadId (IOSim s) -> String -> IOSim s () #

MonadMVar (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type MVar (IOSim s) :: Type -> Type #

Methods

newEmptyMVar :: IOSim s (MVar (IOSim s) a) #

takeMVar :: MVar (IOSim s) a -> IOSim s a #

putMVar :: MVar (IOSim s) a -> a -> IOSim s () #

tryTakeMVar :: MVar (IOSim s) a -> IOSim s (Maybe a) #

tryPutMVar :: MVar (IOSim s) a -> a -> IOSim s Bool #

isEmptyMVar :: MVar (IOSim s) a -> IOSim s Bool #

newMVar :: a -> IOSim s (MVar (IOSim s) a) #

readMVar :: MVar (IOSim s) a -> IOSim s a #

tryReadMVar :: MVar (IOSim s) a -> IOSim s (Maybe a) #

swapMVar :: MVar (IOSim s) a -> a -> IOSim s a #

withMVar :: MVar (IOSim s) a -> (a -> IOSim s b) -> IOSim s b #

withMVarMasked :: MVar (IOSim s) a -> (a -> IOSim s b) -> IOSim s b #

modifyMVar_ :: MVar (IOSim s) a -> (a -> IOSim s a) -> IOSim s () #

modifyMVar :: MVar (IOSim s) a -> (a -> IOSim s (a, b)) -> IOSim s b #

modifyMVarMasked_ :: MVar (IOSim s) a -> (a -> IOSim s a) -> IOSim s () #

modifyMVarMasked :: MVar (IOSim s) a -> (a -> IOSim s (a, b)) -> IOSim s b #

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 #

MonadInspectSTM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type InspectMonad (IOSim s) :: Type -> Type #

Methods

inspectTVar :: proxy (IOSim s) -> TVar (IOSim s) a -> InspectMonad (IOSim s) a #

inspectTMVar :: proxy (IOSim s) -> TMVar (IOSim s) a -> InspectMonad (IOSim s) (Maybe a) #

MonadLabelledSTM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

labelTVar :: TVar (IOSim s) a -> String -> STM (IOSim s) () #

labelTMVar :: TMVar (IOSim s) a -> String -> STM (IOSim s) () #

labelTQueue :: TQueue (IOSim s) a -> String -> STM (IOSim s) () #

labelTBQueue :: TBQueue (IOSim s) a -> String -> STM (IOSim s) () #

labelTArray :: (Ix i, Show i) => TArray (IOSim s) i e -> String -> STM (IOSim s) () #

labelTSem :: TSem (IOSim s) -> String -> STM (IOSim s) () #

labelTChan :: TChan (IOSim s) a -> String -> STM (IOSim s) () #

labelTVarIO :: TVar (IOSim s) a -> String -> IOSim s () #

labelTMVarIO :: TMVar (IOSim s) a -> String -> IOSim s () #

labelTQueueIO :: TQueue (IOSim s) a -> String -> IOSim s () #

labelTBQueueIO :: TBQueue (IOSim s) a -> String -> IOSim s () #

labelTArrayIO :: (Ix i, Show i) => TArray (IOSim s) i e -> String -> IOSim s () #

labelTSemIO :: TSem (IOSim s) -> String -> IOSim s () #

labelTChanIO :: TChan (IOSim s) a -> String -> IOSim s () #

MonadSTM (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type STM (IOSim s) = (stm :: Type -> Type) #

type TVar (IOSim s) :: Type -> Type #

type TMVar (IOSim s) :: Type -> Type #

type TQueue (IOSim s) :: Type -> Type #

type TBQueue (IOSim s) :: Type -> Type #

type TArray (IOSim s) :: Type -> Type -> Type #

type TSem (IOSim s) #

type TChan (IOSim s) :: Type -> Type #

Methods

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

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

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

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

retry :: STM (IOSim s) a #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

flushTQueue :: TQueue (IOSim s) a -> STM (IOSim s) [a] #

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

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

unGetTQueue :: TQueue (IOSim s) a -> a -> STM (IOSim s) () #

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

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

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

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

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

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

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

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

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

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

unGetTBQueue :: TBQueue (IOSim s) a -> a -> STM (IOSim s) () #

newTSem :: Integer -> STM (IOSim s) (TSem (IOSim s)) #

waitTSem :: TSem (IOSim s) -> STM (IOSim s) () #

signalTSem :: TSem (IOSim s) -> STM (IOSim s) () #

signalTSemN :: Natural -> TSem (IOSim s) -> STM (IOSim s) () #

newTChan :: STM (IOSim s) (TChan (IOSim s) a) #

newBroadcastTChan :: STM (IOSim s) (TChan (IOSim s) a) #

dupTChan :: TChan (IOSim s) a -> STM (IOSim s) (TChan (IOSim s) a) #

cloneTChan :: TChan (IOSim s) a -> STM (IOSim s) (TChan (IOSim s) a) #

readTChan :: TChan (IOSim s) a -> STM (IOSim s) a #

tryReadTChan :: TChan (IOSim s) a -> STM (IOSim s) (Maybe a) #

peekTChan :: TChan (IOSim s) a -> STM (IOSim s) a #

tryPeekTChan :: TChan (IOSim s) a -> STM (IOSim s) (Maybe a) #

writeTChan :: TChan (IOSim s) a -> a -> STM (IOSim s) () #

unGetTChan :: TChan (IOSim s) a -> a -> STM (IOSim s) () #

isEmptyTChan :: TChan (IOSim s) a -> STM (IOSim s) Bool #

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

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

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

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

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

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

newTChanIO :: IOSim s (TChan (IOSim s) a) #

newBroadcastTChanIO :: IOSim s (TChan (IOSim s) a) #

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) () #

traceTMVar :: proxy (IOSim s) -> TMVar (IOSim s) a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad (IOSim s) TraceValue) -> STM (IOSim s) () #

traceTQueue :: proxy (IOSim s) -> TQueue (IOSim s) a -> (Maybe [a] -> [a] -> InspectMonad (IOSim s) TraceValue) -> STM (IOSim s) () #

traceTBQueue :: proxy (IOSim s) -> TBQueue (IOSim s) a -> (Maybe [a] -> [a] -> InspectMonad (IOSim s) TraceValue) -> STM (IOSim s) () #

traceTSem :: proxy (IOSim s) -> TSem (IOSim s) -> (Maybe Integer -> Integer -> InspectMonad (IOSim s) TraceValue) -> STM (IOSim s) () #

traceTVarIO :: TVar (IOSim s) a -> (Maybe a -> a -> InspectMonad (IOSim s) TraceValue) -> IOSim s () #

traceTMVarIO :: TMVar (IOSim s) a -> (Maybe (Maybe a) -> Maybe a -> InspectMonad (IOSim s) TraceValue) -> IOSim s () #

traceTQueueIO :: TQueue (IOSim s) a -> (Maybe [a] -> [a] -> InspectMonad (IOSim s) TraceValue) -> IOSim s () #

traceTBQueueIO :: TBQueue (IOSim s) a -> (Maybe [a] -> [a] -> InspectMonad (IOSim s) TraceValue) -> IOSim s () #

traceTSemIO :: TSem (IOSim s) -> (Maybe Integer -> Integer -> InspectMonad (IOSim s) TraceValue) -> IOSim s () #

MonadSay (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

say :: String -> IOSim s () #

MonadTest (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

exploreRaces :: IOSim s () #

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 #

catchJust :: Exception e => (e -> Maybe b) -> IOSim s a -> (b -> IOSim s a) -> IOSim s a #

try :: Exception e => IOSim s a -> IOSim s (Either e a) #

tryJust :: Exception e => (e -> Maybe b) -> IOSim s a -> IOSim s (Either b a) #

handle :: Exception e => (e -> IOSim s a) -> IOSim s a -> IOSim s a #

handleJust :: Exception e => (e -> Maybe b) -> (b -> IOSim s a) -> IOSim s a -> IOSim s a #

onException :: IOSim s a -> IOSim s b -> IOSim s a #

bracketOnError :: IOSim s a -> (a -> IOSim s b) -> (a -> IOSim s c) -> IOSim s c #

generalBracket :: IOSim s a -> (a -> ExitCase b -> IOSim s c) -> (a -> IOSim s b) -> IOSim s (b, c) #

MonadEvaluate (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

evaluate :: a -> IOSim s a #

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 #

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

mask_ :: IOSim s a -> IOSim s a #

uninterruptibleMask_ :: IOSim s a -> IOSim s a #

MonadMaskingState (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadThrow (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

throwIO :: Exception e => e -> IOSim s a #

bracket :: IOSim s a -> (a -> IOSim s b) -> (a -> IOSim s c) -> IOSim s c #

bracket_ :: IOSim s a -> IOSim s b -> IOSim s c -> IOSim s c #

finally :: IOSim s a -> IOSim s b -> IOSim s a #

MonadMonotonicTimeNSec (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadTime (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadDelay (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

threadDelay :: Int -> IOSim s () #

MonadTimer (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

registerDelay :: Int -> IOSim s (TVar (IOSim s) Bool) #

timeout :: Int -> IOSim s a -> IOSim s (Maybe a) #

MonadMonotonicTime (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

MonadDelay (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

threadDelay :: DiffTime -> IOSim s () #

MonadTimer (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

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

Defined in Control.Monad.IOSim.Types

Methods

mempty :: IOSim s a #

mappend :: IOSim s a -> IOSim s a -> IOSim s a #

mconcat :: [IOSim s a] -> IOSim s a #

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 #

sconcat :: NonEmpty (IOSim s a) -> IOSim s a #

stimes :: Integral b => b -> IOSim s a -> IOSim s a #

NoThunks (IOSim s a) Source #

Just like the IO instance, we don't actually check anything here

Instance details

Defined in Control.Monad.IOSim.Types

NoThunks a => NoThunks (StrictTVar (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

type Async (IOSim s)
type ThreadId (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type ThreadId (IOSim s)
type MVar (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type MVar (IOSim s)
type InspectMonad (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

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

Defined in Control.Monad.IOSim.Types

type STM (IOSim s)
type TArray (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 TBQueue (IOSim s)
type TChan (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TChan (IOSim s) = TChanDefault (IOSim s)
type TMVar (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

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

Defined in Control.Monad.IOSim.Types

type TQueue (IOSim s)
type TSem (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TSem (IOSim s) = TSemDefault (IOSim s)
type TVar (IOSim s) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type TVar (IOSim s)

type STMSim = STM Source #

Run simulation

runSim :: forall a. (forall s. IOSim s a) -> Either Failure a Source #

IOSim is a pure monad.

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 cleanup policy then this helps testing for that.

data Failure Source #

Simulation terminated a 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.

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.

Instances

Instances details
Exception Failure Source # 
Instance details

Defined in Control.Monad.IOSim

Show Failure Source # 
Instance details

Defined in Control.Monad.IOSim

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

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 MonadTimeout api. The usual quickcheck techniques can help explore different schedules of threads too.

exploreSimTrace Source #

Arguments

:: 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 is slower).

On property failure it will show the failing schedule (ScheduleControl) which can be plugged to controlSimTrace.

controlSimTrace Source #

Arguments

:: 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 ControlDefault or ControlAwait.

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

data ScheduleMod Source #

A schedule modification inserted at given execution step.

Constructors

ScheduleMod 

Fields

data ScheduleControl Source #

Modified execution schedule.

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.

Exploration options

data ExplorationOptions Source #

Race exploration options.

Constructors

ExplorationOptions 

Fields

  • explorationScheduleBound :: Int

    This is an upper bound on the number of schedules with race reversals that will be explored; a bound of zero means that the default schedule will be explored, but no others. Setting the bound to zero makes IOSimPOR behave rather like IOSim, in that only one schedule is explored, but (a) IOSimPOR is considerably slower, because it still collects information on potential races, and (b) the IOSimPOR schedule is different (based on priorities, in contrast to IOSim's round-robin), and plays better with shrinking.

    The default value is `100`.

  • explorationBranching :: Int

    The branching factor. This is the number of alternative schedules that IOSimPOR tries to run, per race reversal. With the default parameters, IOSimPOR will try to reverse the first 33 (100 div 3) races discovered using the default schedule, then (if 33 or more races are discovered), for each such reversed race, will run the reversal and try to reverse two more races in the resulting schedule. A high branching factor will explore more combinations of reversing fewer races, within the overall schedule bound. A branching factor of one will explore only schedules resulting from a single race reversal (unless there are fewer races available to be reversed than the schedule bound).

    The default value is `3`.

  • explorationStepTimelimit :: Maybe Int

    Limit on the computation time allowed per scheduling step, for catching infinite loops etc.

    The default value is Nothing.

  • explorationReplay :: Maybe ScheduleControl

    A schedule to replay.

    The default value is Nothing.

Lift ST computations

liftST :: ST s a -> IOSim s a Source #

Lift an ST computation to IOSim.

Note: you can use MonadST to lift ST computations, this is just a more convenient function just for IOSim.

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.

data Trace a b Source #

A cons list with polymorphic nil.

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

Instances details
Bifoldable Trace Source # 
Instance details

Defined in Data.List.Trace

Methods

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

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Trace a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Trace a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Trace a b -> c #

Bifunctor Trace Source # 
Instance details

Defined in Data.List.Trace

Methods

bimap :: (a -> b) -> (c -> d) -> Trace a c -> Trace b d #

first :: (a -> b) -> Trace a c -> Trace b c #

second :: (b -> c) -> Trace a b -> Trace a c #

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

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

Defined in Data.List.Trace

Methods

fail :: String -> Trace a a0 #

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

Defined in Data.List.Trace

Methods

mfix :: (a0 -> Trace a a0) -> Trace a a0 #

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 #

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 #

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

Defined in Data.List.Trace

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Trace a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Trace a a0] -> ShowS #

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

Defined in Data.List.Trace

Methods

empty :: Trace a a0 #

(<|>) :: Trace a a0 -> Trace a a0 -> Trace a a0 #

some :: Trace a a0 -> Trace a [a0] #

many :: Trace a a0 -> Trace a [a0] #

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

Defined in Data.List.Trace

Methods

pure :: a0 -> Trace a a0 #

(<*>) :: Trace a (a0 -> b) -> Trace a a0 -> Trace a b #

liftA2 :: (a0 -> b -> c) -> Trace a a0 -> Trace a b -> Trace a c #

(*>) :: Trace a a0 -> Trace a b -> Trace a b #

(<*) :: Trace a a0 -> Trace a b -> Trace a a0 #

Functor (Trace a) Source # 
Instance details

Defined in Data.List.Trace

Methods

fmap :: (a0 -> b) -> Trace a a0 -> Trace a b #

(<$) :: a0 -> Trace a b -> Trace a a0 #

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

Defined in Data.List.Trace

Methods

(>>=) :: Trace a a0 -> (a0 -> Trace a b) -> Trace a b #

(>>) :: Trace a a0 -> Trace a b -> Trace a b #

return :: a0 -> Trace a a0 #

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

Defined in Data.List.Trace

Methods

mzero :: Trace a a0 #

mplus :: Trace a a0 -> Trace a a0 -> Trace a a0 #

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

Defined in Data.List.Trace

Methods

mempty :: Trace a b #

mappend :: Trace a b -> Trace a b -> Trace a b #

mconcat :: [Trace a b] -> Trace a b #

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

Defined in Data.List.Trace

Methods

(<>) :: Trace a b -> Trace a b -> Trace a b #

sconcat :: NonEmpty (Trace a b) -> Trace a b #

stimes :: Integral b0 => b0 -> Trace a b -> Trace a b #

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

Defined in Data.List.Trace

Methods

showsPrec :: Int -> Trace a b -> ShowS #

show :: Trace a b -> String #

showList :: [Trace a b] -> ShowS #

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

Defined in Data.List.Trace

Methods

(==) :: Trace a b -> Trace a b -> Bool #

(/=) :: Trace a b -> Trace a b -> Bool #

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

Defined in Data.List.Trace

Methods

compare :: Trace a b -> Trace a b -> Ordering #

(<) :: Trace a b -> Trace a b -> Bool #

(<=) :: Trace a b -> Trace a b -> Bool #

(>) :: Trace a b -> Trace a b -> Bool #

(>=) :: Trace a b -> Trace a b -> Bool #

max :: Trace a b -> Trace a b -> Trace a b #

min :: Trace a b -> Trace a b -> Trace a b #

data SimResult a Source #

A result type of a simulation.

Constructors

MainReturn !Time a ![Labelled ThreadId]

Return value of the main thread.

MainException !Time SomeException ![Labelled ThreadId]

Exception thrown by the main thread.

Deadlock !Time ![Labelled ThreadId]

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 explorationStepTimelimit was exceeded.

Instances

Instances details
Functor SimResult Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Methods

fmap :: (a -> b) -> SimResult a -> SimResult b #

(<$) :: a -> SimResult b -> SimResult a #

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 scheduling, 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 discovered races.

See also: traceEvents, traceResult, selectTraceEvents, selectTraceEventsDynamic and printTraceEventsSay.

Constructors

SimEvent

Used when using IOSim.

Fields

SimPOREvent

Only used for IOSimPOR

Fields

SimRacesFound [ScheduleControl]

Only used for IOSimPOR

Instances

Instances details
Generic SimEvent Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type Rep SimEvent :: Type -> Type #

Methods

from :: SimEvent -> Rep SimEvent x #

to :: Rep SimEvent x -> SimEvent #

Show SimEvent Source # 
Instance details

Defined in Control.Monad.IOSim.Types

type Rep SimEvent Source # 
Instance details

Defined in Control.Monad.IOSim.Types

data SimEventType Source #

Events recorded by the simulation.

Constructors

EventSay String

hold value of say

EventLog Dynamic

hold a dynamic value of traceM

EventMask MaskingState

masking state changed

EventThrow SomeException

throw exception

EventThrowTo SomeException ThreadId

throw asynchronous exception (throwTo)

EventThrowToBlocked

the thread which executed throwTo is blocked

EventThrowToWakeup

the thread which executed throwTo is woken up

EventThrowToUnmasked (Labelled ThreadId)

a target thread of throwTo unmasked its exceptions, this is paired with EventThrowToWakeup for threads which were blocked on throwTo

EventThreadForked ThreadId

forked a thread

EventThreadFinished

thread terminated normally

EventThreadUnhandled SomeException

thread terminated by an unhandled exception

EventTxCommitted

committed STM transaction

Fields

  • [Labelled TVarId]

    stm tx wrote to these

  • [Labelled TVarId]

    and created these

  • (Maybe Effect)

    effect performed (only for IOSimPOR) | aborted an STM transaction (by an exception)

    For IOSimPOR it also holds performed effect.

EventTxAborted (Maybe Effect) 
EventTxBlocked

STM transaction blocked (due to retry)

Fields

  • [Labelled TVarId]
     
  • (Maybe Effect)

    effect performed (only for IOSimPOR)

EventTxWakeup [Labelled TVarId]

changed vars causing retry

EventUnblocked [ThreadId]

unblocked threads by a committed STM transaction

EventThreadDelay TimeoutId Time

thread delayed

EventThreadDelayFired TimeoutId

thread woken up after a delay

EventTimeoutCreated TimeoutId ThreadId Time

new timeout created (via timeout)

EventTimeoutFired TimeoutId

timeout fired

EventRegisterDelayCreated TimeoutId TVarId Time

registered delay (via registerDelay)

EventRegisterDelayFired TimeoutId

registered delay fired

EventTimerCreated TimeoutId TVarId Time

a new Timeout created (via newTimeout)

EventTimerUpdated TimeoutId Time

a Timeout was updated (via updateTimeout)

EventTimerCancelled TimeoutId

a Timeout was cancelled (via cancelTimeout)

EventTimerFired TimeoutId

a Timeout fired

EventThreadStatus

event traced when threadStatus is executed

Fields

  • ThreadId

    current thread

  • ThreadId

    queried thread

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

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 

Instances

Instances details
Show SimEventType Source # 
Instance details

Defined in Control.Monad.IOSim.Types

data Labelled a Source #

A labelled value.

For example labelThread or labelTVar will insert a label to ThreadId (or TVarId).

Constructors

Labelled 

Fields

Instances

Instances details
Generic (Labelled a) Source # 
Instance details

Defined in Control.Monad.IOSim.Types

Associated Types

type Rep (Labelled a) :: Type -> Type #

Methods

from :: Labelled a -> Rep (Labelled a) x #

to :: Rep (Labelled a) x -> Labelled a #

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

Defined in Control.Monad.IOSim.Types

Methods

showsPrec :: Int -> Labelled a -> ShowS #

show :: Labelled a -> String #

showList :: [Labelled a] -> ShowS #

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

Defined in Control.Monad.IOSim.Types

Methods

(==) :: Labelled a -> Labelled a -> Bool #

(/=) :: Labelled a -> Labelled a -> Bool #

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

Defined in Control.Monad.IOSim.Types

Methods

compare :: Labelled a -> Labelled a -> Ordering #

(<) :: Labelled a -> Labelled a -> Bool #

(<=) :: Labelled a -> Labelled a -> Bool #

(>) :: Labelled a -> Labelled a -> Bool #

(>=) :: Labelled a -> Labelled a -> Bool #

max :: Labelled a -> Labelled a -> Labelled a #

min :: Labelled a -> Labelled a -> Labelled a #

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-1.0.0.0-Gi7SlAEf6mz7kE66QCskeU" '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

traceM :: Typeable a => a -> IOSim s () Source #

IOSim has the ability to story any Typeable value in its trace which can then be recovered with selectTraceEventsDynamic or selectTraceEventsDynamic`.

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.

ppTrace_ :: SimTrace a -> String Source #

Like ppTrace but does not show the result value.

ppEvents :: [(Time, ThreadId, Maybe ThreadLabel, SimEventType)] -> String Source #

Pretty print a timestamped event.

ppSimEvent Source #

Arguments

:: Int

width of the time

-> Int

width of thread id

-> Int

width of thread label

-> SimEvent 
-> String 

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, ThreadId, Maybe ThreadLabel, SimEventType)] Source #

Turn SimTrace into a list of timestamped events.

traceResult Source #

Arguments

:: 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 a Failure or the simulation result, i.e. the return value of the main thread.

list selectors

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.

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.

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

newTimeout :: DiffTime -> IOSim s (Timeout s) Source #

readTimeout :: Timeout s -> STM s TimeoutState Source #

cancelTimeout :: Timeout s -> IOSim s () Source #

awaitTimeout :: Timeout s -> STM s Bool Source #