heaps-0.4: Asymptotically optimal Brodal/Okasaki heaps.
Copyright(c) Edward Kmett 2010-2015
LicenseBSD-style
Maintainerekmett@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Heap

Description

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:

All time bounds are worst-case.

Synopsis

Heap Type

data Heap a Source #

A min-heap of values of type a.

Instances

Instances details
Foldable Heap Source # 
Instance details

Defined in Data.Heap

Methods

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 #

toList :: Heap a -> [a] #

null :: Heap a -> Bool #

length :: Heap a -> Int #

elem :: Eq a => a -> Heap a -> Bool #

maximum :: Ord a => Heap a -> a #

minimum :: Ord a => Heap a -> a #

sum :: Num a => Heap a -> a #

product :: Num a => Heap a -> a #

Eq (Heap a) Source # 
Instance details

Defined in Data.Heap

Methods

(==) :: Heap a -> Heap a -> Bool #

(/=) :: Heap a -> Heap a -> Bool #

(Ord a, Data a) => Data (Heap a) Source # 
Instance details

Defined in Data.Heap

Methods

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 :: forall r r'. (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 # 
Instance details

Defined in Data.Heap

Methods

compare :: Heap a -> Heap a -> Ordering #

(<) :: Heap a -> Heap a -> Bool #

(<=) :: Heap a -> Heap a -> Bool #

(>) :: Heap a -> Heap a -> Bool #

(>=) :: Heap a -> Heap a -> Bool #

max :: Heap a -> Heap a -> Heap a #

min :: Heap a -> Heap a -> Heap a #

(Ord a, Read a) => Read (Heap a) Source # 
Instance details

Defined in Data.Heap

Show a => Show (Heap a) Source # 
Instance details

Defined in Data.Heap

Methods

showsPrec :: Int -> Heap a -> ShowS #

show :: Heap a -> String #

showList :: [Heap a] -> ShowS #

Semigroup (Heap a) Source # 
Instance details

Defined in Data.Heap

Methods

(<>) :: Heap a -> Heap a -> Heap a #

sconcat :: NonEmpty (Heap a) -> Heap a #

stimes :: Integral b => b -> Heap a -> Heap a #

Monoid (Heap a) Source # 
Instance details

Defined in Data.Heap

Methods

mempty :: Heap a #

mappend :: Heap a -> Heap a -> Heap a #

mconcat :: [Heap a] -> Heap a #

Entry type

data Entry p a Source #

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!"

Constructors

Entry 

Fields

Instances

Instances details
Bifunctor Entry Source # 
Instance details

Defined in Data.Heap

Methods

bimap :: (a -> b) -> (c -> d) -> Entry a c -> Entry b d #

first :: (a -> b) -> Entry a c -> Entry b c #

second :: (b -> c) -> Entry a b -> Entry a c #

Functor (Entry p) Source # 
Instance details

Defined in Data.Heap

Methods

fmap :: (a -> b) -> Entry p a -> Entry p b #

(<$) :: a -> Entry p b -> Entry p a #

Foldable (Entry p) Source # 
Instance details

Defined in Data.Heap

Methods

fold :: Monoid m => Entry p m -> m #

foldMap :: Monoid m => (a -> m) -> Entry p a -> 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 #

toList :: Entry p a -> [a] #

null :: Entry p a -> Bool #

length :: Entry p a -> Int #

elem :: Eq a => a -> Entry p a -> Bool #

maximum :: Ord a => Entry p a -> a #

minimum :: Ord a => Entry p a -> a #

sum :: Num a => Entry p a -> a #

product :: Num a => Entry p a -> a #

Traversable (Entry p) Source # 
Instance details

Defined in Data.Heap

Methods

traverse :: Applicative f => (a -> f b) -> Entry p a -> f (Entry p b) #

sequenceA :: Applicative f => Entry p (f a) -> f (Entry p a) #

mapM :: Monad m => (a -> m b) -> Entry p a -> m (Entry p b) #

sequence :: Monad m => Entry p (m a) -> m (Entry p a) #

Eq p => Eq (Entry p a) Source # 
Instance details

Defined in Data.Heap

Methods

(==) :: Entry p a -> Entry p a -> Bool #

(/=) :: Entry p a -> Entry p a -> Bool #

(Data p, Data a) => Data (Entry p a) Source # 
Instance details

Defined in Data.Heap

Methods

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 :: forall r r'. (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 # 
Instance details

Defined in Data.Heap

Methods

compare :: Entry p a -> Entry p a -> Ordering #

(<) :: Entry p a -> Entry p a -> Bool #

(<=) :: Entry p a -> Entry p a -> Bool #

(>) :: Entry p a -> Entry p a -> Bool #

(>=) :: Entry p a -> Entry p a -> Bool #

max :: Entry p a -> Entry p a -> Entry p a #

min :: Entry p a -> Entry p a -> Entry p a #

(Read p, Read a) => Read (Entry p a) Source # 
Instance details

Defined in Data.Heap

(Show p, Show a) => Show (Entry p a) Source # 
Instance details

Defined in Data.Heap

Methods

showsPrec :: Int -> Entry p a -> ShowS #

show :: Entry p a -> String #

showList :: [Entry p a] -> ShowS #

Basic functions

empty :: Heap a Source #

O(1). The empty heap

emptyfromList []
>>> size empty
0

null :: Heap a -> Bool Source #

O(1). Is the heap empty?

>>> null empty
True
>>> null (singleton "hello")
False

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

singleton :: Ord a => a -> Heap a Source #

O(1). A heap with a single element

singleton x ≡ fromList [x]
singleton x ≡ insert x empty
>>> size (singleton "hello")
1

insert :: Ord a => a -> Heap a -> Heap a Source #

O(1). Insert a new value into the heap.

>>> insert 2 (fromList [1,3])
fromList [1,2,3]
insert x emptysingleton x
size (insert x xs) ≡ 1 + size xs

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]

adjustMin :: (a -> a) -> Heap a -> Heap a Source #

O(log n). Adjust the minimum key in the heap and return the resulting heap.

>>> adjustMin (+1) (fromList [1,2,3])
fromList [2,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])

viewMin :: Heap a -> Maybe (a, Heap a) Source #

Same as uncons

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 . toUnsortedListid

fromList :: Ord a => [a] -> Heap a Source #

O(n). Build a heap from a list of values.

fromList . toListid
toList . fromListsort

sort :: Ord a => [a] -> [a] Source #

O(n log n). Perform a heap sort

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 Monadic 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])

break p is equivalent to span (not . p).

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])

span p xs is equivalent to (takeWhile p xs, dropWhile p xs)

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]

dropWhile :: (a -> Bool) -> Heap a -> Heap a Source #

O(n log n). dropWhile p xs returns the suffix of the heap remaining after takeWhile p xs.

>>> dropWhile (\x -> x `mod` 4 == 0) (fromList [4,8,12,14,16])
fromList [14,16]

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.

Duplication

replicate :: Ord a => a -> Int -> Heap a Source #

O(log n). Create a heap consisting of multiple copies of the same value.

>>> replicate 'a' 10
fromList "aaaaaaaaaa"