| Copyright | (c) 2016--2018 Michael Walker | 
|---|---|
| License | MIT | 
| Maintainer | Michael Walker <mike@barrucadu.co.uk> | 
| Stability | experimental | 
| Portability | ExistentialQuantification, FlexibleContexts, RankNTypes | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
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
- type Threads n = Map ThreadId (Thread n)
- data Thread n = Thread {- _continuation :: Action n
- _blocking :: Maybe BlockedOn
- _handlers :: [Handler n]
- _masking :: MaskingState
- _bound :: Maybe (BoundThread n)
 
- data BoundThread n = BoundThread {- _runboundIO :: MVar n (n (Action n))
- _getboundIO :: MVar n (Action n)
- _boundTId :: ThreadId n
 
- mkthread :: Action n -> Thread n
- data BlockedOn
- (~=) :: Thread n -> BlockedOn -> Bool
- data Handler n = Exception e => Handler (e -> MaskingState -> Action n)
- propagate :: HasCallStack => SomeException -> ThreadId -> Threads n -> Maybe (Threads n)
- interruptible :: Thread n -> Bool
- catching :: (Exception e, HasCallStack) => (e -> Action n) -> ThreadId -> Threads n -> Threads n
- uncatching :: HasCallStack => ThreadId -> Threads n -> Threads n
- except :: HasCallStack => (MaskingState -> Action n) -> [Handler n] -> ThreadId -> Threads n -> Threads n
- mask :: HasCallStack => MaskingState -> ThreadId -> Threads n -> Threads n
- goto :: HasCallStack => Action n -> ThreadId -> Threads n -> Threads n
- launch :: HasCallStack => ThreadId -> ThreadId -> ((forall b. ModelConc n b -> ModelConc n b) -> Action n) -> Threads n -> Threads n
- launch' :: HasCallStack => MaskingState -> ThreadId -> ((forall b. ModelConc n b -> ModelConc n b) -> Action n) -> Threads n -> Threads n
- block :: HasCallStack => BlockedOn -> ThreadId -> Threads n -> Threads n
- wake :: BlockedOn -> Threads n -> (Threads n, [ThreadId])
- makeBound :: (MonadConc n, HasCallStack) => ThreadId -> Threads n -> n (Threads n)
- kill :: (MonadConc n, HasCallStack) => ThreadId -> Threads n -> n (Threads n)
- runLiftedAct :: MonadConc n => ThreadId -> Threads n -> n (Action n) -> n (Action n)
Threads
All the state of a thread.
Constructors
| Thread | |
| Fields 
 | |
data BoundThread n Source #
The state of a bound thread.
Constructors
| BoundThread | |
| Fields 
 | |
Blocking
A BlockedOn is used to determine what sort of variable a thread
 is blocked on.
Constructors
| OnMVarFull MVarId | |
| OnMVarEmpty MVarId | |
| OnTVar [TVarId] | |
| OnMask ThreadId | 
Exceptions
An exception handler.
Constructors
| Exception e => Handler (e -> MaskingState -> 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!
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 :: (MonadConc n, HasCallStack) => ThreadId -> Threads n -> n (Threads n) Source #
Turn a thread into a bound thread.