Abbreviation for the PriorityChansConverger
is PCC.
Based on STM.TChan
s, extended with capacity control
(see Control.Concurrent.STM.TChan.TChanB
).
When user reads from the PCC, the choice is made - from which channel to read. System selects a nonempty channel, whose /(CurrentPriority, StartPriority)/ tuple is max. The side effect of the channel selection is it's CurrentPriority decrease by one, if it's value becomes less than one, then the CurrentPriority is set to StartPriority.
- decPriority :: (CurrentPriority, StartPriority) -> (CurrentPriority, StartPriority)
- data Ord k => PriorityChansConvergerSTM k e = PriorityChansConvergerSTM {
- pccStruct :: Map k (PriorityChan k e)
- pccEmpties :: TVar (Map (CurrentPriority, StartPriority) [PriorityChan k e])
- pccNonEmpties :: TVar (Map (CurrentPriority, StartPriority) [PriorityChan k e])
- pccConcurrentUISupport :: Maybe ConcurrentUISupport
- data PriorityChan k e = PriorityChan {
- pcID :: k
- pcChanB :: TChanB e
- pcPriorityTV :: TVar (CurrentPriority, StartPriority)
- pcLoad :: PriorityChan k e -> STM ChanLoad
- pcCapacity :: PriorityChan k e -> STM ChanCapacity
- pcIsEmpty :: PriorityChan k e -> STM Bool
- pcPriority :: PriorityChan k e -> STM (CurrentPriority, StartPriority)
- pcStartPriority :: PriorityChan k e -> STM StartPriority
- newPriorityChan :: k -> StartPriority -> ChanCapacity -> STM (PriorityChan k e)
- newPriorityChansConvergerSTM_wCUIS :: Ord k => Maybe ConcurrentUISupport -> Map k (StartPriority, ChanCapacity) -> STM (PriorityChansConvergerSTM k e)
- newPriorityChansConvergerSTM :: Ord k => Map k (StartPriority, ChanCapacity) -> STM (PriorityChansConvergerSTM k e)
- isOfStructPCC_STM :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConvergerSTM k e -> STM (PCC_ContainsGivenSpecification, NothingElseIsInStruct)
- mutatePCC_STM :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConvergerSTM k e -> STM (PriorityChansConvergerSTM k e)
- writeInPCC_STM :: Ord k => PermitToBlock -> k -> e -> PriorityChansConvergerSTM k e -> STM (Maybe FailureReasonWPCC)
- interruptableWriteInPCC_STM :: Ord k => STM InterruptShouldWe -> k -> e -> PriorityChansConvergerSTM k e -> STM (Either () (Maybe FailureReasonWPCC))
- readFromPCC_STM :: Ord k => PermitToBlock -> PriorityChansConvergerSTM k e -> STM (Maybe (k, e))
- interruptableReadFromPCC_STM :: Ord k => STM InterruptShouldWe -> PriorityChansConvergerSTM k e -> STM (Either () (k, e))
- flushPCC2List_STM :: Ord k => PriorityChansConvergerSTM k e -> STM [(k, e)]
- flushPCC2List_STM' :: Ord k => PriorityChansConvergerSTM k e -> STM [(k, e)]
- fastFlushPCC2List_STM' :: Ord k => PriorityChansConvergerSTM k e -> STM [(k, e)]
- isEmptyPCC_STM :: Ord k => PriorityChansConvergerSTM k e -> STM Bool
- freeSpaceInPCCInput_STM :: Ord k => PriorityChansConvergerSTM k e -> k -> STM (Maybe ChanContentAmountMeasure)
- filterOutPCCElements_STM' :: Ord k => PriorityChansConvergerSTM k e -> (e -> TakeElementOutShouldWe) -> STM [(k, e)]
- showPCC_STM :: (Ord k, Show k, Show e) => PriorityChansConvergerSTM k e -> STM String
- showPC_STM :: (Show e, Show k) => PriorityChan k e -> STM String
- interruptableSTM :: STM InterruptShouldWe -> STM a -> STM (Maybe a)
PriorityChansConverger ADT and it's administration
decPriority :: (CurrentPriority, StartPriority) -> (CurrentPriority, StartPriority)Source
Decrease
by one, if it's value becomes
less than one, then the CurrentPriority
is set to CurrentPriority
.
StartPriority
data Ord k => PriorityChansConvergerSTM k e Source
PriorityChansConvergerSTM | |
|
data PriorityChan k e Source
PriorityChan = ID +
+ TChanB
TVar
(CurrentPriority
, StartPriority
)
PriorityChan | |
|
pcCapacity :: PriorityChan k e -> STM ChanCapacitySource
pcIsEmpty :: PriorityChan k e -> STM BoolSource
pcPriority :: PriorityChan k e -> STM (CurrentPriority, StartPriority)Source
pcStartPriority :: PriorityChan k e -> STM StartPrioritySource
pcStartPriority
pc = sndliftM
pcPriority
pc
newPriorityChan :: k -> StartPriority -> ChanCapacity -> STM (PriorityChan k e)Source
Constructor.
newPriorityChansConvergerSTM_wCUIS :: Ord k => Maybe ConcurrentUISupport -> Map k (StartPriority, ChanCapacity) -> STM (PriorityChansConvergerSTM k e)Source
PCC constructor with an option to enable utility
(which is useful for debugging).
ConcurrentUISupport
newPriorityChansConvergerSTM :: Ord k => Map k (StartPriority, ChanCapacity) -> STM (PriorityChansConvergerSTM k e)Source
PCC constructor.
is off.
ConcurrentUISupport
newPriorityChansConvergerSTM = newPriorityChansConvergerSTM_wCUIS
Nothing
PriorityChansConvergerSTM mutation
isOfStructPCC_STM :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConvergerSTM k e -> STM (PCC_ContainsGivenSpecification, NothingElseIsInStruct)Source
Checks:
- If PCC contains all channels, constructable by given specification.
- If PCC contains nothing else, than mentioned in the given specification.
mutatePCC_STM :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConvergerSTM k e -> STM (PriorityChansConvergerSTM k e)Source
Updates PCC with given specification. New channels may be added or existing alerted. But no operation for removing channels.
PriorityChansConvergerSTM I/O
writeInPCC_STM :: Ord k => PermitToBlock -> k -> e -> PriorityChansConvergerSTM k e -> STM (Maybe FailureReasonWPCC)Source
If blocking is on, then blocks, when trying to write to a full channel (where's no free space).
interruptableWriteInPCC_STM :: Ord k => STM InterruptShouldWe -> k -> e -> PriorityChansConvergerSTM k e -> STM (Either () (Maybe FailureReasonWPCC))Source
Wrapper around (
- blocking write.
Uses writeInPCC_STM
True)interruptableSTM
. If returns Left, then transaction ended with
interrupting condition.
readFromPCC_STM :: Ord k => PermitToBlock -> PriorityChansConvergerSTM k e -> STM (Maybe (k, e))Source
If
is PermitToBlock
True
, then never returns Nothing
.
interruptableReadFromPCC_STM :: Ord k => STM InterruptShouldWe -> PriorityChansConvergerSTM k e -> STM (Either () (k, e))Source
Wrapper around (
- blocking read.
Uses readFromPCC_STM
True)interruptableSTM
. If returns Left, then transaction ended with
interrupting condition.
flushPCC2List_STM :: Ord k => PriorityChansConvergerSTM k e -> STM [(k, e)]Source
Composition of
s. Lazy (doublecheck that).
readFromPCC_STM
flushPCC2List_STM' :: Ord k => PriorityChansConvergerSTM k e -> STM [(k, e)]Source
Strict. Should be a bit faster than
.
flushPCC2List_STM
fastFlushPCC2List_STM' :: Ord k => PriorityChansConvergerSTM k e -> STM [(k, e)]Source
Strict. This is a fast flush, it doesn't deal with priorities.
isEmptyPCC_STM :: Ord k => PriorityChansConvergerSTM k e -> STM BoolSource
freeSpaceInPCCInput_STM :: Ord k => PriorityChansConvergerSTM k e -> k -> STM (Maybe ChanContentAmountMeasure)Source
Free space in referenced channel = Capacity - Load.
filterOutPCCElements_STM' :: Ord k => PriorityChansConvergerSTM k e -> (e -> TakeElementOutShouldWe) -> STM [(k, e)]Source
Strict.
Take everything, applu filter, return what's left in the PCC, return what's taken out.
PriorityChansConvergerSTM representation
showPCC_STM :: (Ord k, Show k, Show e) => PriorityChansConvergerSTM k e -> STM StringSource
Used wrapped in (unsafePerformIO . atomically)
in the definition
of show instance.
showPC_STM :: (Show e, Show k) => PriorityChan k e -> STM StringSource
Used wrapped in (unsafePerformIO . atomically)
in the definition
of show instance.
Helpers
interruptableSTM :: STM InterruptShouldWe -> STM a -> STM (Maybe a)Source
For interruptableSTM interrupter subj
, when interrupter
returns True
,
the transaction returns Nothing
. Else the result of subj
is waited
and returned wrapped into Just
.