extended-containers-0.1.0.0: Heap and Vector container types

Safe HaskellNone
LanguageHaskell2010

Data.Heap

Contents

Description

Finite heaps

The Heap a type represents a finite heap (or priority queue) of elements of type a. 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 maxBound :: Int. Violation of this condition is not detected and if the length limit is exceeded, the behaviour of the heap is undefined.

Implementation

The implementation uses skew binomial heaps, as described in

  • Chris Okasaki, "Purely Functional Data Structures", 1998
Synopsis

Documentation

data Heap a Source #

A skew binomial heap.

Instances
Foldable Heap Source # 
Instance details

Defined in Data.Heap.Internal

Methods

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 #

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 #

Show1 Heap Source # 
Instance details

Defined in Data.Heap.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Heap a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Heap a] -> ShowS #

Ord a => IsList (Heap a) Source # 
Instance details

Defined in Data.Heap.Internal

Associated Types

type Item (Heap a) :: Type #

Methods

fromList :: [Item (Heap a)] -> Heap a #

fromListN :: Int -> [Item (Heap a)] -> Heap a #

toList :: Heap a -> [Item (Heap a)] #

Ord a => Eq (Heap a) Source # 
Instance details

Defined in Data.Heap.Internal

Methods

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

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

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

Defined in Data.Heap.Internal

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

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

Defined in Data.Heap.Internal

Methods

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

show :: Heap a -> String #

showList :: [Heap a] -> ShowS #

Ord a => Semigroup (Heap a) Source # 
Instance details

Defined in Data.Heap.Internal

Methods

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

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

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

Ord a => Monoid (Heap a) Source # 
Instance details

Defined in Data.Heap.Internal

Methods

mempty :: Heap a #

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

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

type Item (Heap a) Source # 
Instance details

Defined in Data.Heap.Internal

type Item (Heap a) = a

Construction

empty :: Heap a Source #

O(1). The empty heap.

empty = fromList []

singleton :: a -> Heap a Source #

O(1). A heap with a single element.

singleton x = fromList [x]

From Lists

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

O(n). Create a heap from a list.

Insertion/Union

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

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

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

O(log n). The union of two heaps.

unions :: (Foldable f, Ord a) => f (Heap a) -> Heap a Source #

The union of a foldable of heaps.

unions = foldl union empty

Traversal/Filter

map :: Ord b => (a -> b) -> Heap a -> Heap b Source #

O(n). Map a function over the heap.

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

size :: Heap a -> Int Source #

O(1). The number of elements in the heap.

member :: Ord a => a -> Heap a -> Bool Source #

O(n). Is the value a member of the heap?

notMember :: Ord a => a -> Heap a -> Bool Source #

O(n). Is the value not a member of the heap?

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)

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

O(n * log n). Remove duplicate elements from the heap.

Conversion

To Lists

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

O(n * log n). Create a descending list from the heap.

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

O(n * log n). Create a descending list from the heap.

Heapsort

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

O(n * log n). Sort a list using a heap. The sort is unstable.