priority-sync-0.1.0.0: Task prioritization.Source codeContentsIndex
Control.Concurrent.Priority.Queue
Synopsis
data Ord a => Queue a
data TaskHandle a
data QueueOrder
= FIFO
| FILO
data Ord a => QueueConfigurationRecord a = QueueConfigurationRecord {
queue_predicate :: STM ()
priority_indexed_predicate :: a -> STM ()
allowed_priority_inversion :: a -> a -> Bool
allowed_ordering_inversion :: Int
queue_order :: !QueueOrder
}
fair_queue_configuration :: Ord a => QueueConfigurationRecord a
fast_queue_configuration :: Ord a => QueueConfigurationRecord a
newQueue :: Ord a => QueueConfigurationRecord a -> IO (Queue a)
taskPriority :: TaskHandle a -> a
taskQueue :: TaskHandle a -> Queue a
pendingTasks :: Ord a => Queue a -> STM [TaskHandle a]
isTopOfQueue :: TaskHandle a -> STM Bool
hasCompleted :: TaskHandle a -> STM Bool
putTask :: Ord a => Queue a -> a -> STM () -> STM (TaskHandle a)
pullTask :: Ord a => Queue a -> STM (TaskHandle a)
pullFromTop :: Ord a => TaskHandle a -> STM (TaskHandle a)
pullSpecificTasks :: Ord a => [TaskHandle a] -> IO ()
dispatchTasks :: Ord a => [(Queue a, a, STM ())] -> IO [TaskHandle a]
flushQueue :: Ord a => Queue a -> IO ()
load :: Ord a => Queue a -> STM Int
Documentation
data Ord a => Queue a Source

A prioritized Queue. Prioritization is least-first, i.e. larger values are nicer.

A Queue is not associated with any working thread, therefore, it is the client's responsibility to make sure that every pushed task is also pulled, or the Queue will stall. There are several ways to accomplish this:

show/hide Instances
Ord a => Eq (Queue a)
Ord a => Ord (Queue a)
data TaskHandle a Source
show/hide Instances
(Ord a, Eq a) => Eq (TaskHandle a)
Ord a => Ord (TaskHandle a)
data QueueOrder Source
Constructors
FIFO
FILO
data Ord a => QueueConfigurationRecord a Source

Configuration options for a Queue. A Queue blocks on a number of predicates when dispatching a job. Generally, fair_queue_configuration should work well for long-running batch jobs and fast_queue_configuration should work for rapid paced jobs.

  • A single STM predicate for the entire Queue. This blocks the entire Queue until the predicate is satisfied.
  • A STM predicate parameterized by priority. This blocks a single priority level, and the Queue will skip all tasks at that priority.
  • Each task is itself an STM transaction, and can block itself.
  • Pure constraints on priority and ordering inversion.

If a task is blocked for any reason, the task is skipped and the next task attempted, in priority order.

Constructors
QueueConfigurationRecord
queue_predicate :: STM ()A predicate that must hold before any task may be pulled from a Queue.
priority_indexed_predicate :: a -> STM ()A predicate that must hold before any priority level may be pulled from a Queue.
allowed_priority_inversion :: a -> a -> BoolConstrains the greatest allowed difference between the priority of the top-of-queue task and the priority of a task to be pulled.
allowed_ordering_inversion :: IntThe greatest allowed difference between the ideal prioritized FILO/FIFO ordering of tasks and the actual ordering of tasks. Setting this too high can introduce a lot of overhead in the presence of a lot of short-running tasks. Setting this to zero turns off the predicate failover feature, i.e. only the top of queue task will ever be pulled.
queue_order :: !QueueOrderShould the Queue run in FILO or FIFO order. Ordering takes place after prioritization, and won't have much effect if priorities are very fine-grained.
fair_queue_configuration :: Ord a => QueueConfigurationRecord aSource
A queue tuned for high throughput and fairness when processing moderate to long running tasks.
fast_queue_configuration :: Ord a => QueueConfigurationRecord aSource
A queue tuned for high responsiveness and low priority inversion, but may have poorer long-term throughput and potential to starve some tasks compared to fair_queue_configuration.
newQueue :: Ord a => QueueConfigurationRecord a -> IO (Queue a)Source
Create a new Queue.
taskPriority :: TaskHandle a -> aSource
taskQueue :: TaskHandle a -> Queue aSource
pendingTasks :: Ord a => Queue a -> STM [TaskHandle a]Source
isTopOfQueue :: TaskHandle a -> STM BoolSource
True iff this task is poised at the top of it's Queue.
hasCompleted :: TaskHandle a -> STM BoolSource
putTask :: Ord a => Queue a -> a -> STM () -> STM (TaskHandle a)Source
Put a task with it's priority value onto this queue. Returns a handle to the task.
pullTask :: Ord a => Queue a -> STM (TaskHandle a)Source
Pull and commit a task from this Queue.
pullFromTop :: Ord a => TaskHandle a -> STM (TaskHandle a)Source
Pull this task from the top of a Queue, if it is already there. If this task is top-of-queue, but it's predicates fail, then pullFromTop may instead pull a lower-priority TaskHandle.
pullSpecificTasks :: Ord a => [TaskHandle a] -> IO ()Source
Don't return until the given TaskHandles have been pulled from their associated Queues. This doesn't guarantee that the TaskHandle will ever be pulled, even when the TaskHandle and Queue are both viable. You must concurrently arrange for every other TaskHandle associated with the same Queue to be pulled, or the Queue will stall. pullSpecificTasks can handle lists TaskHandles that are distributed among several Queues, as well as a TaskHandles that have already completed or complete concurrently from another thread.
dispatchTasks :: Ord a => [(Queue a, a, STM ())] -> IO [TaskHandle a]Source
"Fire and forget" some tasks on a separate thread.
flushQueue :: Ord a => Queue a -> IO ()Source
Process a Queue until it is empty.
load :: Ord a => Queue a -> STM IntSource
The number of tasks pending on this Queue.
Produced by Haddock version 2.4.2