Safe Haskell | None |
---|---|
Language | Haskell2010 |
Finite heaps
The
type represents a finite heap (or priority queue) of elements of type Heap
aa
.
A Heap
is strict in its spine. Unlike with sets, duplicate elements 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 Heap
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 by:
- Chris Okasaki, "Purely Functional Data Structures", 1998.
Synopsis
- data Heap a
- empty :: Heap a
- singleton :: a -> Heap a
- fromList :: Ord a => [a] -> Heap a
- insert :: Ord a => a -> Heap a -> Heap a
- union :: Ord a => Heap a -> Heap a -> Heap a
- unions :: (Foldable f, Ord a) => f (Heap a) -> Heap a
- map :: Ord b => (a -> b) -> Heap a -> Heap b
- mapMonotonic :: (a -> b) -> Heap a -> Heap b
- filter :: Ord a => (a -> Bool) -> Heap a -> Heap a
- partition :: Ord a => (a -> Bool) -> Heap a -> (Heap a, Heap a)
- foldMapOrd :: (Ord a, Monoid m) => (a -> m) -> Heap a -> m
- foldlOrd :: Ord a => (b -> a -> b) -> b -> Heap a -> b
- foldrOrd :: Ord a => (a -> b -> b) -> b -> Heap a -> b
- foldlOrd' :: Ord a => (b -> a -> b) -> b -> Heap a -> b
- foldrOrd' :: Ord a => (a -> b -> b) -> b -> Heap a -> b
- size :: Heap a -> Int
- member :: Ord a => a -> Heap a -> Bool
- notMember :: Ord a => a -> Heap a -> Bool
- lookupMin :: Heap a -> Maybe a
- findMin :: Heap a -> a
- deleteMin :: Ord a => Heap a -> Heap a
- deleteFindMin :: Ord a => Heap a -> (a, Heap a)
- minView :: Ord a => Heap a -> Maybe (a, Heap a)
- take :: Ord a => Int -> Heap a -> [a]
- drop :: Ord a => Int -> Heap a -> Heap a
- splitAt :: Ord a => Int -> Heap a -> ([a], Heap a)
- takeWhile :: Ord a => (a -> Bool) -> Heap a -> [a]
- dropWhile :: Ord a => (a -> Bool) -> Heap a -> Heap a
- span :: Ord a => (a -> Bool) -> Heap a -> ([a], Heap a)
- break :: Ord a => (a -> Bool) -> Heap a -> ([a], Heap a)
- nub :: Ord a => Heap a -> Heap a
- toAscList :: Ord a => Heap a -> [a]
- toDescList :: Ord a => Heap a -> [a]
- heapsort :: Ord a => [a] -> [a]
Documentation
A skew binomial heap.
Instances
Foldable Heap Source # | |
Defined in Data.Heap.Internal fold :: Monoid m => Heap m -> m # foldMap :: Monoid m => (a -> m) -> Heap a -> m # foldMap' :: Monoid m => (a -> m) -> Heap a -> m # foldr :: (a -> b -> b) -> b -> Heap a -> b # foldr' :: (a -> b -> b) -> b -> Heap a -> b # foldl :: (b -> a -> b) -> b -> Heap a -> b # foldl' :: (b -> a -> b) -> b -> Heap a -> b # foldr1 :: (a -> a -> a) -> Heap a -> a # foldl1 :: (a -> a -> a) -> Heap a -> a # elem :: Eq a => a -> Heap a -> Bool # maximum :: Ord a => Heap a -> a # | |
Show1 Heap Source # | |
Ord a => IsList (Heap a) Source # | |
Ord a => Eq (Heap a) Source # | |
Ord a => Ord (Heap a) Source # | |
(Ord a, Read a) => Read (Heap a) Source # | |
Show a => Show (Heap a) Source # | |
Ord a => Semigroup (Heap a) Source # | |
Ord a => Monoid (Heap a) Source # | |
NFData a => NFData (Heap a) Source # | |
Defined in Data.Heap.Internal | |
type Item (Heap a) Source # | |
Defined in Data.Heap.Internal |
Construction
From Lists
Insertion/Union
unions :: (Foldable f, Ord a) => f (Heap a) -> Heap a Source #
The union of a foldable of heaps.
unions = foldl union empty
Traversal/Filter
mapMonotonic :: (a -> b) -> Heap a -> Heap b Source #
O(n), Map an increasing function over the heap. The precondition is not checked.
filter :: Ord a => (a -> Bool) -> Heap a -> Heap a Source #
O(n). Filter all elements that satisfy the predicate.
partition :: Ord a => (a -> Bool) -> Heap a -> (Heap a, Heap 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.
Ordered Folds
foldMapOrd :: (Ord a, Monoid m) => (a -> m) -> Heap a -> m Source #
O(n * log n). Fold the values in the heap in order, using the given monoid.
foldlOrd :: Ord a => (b -> a -> b) -> b -> Heap a -> b Source #
O(n * log n). Fold the values in the heap in order, using the given left-associative function.
foldrOrd :: Ord a => (a -> b -> b) -> b -> Heap a -> b Source #
O(n * log n). Fold the values in the heap in order, using the given right-associative function.
foldlOrd' :: Ord a => (b -> a -> b) -> b -> Heap 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 a => (a -> b -> b) -> b -> Heap 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.
Query
Min
lookupMin :: Heap a -> Maybe a Source #
O(log n). The minimal element in the heap or Nothing
if the heap is empty.
findMin :: Heap a -> a Source #
O(log n). The minimal element in the heap. Calls error
if the heap is empty.
deleteMin :: Ord a => Heap a -> Heap a Source #
O(log n). Delete the minimal element. Returns the empty heap if the heap is empty.
deleteFindMin :: Ord a => Heap a -> (a, Heap a) Source #
O(log n). Delete and find the minimal element. Calls error
if the heap is empty.
deleteFindMin heap = (findMin heap, deleteMin heap)
minView :: Ord a => Heap a -> Maybe (a, Heap a) Source #
O(log n). Retrieves the minimal element of the heap and the heap stripped of that element or Nothing
if the heap is empty.
Subranges
take :: Ord a => Int -> Heap a -> [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 a => Int -> Heap a -> Heap a Source #
O(n * log n). drop n heap
drops the n
smallest elements from heap
.
splitAt :: Ord a => Int -> Heap a -> ([a], Heap a) Source #
O(n * log n). splitAt n heap
takes and drops the n
smallest elements from heap
.
splitAt n heap = (take n heap, drop n heap)
takeWhile :: Ord a => (a -> Bool) -> Heap a -> [a] Source #
O(n * log n). takeWhile p heap
takes the elements from heap
in ascending order, while p
holds.
dropWhile :: Ord a => (a -> Bool) -> Heap a -> Heap a Source #
O(n * log n). dropWhile p heap
drops the elements from heap
in ascending order, while p
holds.
span :: Ord a => (a -> Bool) -> Heap a -> ([a], Heap a) Source #
O(n * log n). span p heap
takes and drops the elements from heap
, while p
holds
span p heap = (takeWhile p heap, dropWhile p heap)
break :: Ord a => (a -> Bool) -> Heap a -> ([a], Heap a) Source #
O(n * log n). span
, but with inverted predicate.
break p = span (not . p)
Conversion
To Lists
toDescList :: Ord a => Heap a -> [a] Source #
O(n * log n). Create a descending list from the heap.