dejafu-2.1.0.1: A library for unit-testing concurrent programs.

Copyright(c) 2017--2019 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityDeriveGeneric, FlexibleInstances, GeneralizedNewtypeDeriving, LambdaCase, RankNTypes, StandaloneDeriving, TypeFamilies
Safe HaskellNone
LanguageHaskell2010

Test.DejaFu.Types

Contents

Description

Common types and functions used throughout DejaFu.

Synopsis

The MonadDejaFu typeclass

class MonadThrow m => MonadDejaFu m where Source #

The MonadDejaFu class captures the two things needed to run a concurrent program which we can't implement in normal Haskell: mutable references, and the ability to create a bound thread in IO.

In addition to needing the operations in this class, dejafu also needs the ability to throw exceptions, as these are used to communicate Errors, so there is a MonadThrow constraint.

Since: 2.1.0.0

Associated Types

type Ref m :: * -> * Source #

The type of mutable references. These references will always contain a value, and so don't need to handle emptiness (like MVar does).

These references are always used from the same Haskell thread, so it's safe to implement these using unsynchronised primitives with relaxed-memory behaviours (like IORefs).

type BoundThread m :: * -> * Source #

A handle to a bound thread. If the monad doesn't support bound threads (for example, if it's not based on IO), then this should be some type which can't be constructed, like V1.

Methods

newRef :: a -> m (Ref m a) Source #

Create a new reference holding a given initial value.

readRef :: Ref m a -> m a Source #

Read the current value in the reference.

writeRef :: Ref m a -> a -> m () Source #

Replace the value in the reference.

forkBoundThread :: Maybe (m (BoundThread m a)) Source #

Fork a new bound thread, if the monad supports them.

runInBoundThread :: BoundThread m a -> m a -> m a Source #

Run an action in a previously created bound thread.

killBoundThread :: BoundThread m a -> m () Source #

Terminate a previously created bound thread.

After termination, runInBoundThread and killBoundThread will never be called on this BoundThread m a value again.

Instances
MonadDejaFu IO Source #

Since: 2.1.0.0

Instance details

Defined in Test.DejaFu.Types

Associated Types

type Ref IO :: Type -> Type Source #

type BoundThread IO :: Type -> Type Source #

MonadDejaFu (CatchT (ST t)) Source #

This instance does not support bound threads.

Since: 2.1.0.0

Instance details

Defined in Test.DejaFu.Types

Associated Types

type Ref (CatchT (ST t)) :: Type -> Type Source #

type BoundThread (CatchT (ST t)) :: Type -> Type Source #

Methods

newRef :: a -> CatchT (ST t) (Ref (CatchT (ST t)) a) Source #

readRef :: Ref (CatchT (ST t)) a -> CatchT (ST t) a Source #

writeRef :: Ref (CatchT (ST t)) a -> a -> CatchT (ST t) () Source #

forkBoundThread :: Maybe (CatchT (ST t) (BoundThread (CatchT (ST t)) a)) Source #

runInBoundThread :: BoundThread (CatchT (ST t)) a -> CatchT (ST t) a -> CatchT (ST t) a Source #

killBoundThread :: BoundThread (CatchT (ST t)) a -> CatchT (ST t) () Source #

data IOBoundThread a Source #

A bound thread in IO.

Since: 2.1.0.0

Constructors

IOBoundThread 

Fields

Identifiers

newtype ThreadId Source #

Every thread has a unique identitifer.

Since: 1.0.0.0

Constructors

ThreadId Id 
Instances
Eq ThreadId Source # 
Instance details

Defined in Test.DejaFu.Types

Ord ThreadId Source # 
Instance details

Defined in Test.DejaFu.Types

Show ThreadId Source # 
Instance details

Defined in Test.DejaFu.Types

Generic ThreadId Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep ThreadId :: Type -> Type #

Methods

from :: ThreadId -> Rep ThreadId x #

to :: Rep ThreadId x -> ThreadId #

NFData ThreadId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: ThreadId -> () #

type Rep ThreadId Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep ThreadId = D1 (MetaData "ThreadId" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "ThreadId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Id)))

newtype IORefId Source #

Every IORef has a unique identifier.

Since: 1.11.0.0

Constructors

IORefId Id 
Instances
Eq IORefId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: IORefId -> IORefId -> Bool #

(/=) :: IORefId -> IORefId -> Bool #

Ord IORefId Source # 
Instance details

Defined in Test.DejaFu.Types

Show IORefId Source # 
Instance details

Defined in Test.DejaFu.Types

Generic IORefId Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep IORefId :: Type -> Type #

Methods

from :: IORefId -> Rep IORefId x #

to :: Rep IORefId x -> IORefId #

NFData IORefId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: IORefId -> () #

type Rep IORefId Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep IORefId = D1 (MetaData "IORefId" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "IORefId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Id)))

newtype MVarId Source #

Every MVar has a unique identifier.

Since: 1.0.0.0

Constructors

MVarId Id 
Instances
Eq MVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: MVarId -> MVarId -> Bool #

(/=) :: MVarId -> MVarId -> Bool #

Ord MVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Show MVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Generic MVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep MVarId :: Type -> Type #

Methods

from :: MVarId -> Rep MVarId x #

to :: Rep MVarId x -> MVarId #

NFData MVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: MVarId -> () #

type Rep MVarId Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep MVarId = D1 (MetaData "MVarId" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "MVarId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Id)))

newtype TVarId Source #

Every TVar has a unique identifier.

Since: 1.0.0.0

Constructors

TVarId Id 
Instances
Eq TVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: TVarId -> TVarId -> Bool #

(/=) :: TVarId -> TVarId -> Bool #

Ord TVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Show TVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Generic TVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep TVarId :: Type -> Type #

Methods

from :: TVarId -> Rep TVarId x #

to :: Rep TVarId x -> TVarId #

NFData TVarId Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: TVarId -> () #

type Rep TVarId Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep TVarId = D1 (MetaData "TVarId" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "TVarId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Id)))

data Id Source #

An identifier for a thread, MVar, IORef, or TVar.

The number is the important bit. The string is to make execution traces easier to read, but is meaningless.

Since: 1.0.0.0

Constructors

Id (Maybe String) !Int 
Instances
Eq Id Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: Id -> Id -> Bool #

(/=) :: Id -> Id -> Bool #

Ord Id Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

(>=) :: Id -> Id -> Bool #

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Show Id Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Generic Id Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Id :: Type -> Type #

Methods

from :: Id -> Rep Id x #

to :: Rep Id x -> Id #

NFData Id Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: Id -> () #

type Rep Id Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

initialThread :: ThreadId Source #

The ID of the initial thread.

Since: 0.4.0.0

Actions

data ThreadAction Source #

All the actions that a thread can perform.

Since: 2.0.0.0

Constructors

Fork ThreadId

Start a new thread.

ForkOS ThreadId

Start a new bound thread.

SupportsBoundThreads Bool

Check if bound threads are supported.

IsCurrentThreadBound Bool

Check if the current thread is bound.

MyThreadId

Get the ThreadId of the current thread.

GetNumCapabilities Int

Get the number of Haskell threads that can run simultaneously.

SetNumCapabilities Int

Set the number of Haskell threads that can run simultaneously.

Yield

Yield the current thread.

ThreadDelay Int

Yield/delay the current thread.

NewMVar MVarId

Create a new MVar.

PutMVar MVarId [ThreadId]

Put into a MVar, possibly waking up some threads.

BlockedPutMVar MVarId

Get blocked on a put.

TryPutMVar MVarId Bool [ThreadId]

Try to put into a MVar, possibly waking up some threads.

ReadMVar MVarId

Read from a MVar.

TryReadMVar MVarId Bool

Try to read from a MVar.

BlockedReadMVar MVarId

Get blocked on a read.

TakeMVar MVarId [ThreadId]

Take from a MVar, possibly waking up some threads.

BlockedTakeMVar MVarId

Get blocked on a take.

TryTakeMVar MVarId Bool [ThreadId]

Try to take from a MVar, possibly waking up some threads.

NewIORef IORefId

Create a new IORef.

ReadIORef IORefId

Read from a IORef.

ReadIORefCas IORefId

Read from a IORef for a future compare-and-swap.

ModIORef IORefId

Modify a IORef.

ModIORefCas IORefId

Modify a IORef using a compare-and-swap.

WriteIORef IORefId

Write to a IORef without synchronising.

CasIORef IORefId Bool

Attempt to to a IORef using a compare-and-swap, synchronising it.

CommitIORef ThreadId IORefId

Commit the last write to the given IORef by the given thread, so that all threads can see the updated value.

STM [TAction] [ThreadId]

An STM transaction was executed, possibly waking up some threads.

BlockedSTM [TAction]

Got blocked in an STM transaction.

Catching

Register a new exception handler

PopCatching

Pop the innermost exception handler from the stack.

Throw Bool

Throw an exception. If the Bool is True, then this killed the thread.

ThrowTo ThreadId Bool

Throw an exception to a thread. If the Bool is True, then this killed the thread.

BlockedThrowTo ThreadId

Get blocked on a throwTo.

SetMasking Bool MaskingState

Set the masking state. If True, this is being used to set the masking state to the original state in the argument passed to a masked function.

ResetMasking Bool MaskingState

Return to an earlier masking state. If True, this is being used to return to the state of the masked block in the argument passed to a masked function.

LiftIO

Lift an IO action. Note that this can only happen with ConcIO.

Return

A return or pure action was executed.

Stop

Cease execution and terminate.

RegisterInvariant

Register an invariant.

Instances
Eq ThreadAction Source # 
Instance details

Defined in Test.DejaFu.Types

Show ThreadAction Source # 
Instance details

Defined in Test.DejaFu.Types

Generic ThreadAction Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep ThreadAction :: Type -> Type #

NFData ThreadAction Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: ThreadAction -> () #

type Rep ThreadAction Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep ThreadAction = D1 (MetaData "ThreadAction" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (((((C1 (MetaCons "Fork" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId)) :+: C1 (MetaCons "ForkOS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId))) :+: (C1 (MetaCons "SupportsBoundThreads" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: (C1 (MetaCons "IsCurrentThreadBound" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "MyThreadId" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "GetNumCapabilities" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "SetNumCapabilities" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "Yield" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ThreadDelay" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "NewMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)))))) :+: (((C1 (MetaCons "PutMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ThreadId])) :+: C1 (MetaCons "BlockedPutMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId))) :+: (C1 (MetaCons "TryPutMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ThreadId]))) :+: (C1 (MetaCons "ReadMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: C1 (MetaCons "TryReadMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) :+: ((C1 (MetaCons "BlockedReadMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: C1 (MetaCons "TakeMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ThreadId]))) :+: (C1 (MetaCons "BlockedTakeMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: (C1 (MetaCons "TryTakeMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ThreadId]))) :+: C1 (MetaCons "NewIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId))))))) :+: ((((C1 (MetaCons "ReadIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: C1 (MetaCons "ReadIORefCas" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId))) :+: (C1 (MetaCons "ModIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: (C1 (MetaCons "ModIORefCas" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: C1 (MetaCons "WriteIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId))))) :+: ((C1 (MetaCons "CasIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "CommitIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId))) :+: (C1 (MetaCons "STM" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TAction]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ThreadId])) :+: (C1 (MetaCons "BlockedSTM" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TAction])) :+: C1 (MetaCons "Catching" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "PopCatching" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Throw" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: (C1 (MetaCons "ThrowTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: (C1 (MetaCons "BlockedThrowTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId)) :+: C1 (MetaCons "SetMasking" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaskingState))))) :+: ((C1 (MetaCons "ResetMasking" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaskingState)) :+: C1 (MetaCons "LiftIO" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Return" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Stop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RegisterInvariant" PrefixI False) (U1 :: Type -> Type)))))))

data Lookahead Source #

A one-step look-ahead at what a thread will do next.

Since: 2.0.0.0

Constructors

WillFork

Will start a new thread.

WillForkOS

Will start a new bound thread.

WillSupportsBoundThreads

Will check if bound threads are supported.

WillIsCurrentThreadBound

Will check if the current thread is bound.

WillMyThreadId

Will get the ThreadId.

WillGetNumCapabilities

Will get the number of Haskell threads that can run simultaneously.

WillSetNumCapabilities Int

Will set the number of Haskell threads that can run simultaneously.

WillYield

Will yield the current thread.

WillThreadDelay Int

Will yield/delay the current thread.

WillNewMVar

Will create a new MVar.

WillPutMVar MVarId

Will put into a MVar, possibly waking up some threads.

WillTryPutMVar MVarId

Will try to put into a MVar, possibly waking up some threads.

WillReadMVar MVarId

Will read from a MVar.

WillTryReadMVar MVarId

Will try to read from a MVar.

WillTakeMVar MVarId

Will take from a MVar, possibly waking up some threads.

WillTryTakeMVar MVarId

Will try to take from a MVar, possibly waking up some threads.

WillNewIORef

Will create a new IORef.

WillReadIORef IORefId

Will read from a IORef.

WillReadIORefCas IORefId

Will read from a IORef for a future compare-and-swap.

WillModIORef IORefId

Will modify a IORef.

WillModIORefCas IORefId

Will modify a IORef using a compare-and-swap.

WillWriteIORef IORefId

Will write to a IORef without synchronising.

WillCasIORef IORefId

Will attempt to to a IORef using a compare-and-swap, synchronising it.

WillCommitIORef ThreadId IORefId

Will commit the last write by the given thread to the IORef.

WillSTM

Will execute an STM transaction, possibly waking up some threads.

WillCatching

Will register a new exception handler

WillPopCatching

Will pop the innermost exception handler from the stack.

WillThrow

Will throw an exception.

WillThrowTo ThreadId

Will throw an exception to a thread.

WillSetMasking Bool MaskingState

Will set the masking state. If True, this is being used to set the masking state to the original state in the argument passed to a masked function.

WillResetMasking Bool MaskingState

Will return to an earlier masking state. If True, this is being used to return to the state of the masked block in the argument passed to a masked function.

WillLiftIO

Will lift an IO action. Note that this can only happen with ConcIO.

WillReturn

Will execute a return or pure action.

WillStop

Will cease execution and terminate.

WillRegisterInvariant

Will register an invariant

Instances
Eq Lookahead Source # 
Instance details

Defined in Test.DejaFu.Types

Show Lookahead Source # 
Instance details

Defined in Test.DejaFu.Types

Generic Lookahead Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Lookahead :: Type -> Type #

NFData Lookahead Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: Lookahead -> () #

type Rep Lookahead Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep Lookahead = D1 (MetaData "Lookahead" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (((((C1 (MetaCons "WillFork" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WillForkOS" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WillSupportsBoundThreads" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WillIsCurrentThreadBound" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "WillMyThreadId" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WillGetNumCapabilities" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WillSetNumCapabilities" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "WillYield" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "WillThreadDelay" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "WillNewMVar" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WillPutMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: C1 (MetaCons "WillTryPutMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)))) :+: ((C1 (MetaCons "WillReadMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: C1 (MetaCons "WillTryReadMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId))) :+: (C1 (MetaCons "WillTakeMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: (C1 (MetaCons "WillTryTakeMVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MVarId)) :+: C1 (MetaCons "WillNewIORef" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "WillReadIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: C1 (MetaCons "WillReadIORefCas" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId))) :+: (C1 (MetaCons "WillModIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: C1 (MetaCons "WillModIORefCas" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)))) :+: ((C1 (MetaCons "WillWriteIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: C1 (MetaCons "WillCasIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId))) :+: (C1 (MetaCons "WillCommitIORef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IORefId)) :+: (C1 (MetaCons "WillSTM" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WillCatching" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "WillPopCatching" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WillThrow" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WillThrowTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId)) :+: C1 (MetaCons "WillSetMasking" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaskingState)))) :+: ((C1 (MetaCons "WillResetMasking" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaskingState)) :+: C1 (MetaCons "WillLiftIO" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "WillReturn" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "WillStop" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WillRegisterInvariant" PrefixI False) (U1 :: Type -> Type)))))))

data TAction Source #

All the actions that an STM transaction can perform.

Since: 0.8.0.0

Constructors

TNew TVarId

Create a new TVar

TRead TVarId

Read from a TVar.

TWrite TVarId

Write to a TVar.

TRetry

Abort and discard effects.

TOrElse [TAction] (Maybe [TAction])

Execute a transaction. If the transaction aborts by calling retry, execute the other transaction.

TThrow

Throw an exception, abort, and discard effects.

TCatch [TAction] (Maybe [TAction])

Execute a transaction. If the transaction aborts by throwing an exception of the appropriate type, it is handled and execution continues; otherwise aborts, propagating the exception upwards.

TStop

Terminate successfully and commit effects.

Instances
Eq TAction Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: TAction -> TAction -> Bool #

(/=) :: TAction -> TAction -> Bool #

Show TAction Source # 
Instance details

Defined in Test.DejaFu.Types

Generic TAction Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep TAction :: Type -> Type #

Methods

from :: TAction -> Rep TAction x #

to :: Rep TAction x -> TAction #

NFData TAction Source #

Since: 0.5.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: TAction -> () #

type Rep TAction Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

Traces

type Trace = [(Decision, [(ThreadId, Lookahead)], ThreadAction)] Source #

One of the outputs of the runner is a Trace, which is a log of decisions made, all the alternative unblocked threads and what they would do, and the action a thread took in its step.

Since: 0.8.0.0

data Decision Source #

Scheduling decisions are based on the state of the running program, and so we can capture some of that state in recording what specific decision we made.

Since: 0.5.0.0

Constructors

Start ThreadId

Start a new thread, because the last was blocked (or it's the start of computation).

Continue

Continue running the last thread for another step.

SwitchTo ThreadId

Pre-empt the running thread, and switch to another.

Instances
Eq Decision Source # 
Instance details

Defined in Test.DejaFu.Types

Show Decision Source # 
Instance details

Defined in Test.DejaFu.Types

Generic Decision Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Decision :: Type -> Type #

Methods

from :: Decision -> Rep Decision x #

to :: Rep Decision x -> Decision #

NFData Decision Source #

Since: 0.5.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: Decision -> () #

type Rep Decision Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep Decision = D1 (MetaData "Decision" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (C1 (MetaCons "Start" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId)) :+: (C1 (MetaCons "Continue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SwitchTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ThreadId))))

Conditions

data Condition Source #

An indication of how a concurrent computation terminated, if it didn't produce a value.

The Eq, Ord, and NFData instances compare/evaluate the exception with show in the UncaughtException and InvariantFailure cases.

Since: 2.0.0.0

Constructors

Abort

The scheduler chose to abort execution. This will be produced if, for example, all possible decisions exceed the specified bounds (there have been too many pre-emptions, the computation has executed for too long, or there have been too many yields).

Deadlock

Every thread is blocked

UncaughtException SomeException

An uncaught exception bubbled to the top of the computation.

InvariantFailure SomeException

An uncaught exception caused an invariant to fail.

Instances
Eq Condition Source # 
Instance details

Defined in Test.DejaFu.Types

Ord Condition Source # 
Instance details

Defined in Test.DejaFu.Types

Show Condition Source # 
Instance details

Defined in Test.DejaFu.Types

Generic Condition Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Condition :: Type -> Type #

NFData Condition Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: Condition -> () #

type Rep Condition Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep Condition = D1 (MetaData "Condition" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) ((C1 (MetaCons "Abort" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Deadlock" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "UncaughtException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SomeException)) :+: C1 (MetaCons "InvariantFailure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SomeException))))

isAbort :: Condition -> Bool Source #

Check if a condition is an Abort.

Since: 0.9.0.0

isDeadlock :: Condition -> Bool Source #

Check if a condition is a Deadlock.

Since: 0.9.0.0

isUncaughtException :: Condition -> Bool Source #

Check if a condition is an UncaughtException

Since: 0.9.0.0

isInvariantFailure :: Condition -> Bool Source #

Check if a condition is an InvariantFailure

Since: 2.0.0.0

Errors

data Error Source #

An indication that there is a bug in dejafu or you are using it incorrectly.

Since: 2.0.0.0

Constructors

ScheduledBlockedThread

Raised as an exception if the scheduler attempts to schedule a blocked thread.

ScheduledMissingThread

Raised as an exception if the scheduler attempts to schedule a nonexistent thread.

Instances
Bounded Error Source # 
Instance details

Defined in Test.DejaFu.Types

Enum Error Source # 
Instance details

Defined in Test.DejaFu.Types

Eq Error Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Ord Error Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Show Error Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Exception Error Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep Error Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep Error = D1 (MetaData "Error" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (C1 (MetaCons "ScheduledBlockedThread" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ScheduledMissingThread" PrefixI False) (U1 :: Type -> Type))

isSchedulerError :: Error -> Bool Source #

Check if an error is a scheduler error.

Since: 1.12.0.0

Schedule bounding

data Bounds Source #

Since: 2.0.0.0

Instances
Eq Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: Bounds -> Bounds -> Bool #

(/=) :: Bounds -> Bounds -> Bool #

Ord Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

Read Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

Show Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

Generic Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Bounds :: Type -> Type #

Methods

from :: Bounds -> Rep Bounds x #

to :: Rep Bounds x -> Bounds #

NFData Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: Bounds -> () #

type Rep Bounds Source # 
Instance details

Defined in Test.DejaFu.Types

type Rep Bounds = D1 (MetaData "Bounds" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (C1 (MetaCons "Bounds" PrefixI True) (S1 (MetaSel (Just "boundPreemp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PreemptionBound)) :*: S1 (MetaSel (Just "boundFair") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FairBound))))

newtype PreemptionBound Source #

Restrict the number of pre-emptive context switches allowed in an execution.

A pre-emption bound of zero disables pre-emptions entirely.

Since: 0.2.0.0

Constructors

PreemptionBound Int 
Instances
Enum PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Eq PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Integral PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Num PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Ord PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Read PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Real PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Show PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Generic PreemptionBound Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep PreemptionBound :: Type -> Type #

NFData PreemptionBound Source #

Since: 0.5.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: PreemptionBound -> () #

type Rep PreemptionBound Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep PreemptionBound = D1 (MetaData "PreemptionBound" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "PreemptionBound" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype FairBound Source #

Restrict the maximum difference between the number of yield or delay operations different threads have performed.

A fair bound of zero disables yields and delays entirely.

Since: 0.2.0.0

Constructors

FairBound Int 
Instances
Enum FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Eq FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Integral FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Num FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Ord FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Read FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Real FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Show FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Generic FairBound Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep FairBound :: Type -> Type #

NFData FairBound Source #

Since: 0.5.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: FairBound -> () #

type Rep FairBound Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep FairBound = D1 (MetaData "FairBound" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "FairBound" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype LengthBound Source #

Restrict the maximum length (in terms of primitive actions) of an execution.

A length bound of zero immediately aborts the execution.

Since: 0.2.0.0

Constructors

LengthBound Int 
Instances
Enum LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Eq LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Integral LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Num LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Ord LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Read LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Real LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Show LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Generic LengthBound Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep LengthBound :: Type -> Type #

NFData LengthBound Source #

Since: 0.5.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: LengthBound -> () #

type Rep LengthBound Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep LengthBound = D1 (MetaData "LengthBound" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "LengthBound" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

Discarding results and traces

data Discard Source #

An Either Condition a -> Maybe Discard value can be used to selectively discard results.

Since: 0.7.1.0

Constructors

DiscardTrace

Discard the trace but keep the result. The result will appear to have an empty trace.

DiscardResultAndTrace

Discard the result and the trace. It will simply not be reported as a possible behaviour of the program.

Instances
Bounded Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Enum Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Eq Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: Discard -> Discard -> Bool #

(/=) :: Discard -> Discard -> Bool #

Ord Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Read Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Show Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Generic Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep Discard :: Type -> Type #

Methods

from :: Discard -> Rep Discard x #

to :: Rep Discard x -> Discard #

NFData Discard Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: Discard -> () #

type Rep Discard Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep Discard = D1 (MetaData "Discard" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (C1 (MetaCons "DiscardTrace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DiscardResultAndTrace" PrefixI False) (U1 :: Type -> Type))

newtype Weaken a Source #

A monoid for discard functions: combines two functions, keeping the weaker.

Nothing is weaker than Just DiscardTrace, which is weaker than Just DiscardResultAndTrace. This forms a commutative monoid where the unit is const (Just DiscardResultAndTrace).

Since: 1.5.1.0

Constructors

Weaken 
Instances
Contravariant Weaken Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

contramap :: (a -> b) -> Weaken b -> Weaken a #

(>$) :: b -> Weaken b -> Weaken a #

Divisible Weaken Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

divide :: (a -> (b, c)) -> Weaken b -> Weaken c -> Weaken a #

conquer :: Weaken a #

Semigroup (Weaken a) Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(<>) :: Weaken a -> Weaken a -> Weaken a #

sconcat :: NonEmpty (Weaken a) -> Weaken a #

stimes :: Integral b => b -> Weaken a -> Weaken a #

Monoid (Weaken a) Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

mempty :: Weaken a #

mappend :: Weaken a -> Weaken a -> Weaken a #

mconcat :: [Weaken a] -> Weaken a #

weakenDiscard :: (Either Condition a -> Maybe Discard) -> (Either Condition a -> Maybe Discard) -> Either Condition a -> Maybe Discard Source #

Combine two discard functions, keeping the weaker.

Since: 1.0.0.0

newtype Strengthen a Source #

A monoid for discard functions: combines two functions, keeping the stronger.

Just DiscardResultAndTrace is stronger than Just DiscardTrace, which is stronger than Nothing. This forms a commutative monoid where the unit is const Nothing.

Since: 1.5.1.0

Instances
Contravariant Strengthen Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

contramap :: (a -> b) -> Strengthen b -> Strengthen a #

(>$) :: b -> Strengthen b -> Strengthen a #

Divisible Strengthen Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

divide :: (a -> (b, c)) -> Strengthen b -> Strengthen c -> Strengthen a #

conquer :: Strengthen a #

Semigroup (Strengthen a) Source # 
Instance details

Defined in Test.DejaFu.Types

Monoid (Strengthen a) Source # 
Instance details

Defined in Test.DejaFu.Types

strengthenDiscard :: (Either Condition a -> Maybe Discard) -> (Either Condition a -> Maybe Discard) -> Either Condition a -> Maybe Discard Source #

Combine two discard functions, keeping the stronger.

Since: 1.0.0.0

Memory Models

data MemType Source #

The memory model to use for non-synchronised IORef operations.

Since: 0.4.0.0

Constructors

SequentialConsistency

The most intuitive model: a program behaves as a simple interleaving of the actions in different threads. When a IORef is written to, that write is immediately visible to all threads.

TotalStoreOrder

Each thread has a write buffer. A thread sees its writes immediately, but other threads will only see writes when they are committed, which may happen later. Writes are committed in the same order that they are created.

PartialStoreOrder

Each IORef has a write buffer. A thread sees its writes immediately, but other threads will only see writes when they are committed, which may happen later. Writes to different IORefs are not necessarily committed in the same order that they are created.

Instances
Bounded MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Enum MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Eq MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Methods

(==) :: MemType -> MemType -> Bool #

(/=) :: MemType -> MemType -> Bool #

Ord MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Read MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Show MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Generic MemType Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep MemType :: Type -> Type #

Methods

from :: MemType -> Rep MemType x #

to :: Rep MemType x -> MemType #

NFData MemType Source #

Since: 0.5.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: MemType -> () #

type Rep MemType Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep MemType = D1 (MetaData "MemType" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" False) (C1 (MetaCons "SequentialConsistency" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TotalStoreOrder" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PartialStoreOrder" PrefixI False) (U1 :: Type -> Type)))

MonadFail

newtype MonadFailException Source #

An exception for errors in testing caused by use of fail.

Instances
Show MonadFailException Source # 
Instance details

Defined in Test.DejaFu.Types

Generic MonadFailException Source # 
Instance details

Defined in Test.DejaFu.Types

Associated Types

type Rep MonadFailException :: Type -> Type #

Exception MonadFailException Source # 
Instance details

Defined in Test.DejaFu.Types

NFData MonadFailException Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

Methods

rnf :: MonadFailException -> () #

type Rep MonadFailException Source #

Since: 1.3.1.0

Instance details

Defined in Test.DejaFu.Types

type Rep MonadFailException = D1 (MetaData "MonadFailException" "Test.DejaFu.Types" "dejafu-2.1.0.1-HtmfKfFAUia8NliziOK9DG" True) (C1 (MetaCons "MonadFailException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

Concurrency state

data ConcurrencyState Source #

A summary of the concurrency state of the program.

Since: 2.0.0.0

Constructors

ConcurrencyState 

Fields

isBuffered :: ConcurrencyState -> IORefId -> Bool Source #

Check if a IORef has a buffered write pending.

Since: 2.0.0.0

numBuffered :: ConcurrencyState -> IORefId -> Int Source #

Check how many buffered writes an IORef has.

Since: 2.0.0.0

isFull :: ConcurrencyState -> MVarId -> Bool Source #

Check if an MVar is full.

Since: 2.0.0.0

canInterrupt :: ConcurrencyState -> ThreadId -> ThreadAction -> Bool Source #

Check if an exception can interrupt a thread (action).

Since: 2.0.0.0

canInterruptL :: ConcurrencyState -> ThreadId -> Lookahead -> Bool Source #

Check if an exception can interrupt a thread (lookahead).

Since: 2.0.0.0

isMaskedInterruptible :: ConcurrencyState -> ThreadId -> Bool Source #

Check if a thread is masked interruptible.

Since: 2.0.0.0

isMaskedUninterruptible :: ConcurrencyState -> ThreadId -> Bool Source #

Check if a thread is masked uninterruptible.

Since: 2.0.0.0