Copyright | (c) Louis Wasserman 2010 |
---|---|
License | BSD-style |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
General purpose priority queue. Each element is associated with a key, and the priority queue supports viewing and extracting the element with the maximum key.
A worst-case bound is given for each operation. In some cases, an amortized bound is also specified; these bounds do not hold in a persistent context.
This implementation is based on a binomial heap augmented with a global root.
The spine of the heap is maintained lazily. To force the spine of the heap,
use seqSpine
.
We do 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. (Unlike Data.Map, we allow multiple elements with the
same key.)
This implementation offers a number of methods of the form xxxU
, where U
stands for
unordered. No guarantees whatsoever are made on the execution or traversal order of
these functions.
- data MaxPQueue k a
- empty :: MaxPQueue k a
- singleton :: k -> a -> MaxPQueue k a
- insert :: Ord k => k -> a -> MaxPQueue k a -> MaxPQueue k a
- insertBehind :: Ord k => k -> a -> MaxPQueue k a -> MaxPQueue k a
- union :: Ord k => MaxPQueue k a -> MaxPQueue k a -> MaxPQueue k a
- unions :: Ord k => [MaxPQueue k a] -> MaxPQueue k a
- null :: MaxPQueue k a -> Bool
- size :: MaxPQueue k a -> Int
- findMax :: MaxPQueue k a -> (k, a)
- getMax :: MaxPQueue k a -> Maybe (k, a)
- deleteMax :: Ord k => MaxPQueue k a -> MaxPQueue k a
- deleteFindMax :: Ord k => MaxPQueue k a -> ((k, a), MaxPQueue k a)
- adjustMax :: (a -> a) -> MaxPQueue k a -> MaxPQueue k a
- adjustMaxWithKey :: (k -> a -> a) -> MaxPQueue k a -> MaxPQueue k a
- updateMax :: Ord k => (a -> Maybe a) -> MaxPQueue k a -> MaxPQueue k a
- updateMaxWithKey :: Ord k => (k -> a -> Maybe a) -> MaxPQueue k a -> MaxPQueue k a
- maxView :: Ord k => MaxPQueue k a -> Maybe (a, MaxPQueue k a)
- maxViewWithKey :: Ord k => MaxPQueue k a -> Maybe ((k, a), MaxPQueue k a)
- map :: (a -> b) -> MaxPQueue k a -> MaxPQueue k b
- mapWithKey :: (k -> a -> b) -> MaxPQueue k a -> MaxPQueue k b
- mapKeys :: Ord k' => (k -> k') -> MaxPQueue k a -> MaxPQueue k' a
- mapKeysMonotonic :: (k -> k') -> MaxPQueue k a -> MaxPQueue k' a
- foldrWithKey :: Ord k => (k -> a -> b -> b) -> b -> MaxPQueue k a -> b
- foldlWithKey :: Ord k => (b -> k -> a -> b) -> b -> MaxPQueue k a -> b
- traverseWithKey :: (Ord k, Applicative f) => (k -> a -> f b) -> MaxPQueue k a -> f (MaxPQueue k b)
- take :: Ord k => Int -> MaxPQueue k a -> [(k, a)]
- drop :: Ord k => Int -> MaxPQueue k a -> MaxPQueue k a
- splitAt :: Ord k => Int -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)
- takeWhile :: Ord k => (a -> Bool) -> MaxPQueue k a -> [(k, a)]
- takeWhileWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> [(k, a)]
- dropWhile :: Ord k => (a -> Bool) -> MaxPQueue k a -> MaxPQueue k a
- dropWhileWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> MaxPQueue k a
- span :: Ord k => (a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)
- spanWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)
- break :: Ord k => (a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)
- breakWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> ([(k, a)], MaxPQueue k a)
- filter :: Ord k => (a -> Bool) -> MaxPQueue k a -> MaxPQueue k a
- filterWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> MaxPQueue k a
- partition :: Ord k => (a -> Bool) -> MaxPQueue k a -> (MaxPQueue k a, MaxPQueue k a)
- partitionWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> (MaxPQueue k a, MaxPQueue k a)
- mapMaybe :: Ord k => (a -> Maybe b) -> MaxPQueue k a -> MaxPQueue k b
- mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> MaxPQueue k a -> MaxPQueue k b
- mapEither :: Ord k => (a -> Either b c) -> MaxPQueue k a -> (MaxPQueue k b, MaxPQueue k c)
- mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> MaxPQueue k a -> (MaxPQueue k b, MaxPQueue k c)
- fromList :: Ord k => [(k, a)] -> MaxPQueue k a
- fromAscList :: [(k, a)] -> MaxPQueue k a
- fromDescList :: [(k, a)] -> MaxPQueue k a
- keys :: Ord k => MaxPQueue k a -> [k]
- elems :: Ord k => MaxPQueue k a -> [a]
- assocs :: Ord k => MaxPQueue k a -> [(k, a)]
- toAscList :: Ord k => MaxPQueue k a -> [(k, a)]
- toDescList :: Ord k => MaxPQueue k a -> [(k, a)]
- toList :: Ord k => MaxPQueue k a -> [(k, a)]
- foldrU :: (a -> b -> b) -> b -> MaxPQueue k a -> b
- foldrWithKeyU :: (k -> a -> b -> b) -> b -> MaxPQueue k a -> b
- foldlU :: (b -> a -> b) -> b -> MaxPQueue k a -> b
- foldlWithKeyU :: (b -> k -> a -> b) -> b -> MaxPQueue k a -> b
- traverseU :: Applicative f => (a -> f b) -> MaxPQueue k a -> f (MaxPQueue k b)
- traverseWithKeyU :: Applicative f => (k -> a -> f b) -> MaxPQueue k a -> f (MaxPQueue k b)
- keysU :: MaxPQueue k a -> [k]
- elemsU :: MaxPQueue k a -> [a]
- assocsU :: MaxPQueue k a -> [(k, a)]
- toListU :: MaxPQueue k a -> [(k, a)]
- seqSpine :: MaxPQueue k a -> b -> b
Documentation
A priority queue where values of type a
are annotated with keys of type k
.
The queue supports extracting the element with maximum key.
Construction
insert :: Ord k => k -> a -> MaxPQueue k a -> MaxPQueue k a Source #
Amortized O(1), worst-case O(log n). Inserts an element with the specified key into the queue.
insertBehind :: Ord k => k -> a -> MaxPQueue k a -> MaxPQueue k a Source #
Amortized O(1), worst-case O(log n). Insert an element into the priority queue, putting it behind elements that compare equal to the inserted one.
union :: Ord k => MaxPQueue k a -> MaxPQueue k a -> MaxPQueue k a Source #
Amortized O(log(min(n1, n2))), worst-case O(log(max(n1, n2))). Returns the union of the two specified queues.
Query
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 a Source #
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.
adjustMax :: (a -> a) -> MaxPQueue k a -> MaxPQueue k a Source #
O(1). Alter the value at the maximum key. If the queue is empty, does nothing.
adjustMaxWithKey :: (k -> a -> a) -> MaxPQueue k a -> MaxPQueue k a Source #
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 a Source #
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 a Source #
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 b Source #
O(n). Map a function over all values in the queue.
mapWithKey :: (k -> a -> b) -> MaxPQueue k a -> MaxPQueue k b Source #
O(n). Map a function over all values in the queue.
mapKeys :: Ord k' => (k -> k') -> MaxPQueue k a -> MaxPQueue k' a Source #
O(n). Map a function over all values in the queue.
mapKeysMonotonic :: (k -> k') -> MaxPQueue k a -> MaxPQueue k' a Source #
O(n).
, but only works when mapKeysMonotonic
f q == mapKeys
f qf
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 -> b Source #
O(n log n). Fold the keys and values in the map, such that
.foldrWithKey
f z q == foldr
(uncurry
f) z (toDescList
q)
If you do not care about the traversal order, consider using foldrWithKeyU
.
foldlWithKey :: Ord k => (b -> k -> a -> b) -> b -> MaxPQueue k a -> b Source #
O(n log n). Fold the keys and values in the map, such that
.foldlWithKey
f z q == foldl
(uncurry
. f) z (toDescList
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 a Source #
O(k log n). Deletes the first k
(key, value) pairs in the queue, or returns an empty queue if k >= n
.
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
) (toDescList
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) (toDescList
q)
dropWhile :: Ord k => (a -> Bool) -> MaxPQueue k a -> MaxPQueue k a Source #
Removes the longest possible prefix of elements satisfying the predicate.
dropWhileWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> MaxPQueue k a Source #
Removes the longest possible prefix of elements satisfying the predicate.
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
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 a Source #
O(n). Filter all values that satisfy the predicate.
filterWithKey :: Ord k => (k -> a -> Bool) -> MaxPQueue k a -> MaxPQueue k a Source #
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 b Source #
O(n). Map values and collect the Just
results.
mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> MaxPQueue k a -> MaxPQueue k b Source #
O(n). Map values and collect the Just
results.
mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> MaxPQueue k a -> (MaxPQueue k b, MaxPQueue k c) Source #
List operations
Conversion from lists
fromList :: Ord k => [(k, a)] -> MaxPQueue k a Source #
O(n). Build a priority queue from the list of (key, value) pairs.
fromAscList :: [(k, a)] -> MaxPQueue k a Source #
O(n). Build a priority queue from an ascending list of (key, value) pairs. The precondition is not checked.
fromDescList :: [(k, a)] -> MaxPQueue k a Source #
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 descending order.
elems :: Ord k => MaxPQueue k a -> [a] Source #
O(n log n). Return all elements of the queue in descending order by key.
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 toDescList
.
If the traversal order is irrelevant, consider using toListU
.
Unordered operations
foldrU :: (a -> b -> b) -> b -> MaxPQueue k a -> b Source #
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 -> b Source #
O(n). An unordered right fold over the elements of the queue, in no particular order.
foldlU :: (b -> a -> b) -> b -> MaxPQueue k a -> b Source #
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 -> b Source #
O(n). An unordered left fold over the elements of the queue, in no particular order.
traverseU :: Applicative f => (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 => (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.
elemsU :: MaxPQueue k a -> [a] Source #
O(n). Return all elements of the queue in no particular order.
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 -> b Source #
O(log n). Analogous to deepseq
in the deepseq
package, but only forces the spine of the binomial heap.