dejafu-2.4.0.5: A library for unit-testing concurrent programs.
Copyright(c) 2016--2020 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityExistentialQuantification, FlexibleContexts, RankNTypes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.DejaFu.Conc.Internal.Threading

Description

Operations and types for threads. This module is NOT considered to form part of the public interface of this library.

Synopsis

Threads

type Threads n = Map ThreadId (Thread n) Source #

Threads are stored in a map index by ThreadId.

data Thread n Source #

All the state of a thread.

Constructors

Thread 

Fields

mkthread :: Action n -> Thread n Source #

Construct a thread with just one action

Blocking

data BlockedOn Source #

A BlockedOn is used to determine what sort of variable a thread is blocked on.

Instances

Instances details
Eq BlockedOn Source # 
Instance details

Defined in Test.DejaFu.Conc.Internal.Threading

(~=) :: Thread n -> BlockedOn -> Bool Source #

Determine if a thread is blocked in a certain way.

Exceptions

data Handler n Source #

An exception handler.

Constructors

forall e.Exception e => Handler MaskingState (e -> Action n) 

propagate :: HasCallStack => SomeException -> ThreadId -> Threads n -> Maybe (Threads n) Source #

Propagate an exception upwards, finding the closest handler which can deal with it.

interruptible :: Thread n -> Bool Source #

Check if a thread can be interrupted by an exception.

catching :: (Exception e, HasCallStack) => (e -> Action n) -> ThreadId -> Threads n -> Threads n Source #

Register a new exception handler.

uncatching :: HasCallStack => ThreadId -> Threads n -> Threads n Source #

Remove the most recent exception handler.

except :: HasCallStack => MaskingState -> Action n -> [Handler n] -> ThreadId -> Threads n -> Threads n Source #

Raise an exception in a thread.

mask :: HasCallStack => MaskingState -> ThreadId -> Threads n -> Threads n Source #

Set the masking state of a thread.

Manipulating threads

goto :: HasCallStack => Action n -> ThreadId -> Threads n -> Threads n Source #

Replace the Action of a thread.

launch :: HasCallStack => ThreadId -> ThreadId -> ((forall b. ModelConc n b -> ModelConc n b) -> Action n) -> Threads n -> Threads n Source #

Start a thread with the given ID, inheriting the masking state from the parent thread. This ID must not already be in use!

launch' :: HasCallStack => MaskingState -> ThreadId -> ((forall b. ModelConc n b -> ModelConc n b) -> Action n) -> Threads n -> Threads n Source #

Start a thread with the given ID and masking state. This must not already be in use!

block :: HasCallStack => BlockedOn -> ThreadId -> Threads n -> Threads n Source #

Block a thread.

wake :: BlockedOn -> Threads n -> (Threads n, [ThreadId]) Source #

Unblock all threads waiting on the appropriate block. For TVar blocks, this will wake all threads waiting on at least one of the given TVars.

Bound threads

makeBound :: (MonadDejaFu n, HasCallStack) => n (BoundThread n (Action n)) -> ThreadId -> Threads n -> n (Threads n) Source #

Turn a thread into a bound thread.

kill :: (MonadDejaFu n, HasCallStack) => ThreadId -> Threads n -> n (Threads n) Source #

Kill a thread and remove it from the thread map.

If the thread is bound, the worker thread is cleaned up.

runLiftedAct :: MonadDejaFu n => ThreadId -> Threads n -> n (Action n) -> n (Action n) Source #

Run an action.

If the thread is bound, the action is run in the worker thread.