Safe Haskell | None |
---|---|
Language | Haskell2010 |
Finite priority heaps
The
type represents a finite heap (or priority queue) from keys/priorities of type PrioHeap
k ak
to values of type a
.
A PrioHeap
is strict in its spine. Unlike with maps, duplicate keys/priorities are allowed.
Performance
The worst case running time complexities are given, with n referring the the number of elements in the heap.
Warning
The length of a PrioHeap
must not exceed
.
Violation of this condition is not detected and if the length limit is exceeded, the behaviour of the heap is undefined.maxBound
:: Int
Implementation
The implementation uses skew binomial heaps, as described in
- Chris Okasaki, "Purely Functional Data Structures", 1998
Synopsis
- data PrioHeap k a
- empty :: PrioHeap k a
- singleton :: k -> a -> PrioHeap k a
- fromHeap :: (k -> a) -> Heap k -> PrioHeap k a
- fromList :: Ord k => [(k, a)] -> PrioHeap k a
- insert :: Ord k => k -> a -> PrioHeap k a -> PrioHeap k a
- union :: Ord k => PrioHeap k a -> PrioHeap k a -> PrioHeap k a
- unions :: (Foldable f, Ord k) => f (PrioHeap k a) -> PrioHeap k a
- map :: (a -> b) -> PrioHeap k a -> PrioHeap k b
- mapWithKey :: (k -> a -> b) -> PrioHeap k a -> PrioHeap k b
- traverseWithKey :: Applicative f => (k -> a -> f b) -> PrioHeap k a -> f (PrioHeap k b)
- filter :: Ord k => (a -> Bool) -> PrioHeap k a -> PrioHeap k a
- filterWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> PrioHeap k a
- partition :: Ord k => (a -> Bool) -> PrioHeap k a -> (PrioHeap k a, PrioHeap k a)
- partitionWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> (PrioHeap k a, PrioHeap k a)
- mapMaybe :: Ord k => (a -> Maybe b) -> PrioHeap k a -> PrioHeap k b
- mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> PrioHeap k a -> PrioHeap k b
- mapEither :: Ord k => (a -> Either b c) -> PrioHeap k a -> (PrioHeap k b, PrioHeap k c)
- mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> PrioHeap k a -> (PrioHeap k b, PrioHeap k c)
- foldMapWithKey :: Monoid m => (k -> a -> m) -> PrioHeap k a -> m
- foldlWithKey :: (b -> k -> a -> b) -> b -> PrioHeap k a -> b
- foldrWithKey :: (k -> a -> b -> b) -> b -> PrioHeap k a -> b
- foldlWithKey' :: (b -> k -> a -> b) -> b -> PrioHeap k a -> b
- foldrWithKey' :: (k -> a -> b -> b) -> b -> PrioHeap k a -> b
- foldMapOrd :: (Ord k, Monoid m) => (a -> m) -> PrioHeap k a -> m
- foldlOrd :: Ord k => (b -> a -> b) -> b -> PrioHeap k a -> b
- foldrOrd :: Ord k => (a -> b -> b) -> b -> PrioHeap k a -> b
- foldlOrd' :: Ord k => (b -> a -> b) -> b -> PrioHeap k a -> b
- foldrOrd' :: Ord k => (a -> b -> b) -> b -> PrioHeap k a -> b
- foldMapWithKeyOrd :: (Ord k, Monoid m) => (k -> a -> m) -> PrioHeap k a -> m
- foldlWithKeyOrd :: Ord k => (b -> k -> a -> b) -> b -> PrioHeap k a -> b
- foldrWithKeyOrd :: Ord k => (k -> a -> b -> b) -> b -> PrioHeap k a -> b
- foldlWithKeyOrd' :: Ord k => (b -> k -> a -> b) -> b -> PrioHeap k a -> b
- foldrWithKeyOrd' :: Ord k => (k -> a -> b -> b) -> b -> PrioHeap k a -> b
- size :: PrioHeap k a -> Int
- member :: Ord k => k -> PrioHeap k a -> Bool
- notMember :: Ord k => k -> PrioHeap k a -> Bool
- adjustMin :: (a -> a) -> PrioHeap k a -> PrioHeap k a
- adjustMinWithKey :: (k -> a -> a) -> PrioHeap k a -> PrioHeap k a
- lookupMin :: PrioHeap k a -> Maybe (k, a)
- findMin :: PrioHeap k a -> (k, a)
- deleteMin :: Ord k => PrioHeap k a -> PrioHeap k a
- deleteFindMin :: Ord k => PrioHeap k a -> ((k, a), PrioHeap k a)
- updateMin :: Ord k => (a -> Maybe a) -> PrioHeap k a -> PrioHeap k a
- updateMinWithKey :: Ord k => (k -> a -> Maybe a) -> PrioHeap k a -> PrioHeap k a
- minView :: Ord k => PrioHeap k a -> Maybe ((k, a), PrioHeap k a)
- take :: Ord k => Int -> PrioHeap k a -> [(k, a)]
- drop :: Ord k => Int -> PrioHeap k a -> PrioHeap k a
- splitAt :: Ord k => Int -> PrioHeap k a -> ([(k, a)], PrioHeap k a)
- takeWhile :: Ord k => (a -> Bool) -> PrioHeap k a -> [(k, a)]
- takeWhileWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> [(k, a)]
- dropWhile :: Ord k => (a -> Bool) -> PrioHeap k a -> PrioHeap k a
- dropWhileWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> PrioHeap k a
- span :: Ord k => (a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a)
- spanWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a)
- break :: Ord k => (a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a)
- breakWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a)
- nub :: Ord k => PrioHeap k a -> PrioHeap k a
- keysHeap :: PrioHeap k a -> Heap k
- toList :: PrioHeap k a -> [(k, a)]
- toAscList :: Ord k => PrioHeap k a -> [(k, a)]
- toDescList :: Ord k => PrioHeap k a -> [(k, a)]
Documentation
A skew binomial heap with associated priorities.
Instances
Construction
singleton :: k -> a -> PrioHeap k a Source #
O(1). A heap with a single element.
singleton x = fromList [x]
fromHeap :: (k -> a) -> Heap k -> PrioHeap k a Source #
O(n). Create a heap from a Heap
of keys and a function which computes the value for each key.
From Lists
Insertion/Union
insert :: Ord k => k -> a -> PrioHeap k a -> PrioHeap k a Source #
O(1). Insert a new key and value into the heap.
union :: Ord k => PrioHeap k a -> PrioHeap k a -> PrioHeap k a Source #
O(log n). The union of two heaps.
unions :: (Foldable f, Ord k) => f (PrioHeap k a) -> PrioHeap k a Source #
The union of a foldable of heaps.
unions = foldl union empty
Traversal/Filter
mapWithKey :: (k -> a -> b) -> PrioHeap k a -> PrioHeap k b Source #
O(n). Map a function that has access to the key associated with a value over the heap.
traverseWithKey :: Applicative f => (k -> a -> f b) -> PrioHeap k a -> f (PrioHeap k b) Source #
O(n). Traverse the heap with a function that has access to the key associated with a value.
filter :: Ord k => (a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #
O(n). Filter all elements that satisfy the predicate.
filterWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #
O(n). Filter all elements that satisfy the predicate.
partition :: Ord k => (a -> Bool) -> PrioHeap k a -> (PrioHeap k a, PrioHeap k a) Source #
O(n). Partition the heap into two heaps, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate.
partitionWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> (PrioHeap k a, PrioHeap k a) Source #
O(n). Partition the heap into two heaps, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate.
mapMaybe :: Ord k => (a -> Maybe b) -> PrioHeap k a -> PrioHeap k b Source #
O(n). Map and collect the Just
results.
mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> PrioHeap k a -> PrioHeap k b Source #
O(n). Map and collect the Just
results.
mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> PrioHeap k a -> (PrioHeap k b, PrioHeap k c) Source #
Folds
foldMapWithKey :: Monoid m => (k -> a -> m) -> PrioHeap k a -> m Source #
O(n). Fold the keys and values in the heap, using the given monoid.
foldlWithKey :: (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #
O(n). Fold the keys and values in the heap, using the given left-associative function.
foldrWithKey :: (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #
O(n). Fold the keys and values in the heap, using the given right-associative function.
foldlWithKey' :: (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #
O(n). A strict version of foldlWithKey
.
Each application of the function is evaluated before using the result in the next application.
foldrWithKey' :: (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #
O(n). A strict version of foldrWithKey
.
Each application of the function is evaluated before using the result in the next application.
foldMapOrd :: (Ord k, Monoid m) => (a -> m) -> PrioHeap k a -> m Source #
O(n * log n). Fold the values in the heap in order, using the given monoid.
foldlOrd :: Ord k => (b -> a -> b) -> b -> PrioHeap k a -> b Source #
O(n * log n). Fold the values in the heap in order, using the given left-associative function.
foldrOrd :: Ord k => (a -> b -> b) -> b -> PrioHeap k a -> b Source #
O(n * log n). Fold the values in the heap in order, using the given right-associative function.
foldlOrd' :: Ord k => (b -> a -> b) -> b -> PrioHeap k a -> b Source #
O(n). A strict version of foldlOrd
.
Each application of the function is evaluated before using the result in the next application.
foldrOrd' :: Ord k => (a -> b -> b) -> b -> PrioHeap k a -> b Source #
O(n * log n). A strict version of foldrOrd
.
Each application of the function is evaluated before using the result in the next application.
foldMapWithKeyOrd :: (Ord k, Monoid m) => (k -> a -> m) -> PrioHeap k a -> m Source #
O(n * log n). Fold the keys and values in the heap in order, using the given monoid.
foldlWithKeyOrd :: Ord k => (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #
O(n * log n). Fold the keys and values in the heap in order, using the given left-associative function.
foldrWithKeyOrd :: Ord k => (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #
O(n * log n). Fold the keys and values in the heap in order, using the given right-associative function.
foldlWithKeyOrd' :: Ord k => (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #
O(n). A strict version of foldlWithKeyOrd
.
Each application of the function is evaluated before using the result in the next application.
foldrWithKeyOrd' :: Ord k => (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #
O(n * log n). A strict version of foldrWithKeyOrd
.
Each application of the function is evaluated before using the result in the next application.
Query
notMember :: Ord k => k -> PrioHeap k a -> Bool Source #
O(n). Is the value not a member of the heap?
Min
adjustMin :: (a -> a) -> PrioHeap k a -> PrioHeap k a Source #
O(1). Adjust the value at the minimal key.
adjustMinWithKey :: (k -> a -> a) -> PrioHeap k a -> PrioHeap k a Source #
O(1). Adjust the value at the minimal key.
lookupMin :: PrioHeap k a -> Maybe (k, a) Source #
O(1). The minimal element in the heap or Nothing
if the heap is empty.
findMin :: PrioHeap k a -> (k, a) Source #
O(1). The minimal element in the heap. Calls error
if the heap is empty.
deleteMin :: Ord k => PrioHeap k a -> PrioHeap k a Source #
O(log n). Delete the minimal element. Returns the empty heap if the heap is empty.
deleteFindMin :: Ord k => PrioHeap k a -> ((k, a), PrioHeap k a) Source #
O(log n). Delete and find the minimal element. Calls error
if the heap is empty.
deleteFindMin heap = (findMin heap, deleteMin heap)
updateMin :: Ord k => (a -> Maybe a) -> PrioHeap k a -> PrioHeap k a Source #
O(log n). Update the value at the minimal key.
updateMinWithKey :: Ord k => (k -> a -> Maybe a) -> PrioHeap k a -> PrioHeap k a Source #
O(log n). Update the value at the minimal key.
minView :: Ord k => PrioHeap k a -> Maybe ((k, a), PrioHeap k a) Source #
O(log n). Retrieves the minimal key/value pair of the heap and the heap stripped of that element or Nothing
if the heap is empty.
Subranges
take :: Ord k => Int -> PrioHeap k a -> [(k, a)] Source #
O(n * log n). take n heap
takes the n
smallest elements of heap
, in ascending order.
take n heap = take n (toAscList heap)
drop :: Ord k => Int -> PrioHeap k a -> PrioHeap k a Source #
O(n * log n). drop n heap
drops the n
smallest elements from heap
.
splitAt :: Ord k => Int -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #
O(n * log n). splitAt n heap
takes and drops the n
smallest elements from heap
.
takeWhile :: Ord k => (a -> Bool) -> PrioHeap k a -> [(k, a)] Source #
O(n * log n). takeWhile p heap
takes the elements from heap
in ascending order, while p
holds.
takeWhileWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> [(k, a)] Source #
O(n * log n). takeWhileWithKey p heap
takes the elements from heap
in ascending order, while p
holds.
dropWhile :: Ord k => (a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #
O(n * log n). dropWhile p heap
drops the elements from heap
in ascending order, while p
holds.
dropWhileWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #
O(n * log n). dropWhileWithKey p heap
drops the elements from heap
in ascending order, while p
holds.
span :: Ord k => (a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #
O(n * log n). span p heap
takes and drops the elements from heap
, while p
holds
spanWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #
O(n * log n). spanWithKey p heap
takes and drops the elements from heap
, while p
holds
break :: Ord k => (a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #
O(n * log n). span
, but with inverted predicate.
breakWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #
O(n * log n). spanWithKey
, but with inverted predicate.
nub :: Ord k => PrioHeap k a -> PrioHeap k a Source #
O(n * log n). Remove duplicate elements from the heap.
Conversion
To Lists
toAscList :: Ord k => PrioHeap k a -> [(k, a)] Source #
O(n * log n). Create an ascending list of key/value pairs from the heap.
toDescList :: Ord k => PrioHeap k a -> [(k, a)] Source #
O(n * log n). Create a descending list of key/value pairs from the heap.