pqueue-1.0.0: Reliable, persistent, fast priority queues.

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Data.PQueue.Prio.Max

Contents

Description

General purpose priority queue, supporting extract-minimum operations. Each element is associated with a key, and the priority queue supports viewing and extracting the element with the minimum key.

An amortized running time is given for each operation, with n referring to the length of the sequence and i being the integral index used by some operations. These bounds hold even in a persistent (shared) setting.

This implementation is based on a binomial heap augmented with a global root. The spine of the heap is maintained lazily.

This implementation does not guarantee stable behavior. Ties are broken arbitrarily -- that is, if k1 <= k2 and k2 <= k1, then there are no guarantees about the relative order in which k1, k2, and their associated elements are returned.

This implementation offers a number of methods of the form xxxU, where U stands for unordered. No guarantees are made on the execution or traversal order of these functions.

Synopsis

Documentation

data MaxPQueue k a Source

A priority queue where values of type a are annotated with keys of type k. The queue supports extracting the element with maximum key.

Instances

Functor (MaxPQueue k) 
Ord k => Foldable (MaxPQueue k) 
Ord k => Traversable (MaxPQueue k) 
(Eq a, Ord k) => Eq (MaxPQueue k a) 
(Ord k, Ord a) => Ord (MaxPQueue k a) 

Construction

empty :: MaxPQueue k aSource

O(1). Returns the empty priority queue.

singleton :: k -> a -> MaxPQueue k aSource

O(1). Constructs a singleton priority queue.

insert :: Ord k => k -> a -> MaxPQueue k a -> MaxPQueue k aSource

Amortized O(1), worst-case O(log n). Inserts an element with the specified key into the queue.

union :: Ord k => MaxPQueue k a -> MaxPQueue k a -> MaxPQueue k aSource

Amortized O(log(min(n1, n2))), worst-case O(log(max(n1, n2))). Returns the union of the two specified queues.

unions :: Ord k => [MaxPQueue k a] -> MaxPQueue k aSource

The union of a list of queues: (unions == foldl union empty).

Query

null :: MaxPQueue k a -> BoolSource

O(1). Checks if this priority queue is empty.

size :: MaxPQueue k a -> IntSource

O(1). Returns the size of this priority queue.

Maximum view

findMax :: MaxPQueue k a -> (k, a)Source

O(1). The maximal (key, element) in the queue. Calls error if empty.

getMax :: MaxPQueue k a -> Maybe (k, a)Source

O(1). The maximal (key, element) in the queue, if the queue is nonempty.

deleteMax :: Ord k => MaxPQueue k a -> MaxPQueue k aSource

O(log n). Delete and find the element with the maximum key. Calls error if empty.

deleteFindMax :: Ord k => MaxPQueue k a -> ((k, a), MaxPQueue k a)Source

O(log n). Delete and find the element with the maximum key. Calls error if empty.

alterMax :: (a -> a) -> MaxPQueue k a -> MaxPQueue k aSource

O(1). Alter the value at the maximum key. If the queue is empty, does nothing.

alterMaxWithKey :: (k -> a -> a) -> MaxPQueue k a -> MaxPQueue k aSource

O(1). Alter the value at the maximum key. If the queue is empty, does nothing.

updateMax :: Ord k => (a -> Maybe a) -> MaxPQueue k a -> MaxPQueue k aSource

O(log n). (Actually O(1) if there's no deletion.) Update the value at the maximum key. If the queue is empty, does nothing.

updateMaxWithKey :: Ord k => (k -> a -> Maybe a) -> MaxPQueue k a -> MaxPQueue k aSource

O(log n). (Actually O(1) if there's no deletion.) Update the value at the maximum key. If the queue is empty, does nothing.

maxView :: Ord k => MaxPQueue k a -> Maybe (a, MaxPQueue k a)Source

O(log n). Retrieves the value associated with the maximum key of the queue, and the queue stripped of that element, or Nothing if passed an empty queue.

maxViewWithKey :: Ord k => MaxPQueue k a -> Maybe ((k, a), MaxPQueue k a)Source

O(log n). Retrieves the maximal (key, value) pair of the map, and the map stripped of that element, or Nothing if passed an empty map.

Traversal

Map

map :: (a -> b) -> MaxPQueue k a -> MaxPQueue k bSource

O(n). Map a function over all values in the queue.

mapWithKey :: (k -> a -> b) -> MaxPQueue k a -> MaxPQueue k bSource

O(n). Map a function over all values in the queue.

mapKeys :: Ord k' => (k -> k') -> MaxPQueue k a -> MaxPQueue k' aSource

O(n). Map a function over all values in the queue.

mapKeysMonotonic :: (k -> k') -> MaxPQueue k a -> MaxPQueue k' aSource

O(n). mapKeysMonotonic f q == mapKeys f q, but only works when f is strictly monotonic. The precondition is not checked. This function has better performance than mapKeys.

Fold

foldrWithKey :: Ord k => (k -> a -> b -> b) -> b -> MaxPQueue k a -> bSource

O(n log n). Fold the keys and values in the map, such that foldrWithKey f z q == foldr (uncurry f) z (toAscList q).

If you do not care about the traversal order, consider using foldrWithKeyU.

foldlWithKey :: Ord k => (b -> k -> a -> b) -> b -> MaxPQueue k a -> bSource

O(n log n). Fold the keys and values in the map, such that foldlWithKey f z q == foldl (uncurry . f) z (toAscList q).

If you do not care about the traversal order, consider using foldlWithKeyU.

Traverse

traverseWithKey :: (Ord k, Applicative f) => (k -> a -> f b) -> MaxPQueue k a -> f (MaxPQueue k b)Source

O(n log n). Traverses the elements of the queue in descending order by key. (traverseWithKey f q == fromDescList $ traverse (uncurry f) (toDescList q))

If you do not care about the order of the traversal, consider using traverseWithKeyU.

Subsets

Indexed

take :: Ord k => Int -> MaxPQueue k a -> [(k, a)]Source

O(k log n). Takes the first k (key, value) pairs in the queue, or the first n if k >= n. (take k q == take k (toDescList q))

drop :: Ord k => Int -> MaxPQueue k a -> MaxPQueue k aSource

O(k log n). Deletes the first k (key, value) pairs in the queue, or returns an empty queue if k >= n.

splitAt :: Ord k => Int -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)Source

O(k log n). Equivalent to (take k q, drop k q).

Predicates

takeWhile :: Ord k => (a -> Bool) -> MaxPQueue k a -> [(k, a)]Source

Takes the longest possible prefix of elements satisfying the predicate. (takeWhile p q == takeWhile (p . snd) (toAscList q))

takeWhileWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> [(k, a)]Source

Takes the longest possible prefix of elements satisfying the predicate. (takeWhile p q == takeWhile (uncurry p) (toAscList q))

dropWhile :: Ord k => (a -> Bool) -> MaxPQueue k a -> MaxPQueue k aSource

Removes the longest possible prefix of elements satisfying the predicate.

dropWhileWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> MaxPQueue k aSource

Removes the longest possible prefix of elements satisfying the predicate.

span :: Ord k => (a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)Source

Equivalent to (takeWhile p q, dropWhile p q).

spanWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)Source

Equivalent to spanWithKey ( k a -> not (p k a)) q.

break :: Ord k => (a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)Source

Equivalent to span (not . p).

breakWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)Source

Equivalent to spanWithKey ( k a -> not (p k a)) q.

Filter

filter :: Ord k => (a -> Bool) -> MaxPQueue k a -> MaxPQueue k aSource

O(n). Filter all values that satisfy the predicate.

filterWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> MaxPQueue k aSource

O(n). Filter all values that satisfy the predicate.

partition :: Ord k => (a -> Bool) -> MaxPQueue k a -> (MaxPQueue k a, MaxPQueue k a)Source

O(n). Partition the queue according to a predicate. The first queue contains all elements which satisfy the predicate, the second all elements that fail the predicate.

partitionWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> (MaxPQueue k a, MaxPQueue k a)Source

O(n). Partition the queue according to a predicate. The first queue contains all elements which satisfy the predicate, the second all elements that fail the predicate.

mapMaybe :: Ord k => (a -> Maybe b) -> MaxPQueue k a -> MaxPQueue k bSource

O(n). Map values and collect the Just results.

mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> MaxPQueue k a -> MaxPQueue k bSource

O(n). Map values and collect the Just results.

mapEither :: Ord k => (a -> Either b c) -> MaxPQueue k a -> (MaxPQueue k b, MaxPQueue k c)Source

O(n). Map values and separate the Left and Right results.

mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> MaxPQueue k a -> (MaxPQueue k b, MaxPQueue k c)Source

O(n). Map values and separate the Left and Right results.

List operations

Conversion from lists

fromList :: Ord k => [(k, a)] -> MaxPQueue k aSource

O(n). Build a priority queue from the list of (key, value) pairs.

fromAscList :: [(k, a)] -> MaxPQueue k aSource

O(n). Build a priority queue from an ascending list of (key, value) pairs. The precondition is not checked.

fromDescList :: [(k, a)] -> MaxPQueue k aSource

O(n). Build a priority queue from a descending list of (key, value) pairs. The precondition is not checked.

Conversion to lists

keys :: Ord k => MaxPQueue k a -> [k]Source

O(n log n). Return all keys of the queue in ascending order.

elems :: Ord k => MaxPQueue k a -> [a]Source

O(n log n). Return all elements of the queue in ascending order by key.

assocs :: Ord k => MaxPQueue k a -> [(k, a)]Source

O(n log n). Equivalent to toDescList.

toAscList :: Ord k => MaxPQueue k a -> [(k, a)]Source

O(n log n). Return all (key, value) pairs in ascending order by key.

toDescList :: Ord k => MaxPQueue k a -> [(k, a)]Source

O(n log n). Return all (key, value) pairs in descending order by key.

toList :: Ord k => MaxPQueue k a -> [(k, a)]Source

O(n log n). Equivalent to toAscList.

If the traversal order is irrelevant, consider using toListU.

Unordered operations

foldrU :: (a -> b -> b) -> b -> MaxPQueue k a -> bSource

O(n). An unordered right fold over the elements of the queue, in no particular order.

foldrWithKeyU :: (k -> a -> b -> b) -> b -> MaxPQueue k a -> bSource

O(n). An unordered right fold over the elements of the queue, in no particular order.

foldlU :: (b -> a -> b) -> b -> MaxPQueue k a -> bSource

O(n). An unordered left fold over the elements of the queue, in no particular order.

foldlWithKeyU :: (b -> k -> a -> b) -> b -> MaxPQueue k a -> bSource

O(n). An unordered left fold over the elements of the queue, in no particular order.

traverseU :: (Applicative f, Ord b) => (a -> f b) -> MaxPQueue k a -> f (MaxPQueue k b)Source

O(n). An unordered traversal over a priority queue, in no particular order. While there is no guarantee in which order the elements are traversed, the resulting priority queue will be perfectly valid.

traverseWithKeyU :: (Applicative f, Ord b) => (k -> a -> f b) -> MaxPQueue k a -> f (MaxPQueue k b)Source

O(n). An unordered traversal over a priority queue, in no particular order. While there is no guarantee in which order the elements are traversed, the resulting priority queue will be perfectly valid.

keysU :: MaxPQueue k a -> [k]Source

O(n). Return all keys of the queue in no particular order.

elemsU :: MaxPQueue k a -> [a]Source

O(n). Return all elements of the queue in no particular order.

assocsU :: MaxPQueue k a -> [(k, a)]Source

O(n). Equivalent to toListU.

toListU :: MaxPQueue k a -> [(k, a)]Source

O(n). Returns all (key, value) pairs in the queue in no particular order.

Helper methods

seqSpine :: MaxPQueue k a -> b -> bSource

O(log n). Analogous to deepseq in the deepseq package, but only forces the spine of the binomial heap.