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

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

Test.DejaFu.Types

Contents

Description

Common types and functions used throughout DejaFu.

Synopsis

Identifiers

newtype ThreadId Source #

Every thread has a unique identitifer.

Since: 1.0.0.0

Constructors

ThreadId Id 

Instances

Eq ThreadId Source # 
Ord ThreadId Source # 
Show ThreadId Source # 
Generic ThreadId Source #

Since: 1.3.1.0

Associated Types

type Rep ThreadId :: * -> * #

Methods

from :: ThreadId -> Rep ThreadId x #

to :: Rep ThreadId x -> ThreadId #

NFData ThreadId Source # 

Methods

rnf :: ThreadId -> () #

type Rep ThreadId Source # 
type Rep ThreadId = D1 * (MetaData "ThreadId" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "ThreadId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Id)))

newtype CRefId Source #

Every CRef has a unique identifier.

Since: 1.0.0.0

Constructors

CRefId Id 

Instances

Eq CRefId Source # 

Methods

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

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

Ord CRefId Source # 
Show CRefId Source # 
Generic CRefId Source #

Since: 1.3.1.0

Associated Types

type Rep CRefId :: * -> * #

Methods

from :: CRefId -> Rep CRefId x #

to :: Rep CRefId x -> CRefId #

NFData CRefId Source # 

Methods

rnf :: CRefId -> () #

type Rep CRefId Source # 
type Rep CRefId = D1 * (MetaData "CRefId" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "CRefId" PrefixI False) (S1 * (MetaSel (Nothing 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 # 

Methods

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

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

Ord MVarId Source # 
Show MVarId Source # 
Generic MVarId Source #

Since: 1.3.1.0

Associated Types

type Rep MVarId :: * -> * #

Methods

from :: MVarId -> Rep MVarId x #

to :: Rep MVarId x -> MVarId #

NFData MVarId Source # 

Methods

rnf :: MVarId -> () #

type Rep MVarId Source # 
type Rep MVarId = D1 * (MetaData "MVarId" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "MVarId" PrefixI False) (S1 * (MetaSel (Nothing 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 # 

Methods

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

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

Ord TVarId Source # 
Show TVarId Source # 
Generic TVarId Source #

Since: 1.3.1.0

Associated Types

type Rep TVarId :: * -> * #

Methods

from :: TVarId -> Rep TVarId x #

to :: Rep TVarId x -> TVarId #

NFData TVarId Source # 

Methods

rnf :: TVarId -> () #

type Rep TVarId Source # 
type Rep TVarId = D1 * (MetaData "TVarId" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "TVarId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Id)))

data Id Source #

An identifier for a thread, MVar, CRef, 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 # 

Methods

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

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

Ord Id Source # 

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 # 

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Generic Id Source #

Since: 1.3.1.0

Associated Types

type Rep Id :: * -> * #

Methods

from :: Id -> Rep Id x #

to :: Rep Id x -> Id #

NFData Id Source # 

Methods

rnf :: Id -> () #

type Rep Id Source # 
type Rep Id = D1 * (MetaData "Id" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) (C1 * (MetaCons "Id" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe String))) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Int))))

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: 1.4.0.0

Constructors

Fork ThreadId

Start a new thread.

ForkOS ThreadId

Start a new bound thread.

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.

NewCRef CRefId

Create a new CRef.

ReadCRef CRefId

Read from a CRef.

ReadCRefCas CRefId

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

ModCRef CRefId

Modify a CRef.

ModCRefCas CRefId

Modify a CRef using a compare-and-swap.

WriteCRef CRefId

Write to a CRef without synchronising.

CasCRef CRefId Bool

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

CommitCRef ThreadId CRefId

Commit the last write to the given CRef 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

Throw an exception.

ThrowTo ThreadId

Throw an exception to a 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.

Subconcurrency

Start executing an action with subconcurrency.

StopSubconcurrency

Stop executing an action with subconcurrency.

DontCheck Trace

Execute an action with dontCheck.

Instances

Eq ThreadAction Source # 
Show ThreadAction Source # 
Generic ThreadAction Source #

Since: 1.3.1.0

Associated Types

type Rep ThreadAction :: * -> * #

NFData ThreadAction Source # 

Methods

rnf :: ThreadAction -> () #

type Rep ThreadAction Source # 
type Rep ThreadAction = D1 * (MetaData "ThreadAction" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Fork" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId))) (C1 * (MetaCons "ForkOS" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId)))) ((:+:) * (C1 * (MetaCons "IsCurrentThreadBound" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:+:) * (C1 * (MetaCons "MyThreadId" PrefixI False) (U1 *)) (C1 * (MetaCons "GetNumCapabilities" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "SetNumCapabilities" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "Yield" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ThreadDelay" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "NewMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))) (C1 * (MetaCons "PutMVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ThreadId])))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "BlockedPutMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))) (C1 * (MetaCons "TryPutMVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ThreadId])))))) ((:+:) * (C1 * (MetaCons "ReadMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))) ((:+:) * (C1 * (MetaCons "TryReadMVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) (C1 * (MetaCons "BlockedReadMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TakeMVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ThreadId])))) (C1 * (MetaCons "BlockedTakeMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)))) ((:+:) * (C1 * (MetaCons "TryTakeMVar" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ThreadId]))))) ((:+:) * (C1 * (MetaCons "NewCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) (C1 * (MetaCons "ReadCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ReadCRefCas" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) (C1 * (MetaCons "ModCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)))) ((:+:) * (C1 * (MetaCons "ModCRefCas" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) ((:+:) * (C1 * (MetaCons "WriteCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) (C1 * (MetaCons "CasCRef" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CommitCRef" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)))) (C1 * (MetaCons "STM" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TAction])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ThreadId]))))) ((:+:) * (C1 * (MetaCons "BlockedSTM" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TAction]))) ((:+:) * (C1 * (MetaCons "Catching" PrefixI False) (U1 *)) (C1 * (MetaCons "PopCatching" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Throw" PrefixI False) (U1 *)) (C1 * (MetaCons "ThrowTo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId)))) ((:+:) * (C1 * (MetaCons "BlockedThrowTo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId))) ((:+:) * (C1 * (MetaCons "SetMasking" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MaskingState)))) (C1 * (MetaCons "ResetMasking" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MaskingState))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "LiftIO" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Return" PrefixI False) (U1 *)) (C1 * (MetaCons "Stop" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Subconcurrency" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StopSubconcurrency" PrefixI False) (U1 *)) (C1 * (MetaCons "DontCheck" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Trace)))))))))

data Lookahead Source #

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

Since: 1.1.0.0

Constructors

WillFork

Will start a new thread.

WillForkOS

Will start a new bound thread.

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.

WillNewCRef

Will create a new CRef.

WillReadCRef CRefId

Will read from a CRef.

WillReadCRefCas CRefId

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

WillModCRef CRefId

Will modify a CRef.

WillModCRefCas CRefId

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

WillWriteCRef CRefId

Will write to a CRef without synchronising.

WillCasCRef CRefId

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

WillCommitCRef ThreadId CRefId

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

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.

WillSubconcurrency

Will execute an action with subconcurrency.

WillStopSubconcurrency

Will stop executing an extion with subconcurrency.

WillDontCheck

Will execute an action with dontCheck.

Instances

Eq Lookahead Source # 
Show Lookahead Source # 
Generic Lookahead Source #

Since: 1.3.1.0

Associated Types

type Rep Lookahead :: * -> * #

NFData Lookahead Source # 

Methods

rnf :: Lookahead -> () #

type Rep Lookahead Source # 
type Rep Lookahead = D1 * (MetaData "Lookahead" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "WillFork" PrefixI False) (U1 *)) (C1 * (MetaCons "WillForkOS" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "WillIsCurrentThreadBound" PrefixI False) (U1 *)) (C1 * (MetaCons "WillMyThreadId" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "WillGetNumCapabilities" PrefixI False) (U1 *)) (C1 * (MetaCons "WillSetNumCapabilities" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "WillYield" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WillThreadDelay" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "WillNewMVar" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "WillPutMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))) (C1 * (MetaCons "WillTryPutMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)))) ((:+:) * (C1 * (MetaCons "WillReadMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))) (C1 * (MetaCons "WillTryReadMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))))) ((:+:) * ((:+:) * (C1 * (MetaCons "WillTakeMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId))) (C1 * (MetaCons "WillTryTakeMVar" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MVarId)))) ((:+:) * (C1 * (MetaCons "WillNewCRef" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WillReadCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) (C1 * (MetaCons "WillReadCRefCas" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "WillModCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) (C1 * (MetaCons "WillModCRefCas" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)))) ((:+:) * (C1 * (MetaCons "WillWriteCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))) (C1 * (MetaCons "WillCasCRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId))))) ((:+:) * ((:+:) * (C1 * (MetaCons "WillCommitCRef" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CRefId)))) (C1 * (MetaCons "WillSTM" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "WillCatching" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WillPopCatching" PrefixI False) (U1 *)) (C1 * (MetaCons "WillThrow" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "WillThrowTo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId))) (C1 * (MetaCons "WillSetMasking" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MaskingState))))) ((:+:) * (C1 * (MetaCons "WillResetMasking" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MaskingState)))) (C1 * (MetaCons "WillLiftIO" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "WillReturn" PrefixI False) (U1 *)) (C1 * (MetaCons "WillStop" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "WillSubconcurrency" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WillStopSubconcurrency" PrefixI False) (U1 *)) (C1 * (MetaCons "WillDontCheck" PrefixI False) (U1 *))))))))

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 # 

Methods

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

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

Show TAction Source # 
Generic TAction Source #

Since: 1.3.1.0

Associated Types

type Rep TAction :: * -> * #

Methods

from :: TAction -> Rep TAction x #

to :: Rep TAction x -> TAction #

NFData TAction Source #

Since: 0.5.1.0

Methods

rnf :: TAction -> () #

type Rep TAction Source # 

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 # 
Show Decision Source # 
Generic Decision Source #

Since: 1.3.1.0

Associated Types

type Rep Decision :: * -> * #

Methods

from :: Decision -> Rep Decision x #

to :: Rep Decision x -> Decision #

NFData Decision Source #

Since: 0.5.1.0

Methods

rnf :: Decision -> () #

type Rep Decision Source # 
type Rep Decision = D1 * (MetaData "Decision" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) ((:+:) * (C1 * (MetaCons "Start" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId))) ((:+:) * (C1 * (MetaCons "Continue" PrefixI False) (U1 *)) (C1 * (MetaCons "SwitchTo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ThreadId)))))

Failures

data Failure Source #

An indication of how a concurrent computation failed.

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

Since: 1.1.0.0

Constructors

InternalError

Will be raised if the scheduler does something bad. This should never arise unless you write your own, faulty, scheduler! If it does, please file a bug report.

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, and the main thread is not blocked in an STM transaction.

STMDeadlock

Every thread is blocked, and the main thread is blocked in an STM transaction.

UncaughtException SomeException

An uncaught exception bubbled to the top of the computation.

IllegalSubconcurrency

Calls to subconcurrency were nested, or attempted when multiple threads existed.

IllegalDontCheck

A call to dontCheck was attempted after the first action of the initial thread.

Instances

Eq Failure Source # 

Methods

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

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

Ord Failure Source # 
Show Failure Source # 
Generic Failure Source #

Since: 1.3.1.0

Associated Types

type Rep Failure :: * -> * #

Methods

from :: Failure -> Rep Failure x #

to :: Rep Failure x -> Failure #

NFData Failure Source # 

Methods

rnf :: Failure -> () #

type Rep Failure Source # 
type Rep Failure = D1 * (MetaData "Failure" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) ((:+:) * ((:+:) * (C1 * (MetaCons "InternalError" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Abort" PrefixI False) (U1 *)) (C1 * (MetaCons "Deadlock" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "STMDeadlock" PrefixI False) (U1 *)) (C1 * (MetaCons "UncaughtException" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SomeException)))) ((:+:) * (C1 * (MetaCons "IllegalSubconcurrency" PrefixI False) (U1 *)) (C1 * (MetaCons "IllegalDontCheck" PrefixI False) (U1 *)))))

isInternalError :: Failure -> Bool Source #

Check if a failure is an InternalError.

Since: 0.9.0.0

isAbort :: Failure -> Bool Source #

Check if a failure is an Abort.

Since: 0.9.0.0

isDeadlock :: Failure -> Bool Source #

Check if a failure is a Deadlock or an STMDeadlock.

Since: 0.9.0.0

isUncaughtException :: Failure -> Bool Source #

Check if a failure is an UncaughtException

Since: 0.9.0.0

isIllegalSubconcurrency :: Failure -> Bool Source #

Check if a failure is an IllegalSubconcurrency

Since: 0.9.0.0

isIllegalDontCheck :: Failure -> Bool Source #

Check if a failure is an IllegalDontCheck

Since: 1.1.0.0

Schedule bounding

data Bounds Source #

Since: 0.2.0.0

Instances

Eq Bounds Source # 

Methods

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

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

Ord Bounds Source # 
Read Bounds Source # 
Show Bounds Source # 
Generic Bounds Source #

Since: 1.3.1.0

Associated Types

type Rep Bounds :: * -> * #

Methods

from :: Bounds -> Rep Bounds x #

to :: Rep Bounds x -> Bounds #

NFData Bounds Source #

Since: 0.5.1.0

Methods

rnf :: Bounds -> () #

type Rep Bounds Source # 

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 # 
Eq PreemptionBound Source # 
Integral PreemptionBound Source # 
Num PreemptionBound Source # 
Ord PreemptionBound Source # 
Read PreemptionBound Source # 
Real PreemptionBound Source # 
Show PreemptionBound Source # 
Generic PreemptionBound Source #

Since: 1.3.1.0

NFData PreemptionBound Source #

Since: 0.5.1.0

Methods

rnf :: PreemptionBound -> () #

type Rep PreemptionBound Source # 
type Rep PreemptionBound = D1 * (MetaData "PreemptionBound" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "PreemptionBound" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Eq FairBound Source # 
Integral FairBound Source # 
Num FairBound Source # 
Ord FairBound Source # 
Read FairBound Source # 
Real FairBound Source # 
Show FairBound Source # 
Generic FairBound Source #

Since: 1.3.1.0

Associated Types

type Rep FairBound :: * -> * #

NFData FairBound Source #

Since: 0.5.1.0

Methods

rnf :: FairBound -> () #

type Rep FairBound Source # 
type Rep FairBound = D1 * (MetaData "FairBound" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "FairBound" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Eq LengthBound Source # 
Integral LengthBound Source # 
Num LengthBound Source # 
Ord LengthBound Source # 
Read LengthBound Source # 
Real LengthBound Source # 
Show LengthBound Source # 
Generic LengthBound Source #

Since: 1.3.1.0

Associated Types

type Rep LengthBound :: * -> * #

NFData LengthBound Source #

Since: 0.5.1.0

Methods

rnf :: LengthBound -> () #

type Rep LengthBound Source # 
type Rep LengthBound = D1 * (MetaData "LengthBound" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" True) (C1 * (MetaCons "LengthBound" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

Discarding results and traces

data Discard Source #

An Either Failure 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 # 
Enum Discard Source # 
Eq Discard Source # 

Methods

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

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

Ord Discard Source # 
Read Discard Source # 
Show Discard Source # 
Generic Discard Source #

Since: 1.3.1.0

Associated Types

type Rep Discard :: * -> * #

Methods

from :: Discard -> Rep Discard x #

to :: Rep Discard x -> Discard #

NFData Discard Source # 

Methods

rnf :: Discard -> () #

type Rep Discard Source # 
type Rep Discard = D1 * (MetaData "Discard" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) ((:+:) * (C1 * (MetaCons "DiscardTrace" PrefixI False) (U1 *)) (C1 * (MetaCons "DiscardResultAndTrace" PrefixI False) (U1 *)))

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

Combine two discard values, 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.0.0.0

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

Combine two discard 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.0.0.0

Memory Models

data MemType Source #

The memory model to use for non-synchronised CRef 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 CRef 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 CRef 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 CRefs are not necessarily committed in the same order that they are created.

Instances

Bounded MemType Source # 
Enum MemType Source # 
Eq MemType Source # 

Methods

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

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

Ord MemType Source # 
Read MemType Source # 
Show MemType Source # 
Generic MemType Source #

Since: 1.3.1.0

Associated Types

type Rep MemType :: * -> * #

Methods

from :: MemType -> Rep MemType x #

to :: Rep MemType x -> MemType #

NFData MemType Source #

Since: 0.5.1.0

Methods

rnf :: MemType -> () #

type Rep MemType Source # 
type Rep MemType = D1 * (MetaData "MemType" "Test.DejaFu.Types" "dejafu-1.5.0.0-BljEa8FOPeHEm3ajEDl3jK" False) ((:+:) * (C1 * (MetaCons "SequentialConsistency" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TotalStoreOrder" PrefixI False) (U1 *)) (C1 * (MetaCons "PartialStoreOrder" PrefixI False) (U1 *))))

MonadFail