Control.Concurrent.PriorityChansConverger.PriorityChansConverger
Contents
Description
This module wraps STM PCC with IO. Some locks are added to balance heavyweight transactions, to reduce "waste efforts".
- data PCC_Lock
- data Ord k => PriorityChansConverger k e = PriorityChansConverger {}
- reportIfPossible :: Ord k => PriorityChansConverger k e -> String -> IO ()
- maybeObserveExceptions :: Ord k => PriorityChansConverger k e -> FunctionName -> IO a -> IO a
- newPriorityChansConverger :: Ord k => Map k (StartPriority, ChanCapacity) -> IO (PriorityChansConverger k e)
- newPriorityChansConverger_wCUIS :: Ord k => Maybe ConcurrentUISupport -> Map k (StartPriority, ChanCapacity) -> IO (PriorityChansConverger k e)
- type FunctionName = String
- type LockUserName = FunctionName
- lockPCC :: Ord k => LockUserName -> [PCC_Lock] -> PriorityChansConverger k e -> IO ()
- unlockPCC :: Ord k => LockUserName -> [PCC_Lock] -> PriorityChansConverger k e -> IO ()
- withLockedDo :: Ord k => LockUserName -> [PCC_Lock] -> PriorityChansConverger k e -> IO a -> IO a
- isOfStructPCC :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConverger k e -> IO (PCC_ContainsGivenSpecification, NothingElseIsInStruct)
- mutatePCC :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConverger k e -> IO (PriorityChansConverger k e)
- writeInPCC :: Ord k => PermitToBlock -> k -> e -> PriorityChansConverger k e -> IO (Maybe FailureReasonWPCC)
- stmInterruptableWriteInPCC :: Ord k => STM InterruptShouldWe -> k -> e -> PriorityChansConverger k e -> IO (Either () (Maybe FailureReasonWPCC))
- interruptableWriteInPCC :: Ord k => (Chan a, a -> InterruptShouldWe) -> k -> e -> PriorityChansConverger k e -> IO (Either () (Maybe FailureReasonWPCC))
- readFromPCC :: Ord k => PermitToBlock -> PriorityChansConverger k e -> IO (Maybe (k, e))
- stmInterruptableReadFromPCC :: Ord k => STM InterruptShouldWe -> PriorityChansConverger k e -> IO (Either () (k, e))
- interruptableReadFromPCC :: Ord k => (Chan a, a -> InterruptShouldWe) -> PriorityChansConverger k e -> IO (Either () (k, e))
- flushPCC2List :: Ord k => PriorityChansConverger k e -> IO [(k, e)]
- flushPCC2List' :: Ord k => PriorityChansConverger k e -> IO [(k, e)]
- fastFlushPCC2List' :: Ord k => PriorityChansConverger k e -> IO [(k, e)]
- isEmptyPCC :: Ord k => PriorityChansConverger k e -> IO Bool
- freeSpaceInPCCInput :: Ord k => PriorityChansConverger k e -> k -> IO (Maybe ChanContentAmountMeasure)
- filterOutPCCElements' :: Ord k => PriorityChansConverger k e -> (e -> TakeElementOutShouldWe) -> IO [(k, e)]
- showPCC :: (Ord k, Show k, Show e) => PriorityChansConverger k e -> IO String
PriorityChansConverger ADT and it's administration
Constructors
| PCC_Lock | |
| PCC_IOInterruptableRead | |
| PCC_IOInterruptableWrite |
data Ord k => PriorityChansConverger k e Source
Wrapper around . Added locks. PriorityChansConvergerSTM instance
is defined using Show.
unsafePerformIO
Constructors
| PriorityChansConverger | |
reportIfPossible :: Ord k => PriorityChansConverger k e -> String -> IO ()Source
maybeObserveExceptions :: Ord k => PriorityChansConverger k e -> FunctionName -> IO a -> IO aSource
newPriorityChansConverger :: Ord k => Map k (StartPriority, ChanCapacity) -> IO (PriorityChansConverger k e)Source
Wrapper around constructor.
newPriorityChansConverger_wCUIS
newPriorityChansConverger = newPriorityChansConverger_wCUIS NothingnewPriorityChansConverger_wCUIS :: Ord k => Maybe ConcurrentUISupport -> Map k (StartPriority, ChanCapacity) -> IO (PriorityChansConverger k e)Source
Wrapper around constructor.
With an option to enable utility newPriorityChansConvergerSTM_wCUIS
(which is useful for debugging)
ConcurrentUISupport
type FunctionName = StringSource
type LockUserName = FunctionNameSource
lockPCC :: Ord k => LockUserName -> [PCC_Lock] -> PriorityChansConverger k e -> IO ()Source
Sort the locks and lock them.
WARNING !!! Asynchronous exceptions may cause loss of locks!
unlockPCC :: Ord k => LockUserName -> [PCC_Lock] -> PriorityChansConverger k e -> IO ()Source
Reverse sort the locks and unlock them.
WARNING !!! Asynchronous exceptions may cause loss of locks!
withLockedDo :: Ord k => LockUserName -> [PCC_Lock] -> PriorityChansConverger k e -> IO a -> IO aSource
Locking IO action wrapper.
WARNING !!! Asynchronous exceptions may cause loss of locks!
PriorityChansConverger mutation
isOfStructPCC :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConverger k e -> IO (PCC_ContainsGivenSpecification, NothingElseIsInStruct)Source
Wrapper around . Used locks: none.
isOfStructPCC_STM
mutatePCC :: Ord k => Map k (StartPriority, ChanCapacity) -> PriorityChansConverger k e -> IO (PriorityChansConverger k e)Source
Wrapper around . Used locks: mutatePCC_STM[
PCC_Lock]
PriorityChansConverger I/O
writeInPCC :: Ord k => PermitToBlock -> k -> e -> PriorityChansConverger k e -> IO (Maybe FailureReasonWPCC)Source
Wrapper around . Used locks: if blocking,
then writeInPCC_STM[] else [.
PCC_Lock]
If blocking is enabled, may block, when there is no free space
in .
PriorityChan
stmInterruptableWriteInPCC :: Ord k => STM InterruptShouldWe -> k -> e -> PriorityChansConverger k e -> IO (Either () (Maybe FailureReasonWPCC))Source
Wrapper around . Used locks: interruptableWriteInPCC_STM[]
Blocking write.
Do not put the control of the under STM InterruptShouldWe.
Keep there PCC_LockFalse, if you don't want to get Left () in return.
Put there True, whenever you want to stop waiting.
interruptableWriteInPCC :: Ord k => (Chan a, a -> InterruptShouldWe) -> k -> e -> PriorityChansConverger k e -> IO (Either () (Maybe FailureReasonWPCC))Source
Wrapper around . Used locks: stmInterruptableWriteInPCC[
PCC_IOInterruptableWrite]
Blocking read.
Creates a to control the interruptability of write operation.
Spawns additional thread, which cyclicly reads given TVar BoolChan and checks,
if it signals terminating condition - if so, then using interrupter TVar
stops trying to write in PCC. Temporary thread gets terminated at the end.
readFromPCC :: Ord k => PermitToBlock -> PriorityChansConverger k e -> IO (Maybe (k, e))Source
Wrapper around . Used locks: if blocking, then readFromPCC_STM[] else [.
PCC_Lock]
stmInterruptableReadFromPCC :: Ord k => STM InterruptShouldWe -> PriorityChansConverger k e -> IO (Either () (k, e))Source
Wrapper around . Used locks: interruptableReadFromPCC_STM[]
Blocking read.
interruptableReadFromPCC :: Ord k => (Chan a, a -> InterruptShouldWe) -> PriorityChansConverger k e -> IO (Either () (k, e))Source
Wrapper around . Used locks: stmInterruptableReadFromPCC[
PCC_IOInterruptableRead]
Blocking read.
Creates a to control the interruptability of read operation.
Spawns additional thread, which cyclicly reads given TVar BoolChan and checks,
if it signals terminating condition - if so, then using interrupter TVar
stops trying to write in PCC. Temporary thread gets terminated at the end.
flushPCC2List :: Ord k => PriorityChansConverger k e -> IO [(k, e)]Source
Wrapper around . Used locks: flushPCC2List_STM[
PCC_Lock]
Lazy (doublecheck that).
flushPCC2List' :: Ord k => PriorityChansConverger k e -> IO [(k, e)]Source
Wrapper around flushPCC2List_STM'
(see Control.Concurrent.PriorityChansConverger.PriorityChansConverger).
Used locks: [
PCC_Lock]
Strict. Should be a bit faster than .
flushPCC2List
fastFlushPCC2List' :: Ord k => PriorityChansConverger k e -> IO [(k, e)]Source
Wrapper around fastFlushPCC2List_STM'
(see Control.Concurrent.PriorityChansConverger.PriorityChansConverger).
Used locks: [
PCC_Lock]
Strict. This is a fast flush, it doesn't deal with priorities.
isEmptyPCC :: Ord k => PriorityChansConverger k e -> IO BoolSource
Wrapper around . Used locks: none
isEmptyPCC_STM
freeSpaceInPCCInput :: Ord k => PriorityChansConverger k e -> k -> IO (Maybe ChanContentAmountMeasure)Source
Wrapper around . Used locks: none
freeSpaceInPCCInput_STM
filterOutPCCElements' :: Ord k => PriorityChansConverger k e -> (e -> TakeElementOutShouldWe) -> IO [(k, e)]Source
Wrapper around filterOutPCCElements_STM'
(see Control.Concurrent.PriorityChansConverger.PriorityChansConverger).
Used locks: [
PCC_Lock]
Strict.
Take everything, applu filter, return what's left in the PCC, return what's taken out.