Copyright | (c) Edward Kmett 2010-2015 |
---|---|
License | BSD-style |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
An efficient, asymptotically optimal, implementation of a priority queues
extended with support for efficient size, and Foldable
Note: Since many function names (but not the type name) clash with
Prelude names, this module is usually imported qualified
, e.g.
import Data.Heap (Heap) import qualified Data.Heap as Heap
The implementation of Heap
is based on bootstrapped skew binomial heaps
as described by:
- G. Brodal and C. Okasaki , "Optimal Purely Functional Priority Queues", Journal of Functional Programming 6:839-857 (1996)
All time bounds are worst-case.
Synopsis
- data Heap a
- data Entry p a = Entry {}
- empty :: Heap a
- null :: Foldable t => t a -> Bool
- size :: Heap a -> Int
- singleton :: Ord a => a -> Heap a
- insert :: Ord a => a -> Heap a -> Heap a
- minimum :: Heap a -> a
- deleteMin :: Heap a -> Heap a
- union :: Heap a -> Heap a -> Heap a
- uncons :: Heap a -> Maybe (a, Heap a)
- viewMin :: Heap a -> Maybe (a, Heap a)
- mapMonotonic :: Ord b => (a -> b) -> Heap a -> Heap b
- map :: Ord b => (a -> b) -> Heap a -> Heap b
- toUnsortedList :: Heap a -> [a]
- fromList :: Ord a => [a] -> Heap a
- sort :: Ord a => [a] -> [a]
- traverse :: (Applicative t, Ord b) => (a -> t b) -> Heap a -> t (Heap b)
- mapM :: (Monad m, Ord b) => (a -> m b) -> Heap a -> m (Heap b)
- concatMap :: (a -> Heap b) -> Heap a -> Heap b
- filter :: (a -> Bool) -> Heap a -> Heap a
- partition :: (a -> Bool) -> Heap a -> (Heap a, Heap a)
- split :: a -> Heap a -> (Heap a, Heap a, Heap a)
- break :: (a -> Bool) -> Heap a -> (Heap a, Heap a)
- span :: (a -> Bool) -> Heap a -> (Heap a, Heap a)
- take :: Int -> Heap a -> Heap a
- drop :: Int -> Heap a -> Heap a
- splitAt :: Int -> Heap a -> (Heap a, Heap a)
- takeWhile :: (a -> Bool) -> Heap a -> Heap a
- dropWhile :: (a -> Bool) -> Heap a -> Heap a
- group :: Heap a -> Heap (Heap a)
- groupBy :: (a -> a -> Bool) -> Heap a -> Heap (Heap a)
- nub :: Heap a -> Heap a
- intersect :: Heap a -> Heap a -> Heap a
- intersectWith :: Ord b => (a -> a -> b) -> Heap a -> Heap a -> Heap b
- replicate :: Ord a => a -> Int -> Heap a
Heap Type
A min-heap of values of type a
.
Instances
Foldable Heap Source # | |
Defined in Data.Heap fold :: Monoid m => Heap m -> 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 # | |
Eq (Heap a) Source # | |
(Ord a, Data a) => Data (Heap a) Source # | |
Defined in Data.Heap gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Heap a -> c (Heap a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Heap a) # toConstr :: Heap a -> Constr # dataTypeOf :: Heap a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Heap a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Heap a)) # gmapT :: (forall b. Data b => b -> b) -> Heap a -> Heap a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Heap a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Heap a -> r # gmapQ :: (forall d. Data d => d -> u) -> Heap a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Heap a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Heap a -> m (Heap a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Heap a -> m (Heap a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Heap a -> m (Heap a) # | |
Ord (Heap a) Source # | |
(Ord a, Read a) => Read (Heap a) Source # | |
Show a => Show (Heap a) Source # | |
Semigroup (Heap a) Source # | |
Monoid (Heap a) Source # | |
Entry type
Explicit priority/payload tuples. Useful to build a priority queue using
a Heap
, since the payload is ignored in the Eq/Ord instances.
myHeap =fromList
[Entry
2 "World",Entry
1 "Hello",Entry
3 "!"] ==>foldMap
payload
myHeap ≡ "HelloWorld!"
Instances
Bifunctor Entry Source # | |
Functor (Entry p) Source # | |
Foldable (Entry p) Source # | |
Defined in Data.Heap fold :: Monoid m => Entry p m -> m # foldMap :: Monoid m => (a -> m) -> Entry p a -> m # foldr :: (a -> b -> b) -> b -> Entry p a -> b # foldr' :: (a -> b -> b) -> b -> Entry p a -> b # foldl :: (b -> a -> b) -> b -> Entry p a -> b # foldl' :: (b -> a -> b) -> b -> Entry p a -> b # foldr1 :: (a -> a -> a) -> Entry p a -> a # foldl1 :: (a -> a -> a) -> Entry p a -> a # elem :: Eq a => a -> Entry p a -> Bool # maximum :: Ord a => Entry p a -> a # minimum :: Ord a => Entry p a -> a # | |
Traversable (Entry p) Source # | |
Eq p => Eq (Entry p a) Source # | |
(Data p, Data a) => Data (Entry p a) Source # | |
Defined in Data.Heap gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Entry p a -> c (Entry p a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Entry p a) # toConstr :: Entry p a -> Constr # dataTypeOf :: Entry p a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Entry p a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Entry p a)) # gmapT :: (forall b. Data b => b -> b) -> Entry p a -> Entry p a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Entry p a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Entry p a -> r # gmapQ :: (forall d. Data d => d -> u) -> Entry p a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Entry p a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Entry p a -> m (Entry p a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Entry p a -> m (Entry p a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Entry p a -> m (Entry p a) # | |
Ord p => Ord (Entry p a) Source # | |
Defined in Data.Heap | |
(Read p, Read a) => Read (Entry p a) Source # | |
(Show p, Show a) => Show (Entry p a) Source # | |
Basic functions
null :: Foldable t => t a -> Bool #
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
size :: Heap a -> Int Source #
O(1). The number of elements in the heap.
>>>
size empty
0>>>
size (singleton "hello")
1>>>
size (fromList [4,1,2])
3
minimum :: Heap a -> a Source #
O(1). Assumes the argument is a non-null
heap.
>>>
minimum (fromList [3,1,2])
1
deleteMin :: Heap a -> Heap a Source #
O(log n). Delete the minimum key from the heap and return the resulting heap.
>>>
deleteMin (fromList [3,1,2])
fromList [2,3]
union :: Heap a -> Heap a -> Heap a Source #
O(1). Meld the values from two heaps into one heap.
>>>
union (fromList [1,3,5]) (fromList [6,4,2])
fromList [1,2,6,4,3,5]>>>
union (fromList [1,1,1]) (fromList [1,2,1])
fromList [1,1,1,2,1,1]
uncons :: Heap a -> Maybe (a, Heap a) Source #
Provides both O(1) access to the minimum element and O(log n) access to the remainder of the heap.
This is the same operation as viewMin
>>>
uncons (fromList [2,1,3])
Just (1,fromList [2,3])
Transformations
mapMonotonic :: Ord b => (a -> b) -> Heap a -> Heap b Source #
O(n). Map a monotone increasing function over the heap.
Provides a better constant factor for performance than map
, but no checking is performed that the function provided is monotone increasing. Misuse of this function can cause a Heap to violate the heap property.
>>>
mapMonotonic (+1) (fromList [1,2,3])
fromList [2,3,4]>>>
mapMonotonic (*2) (fromList [1,2,3])
fromList [2,4,6]
map :: Ord b => (a -> b) -> Heap a -> Heap b Source #
O(n). Map a function over the heap, returning a new heap ordered appropriately for its fresh contents
>>>
map negate (fromList [3,1,2])
fromList [-3,-1,-2]
To/From Lists
toUnsortedList :: Heap a -> [a] Source #
O(n). Returns the elements in the heap in some arbitrary, very likely unsorted, order.
>>>
toUnsortedList (fromList [3,1,2])
[1,3,2]
fromList
.
toUnsortedList
≡id
traverse :: (Applicative t, Ord b) => (a -> t b) -> Heap a -> t (Heap b) Source #
O(n log n). Traverse the elements of the heap in sorted order and produce a new heap using Applicative
side-effects.
mapM :: (Monad m, Ord b) => (a -> m b) -> Heap a -> m (Heap b) Source #
O(n log n). Traverse the elements of the heap in sorted order and produce a new heap using Monad
ic side-effects.
concatMap :: (a -> Heap b) -> Heap a -> Heap b Source #
O(n). Construct heaps from each element in another heap, and union them together.
>>>
concatMap (\a -> fromList [a,a+1]) (fromList [1,4])
fromList [1,4,5,2]
Filtering
filter :: (a -> Bool) -> Heap a -> Heap a Source #
O(n). Filter the heap, retaining only values that satisfy the predicate.
>>>
filter (>'a') (fromList "ab")
fromList "b">>>
filter (>'x') (fromList "ab")
fromList []>>>
filter (<'a') (fromList "ab")
fromList []
partition :: (a -> Bool) -> Heap a -> (Heap a, Heap a) Source #
O(n). Partition the heap according to a predicate. The first heap contains all elements that satisfy the predicate, the second all elements that fail the predicate. See also split
.
>>>
partition (>'a') (fromList "ab")
(fromList "b",fromList "a")
split :: a -> Heap a -> (Heap a, Heap a, Heap a) Source #
O(n). Partition the heap into heaps of the elements that are less than, equal to, and greater than a given value.
>>>
split 'h' (fromList "hello")
(fromList "e",fromList "h",fromList "llo")
break :: (a -> Bool) -> Heap a -> (Heap a, Heap a) Source #
O(n log n). break
applied to a predicate p
and a heap xs
returns a tuple where the first element is a heap consisting of the
longest prefix the least elements of xs
that do not satisfy p and the second element is the remainder of the elements in the heap.
>>>
break (\x -> x `mod` 4 == 0) (fromList [3,5,7,12,13,16])
(fromList [3,5,7],fromList [12,13,16])
span :: (a -> Bool) -> Heap a -> (Heap a, Heap a) Source #
O(n log n). span
applied to a predicate p
and a heap xs
returns a tuple where the first element is a heap consisting of the
longest prefix the least elements of xs that satisfy p
and the second element is the remainder of the elements in the heap.
>>>
span (\x -> x `mod` 4 == 0) (fromList [4,8,12,14,16])
(fromList [4,8,12],fromList [14,16])
take :: Int -> Heap a -> Heap a Source #
O(n log n). Return a heap consisting of the least n
elements of a given heap.
>>>
take 3 (fromList [10,2,4,1,9,8,2])
fromList [1,2,2]
drop :: Int -> Heap a -> Heap a Source #
O(n log n). Return a heap consisting of all members of given heap except for the n
least elements.
splitAt :: Int -> Heap a -> (Heap a, Heap a) Source #
O(n log n). Split a heap into two heaps, the first containing the n
least elements, the latter consisting of all members of the heap except for those elements.
takeWhile :: (a -> Bool) -> Heap a -> Heap a Source #
O(n log n). takeWhile
applied to a predicate p
and a heap xs
returns a heap consisting of the
longest prefix the least elements of xs
that satisfy p
.
>>>
takeWhile (\x -> x `mod` 4 == 0) (fromList [4,8,12,14,16])
fromList [4,8,12]
Grouping
group :: Heap a -> Heap (Heap a) Source #
O(n log n). Group a heap into a heap of heaps, by unioning together duplicates.
>>>
group (fromList "hello")
fromList [fromList "e",fromList "h",fromList "ll",fromList "o"]
groupBy :: (a -> a -> Bool) -> Heap a -> Heap (Heap a) Source #
O(n log n). Group using a user supplied function.
nub :: Heap a -> Heap a Source #
O(n log n). Remove duplicate entries from the heap.
>>>
nub (fromList [1,1,2,6,6])
fromList [1,2,6]
Intersection
intersect :: Heap a -> Heap a -> Heap a Source #
O(n log n + m log m). Intersect the values in two heaps, returning the value in the left heap that compares as equal
intersectWith :: Ord b => (a -> a -> b) -> Heap a -> Heap a -> Heap b Source #
O(n log n + m log m). Intersect the values in two heaps using a function to generate the elements in the right heap.