heap-1.0.1: Heaps in Haskell

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Heap

Contents

Description

A flexible implementation of min-, max-, min-priority, max-priority and custom-priority heaps based on the leftist-heaps from Chris Okasaki's book "Purely Functional Data Structures", Cambridge University Press, 1998, chapter 3.1.

There are different flavours of Heaps, each of them following a different strategy when ordering its elements:

  • Choose MinHeap or MaxHeap if you need a simple minimum or maximum heap (which always keeps the minimum/maximum element at the head of the Heap).
  • If you wish to manually annotate a value with a priority, e. g. an IO () action with an Int use MinPrioHeap or MaxPrioHeap. They manage (prio, val) tuples so that only the priority (and not the value) influences the order of elements.
  • If you still need something different, define a custom order for the heap elements by implementing an instance of HeapItem and let the maintainer know what's missing.

All sorts of heaps mentioned above (MinHeap, MaxHeap, MinPrioHeap and MaxPrioHeap) are built on the same underlying type: HeapT prio val. It is a simple minimum priority heap. The trick is, that you never insert (prio, val) pairs directly: You only insert an "external representation", usually called item, and an appropriate HeapItem instance is used to split the item to a (prio, val) pair. For details refer to the documentation of HeapItem.

Synopsis

Types

Various heap flavours

data HeapT prio val Source

The basic heap type. It stores priority-value pairs (prio, val) and always keeps the pair with minimal priority on top. The value associated to the priority does not have any influence on the ordering of elements.

Instances

Functor (HeapT prio) 
Ord prio => Foldable (HeapT prio) 
(Ord prio, Ord val) => Eq (HeapT prio val) 
(Ord prio, Ord val) => Ord (HeapT prio val) 
(Read prio, Read val, Ord prio) => Read (HeapT prio val) 
(Show prio, Show val) => Show (HeapT prio val) 
Ord prio => Monoid (HeapT prio val) 
Typeable (* -> * -> *) HeapT 

type Heap pol item = HeapT (Prio pol item) (Val pol item) Source

This type alias is an abbreviation for a HeapT which uses the HeapItem instance of pol item to organise its elements.

type MinHeap a = Heap MinPolicy a Source

A Heap which will always extract the minimum first.

type MaxHeap a = Heap MaxPolicy a Source

A Heap which will always extract the maximum first.

type MinPrioHeap prio val = Heap FstMinPolicy (prio, val) Source

A Heap storing priority-value pairs (prio, val). The order of elements is solely determined by the priority prio, the value val has no influence. The priority-value pair with minmal priority will always be extracted first.

type MaxPrioHeap prio val = Heap FstMaxPolicy (prio, val) Source

A Heap storing priority-value pairs (prio, val). The order of elements is solely determined by the priority prio, the value val has no influence. The priority-value pair with maximum priority will always be extracted first.

Ordering strategies

class Ord (Prio pol item) => HeapItem pol item where Source

HeapItem pol item is a type class for items that can be stored in a HeapT. A raw HeapT prio val only provides a minimum priority heap (i. e. val doesn't influence the ordering of elements and the pair with minimal prio will be extracted first, see HeapT documentation). The job of this class is to translate between arbitrary items and priority-value pairs (Prio pol item, Val pol item), depending on the policy pol to be used. This way, we are able to use HeapT not only as MinPrioHeap, but also as MinHeap, MaxHeap, MaxPrioHeap or a custom implementation. In short: The job of this class is to deconstruct arbitrary items into a (prio, val) pairs that can be handled by a minimum priority HeapT.

Example: Consider you want to use HeapT prio val as a MaxHeap a. You would have to invert the order of a (e. g. by introducing newtype InvOrd a = InvOrd a along with an apropriate Ord instance for it) and then use a type MaxHeap a = HeapT (InvOrd a) (). You'd also have to translate every x to (InvOrd x, ()) before insertion and back after removal in order to retrieve your original type a.

This functionality is provided by the HeapItem class. In the above example, you'd use a MaxHeap. The according instance declaration is of course already provided and looks like this (simplified):

@data MaxPolicy

instance (Ord a) => HeapItem MaxPolicy a where newtype Prio MaxPolicy a = MaxP a deriving (Eq) type Val MaxPolicy a = () split x = (MaxP x, ()) merge (MaxP x, _) = x

instance (Ord a) => Ord (Prio MaxPolicy a) where compare (MaxP x) (MaxP y) = compare y x @

MaxPolicy is a phantom type describing which HeapItem instance is actually meant (e. g. we have to distinguish between MinHeap and MaxHeap, which is done via MinPolicy and MaxPolicy, respectively) and MaxP inverts the ordering of a, so that the maximum will be on top of the HeapT.

The conversion functions split and merge have to make sure that

  1. forall p v. split (merge (p, v)) == (p, v) (merge and split don't remove, add or alter anything)
  2. forall p v f. fst (split (merge (p, f v)) == fst (split (merge (p, v))) (modifying the associated value v doesn't alter the priority p)

Associated Types

data Prio pol item :: * Source

The part of item that determines the order of elements on a HeapT.

type Val pol item :: * Source

Everything not part of Prio pol item

Methods

split :: item -> (Prio pol item, Val pol item) Source

Translate an item into a priority-value pair.

merge :: (Prio pol item, Val pol item) -> item Source

Restore the item from a priority-value pair.

Instances

Ord a => HeapItem MaxPolicy a 
Ord a => HeapItem MinPolicy a 
Ord prio => HeapItem FstMaxPolicy (prio, val) 
Ord prio => HeapItem FstMinPolicy (prio, val) 

data MinPolicy Source

Policy type for a MinHeap.

Instances

Ord a => HeapItem MinPolicy a 
Eq a => Eq (Prio MinPolicy a) 
Ord a => Ord (Prio MinPolicy a) 
Read a => Read (Prio MinPolicy a) 
Show a => Show (Prio MinPolicy a) 
data Prio MinPolicy = MinP {} 
type Val MinPolicy a = () 

data MaxPolicy Source

Policy type for a MaxHeap.

Instances

Ord a => HeapItem MaxPolicy a 
Eq a => Eq (Prio MaxPolicy a) 
Ord a => Ord (Prio MaxPolicy a) 
Read a => Read (Prio MaxPolicy a) 
Show a => Show (Prio MaxPolicy a) 
data Prio MaxPolicy = MaxP {} 
type Val MaxPolicy a = () 

data FstMinPolicy Source

Policy type for a (prio, val) MinPrioHeap.

Instances

Ord prio => HeapItem FstMinPolicy (prio, val) 
Eq prio => Eq (Prio FstMinPolicy (prio, val)) 
Ord prio => Ord (Prio FstMinPolicy (prio, val)) 
Read prio => Read (Prio FstMinPolicy (prio, val)) 
Show prio => Show (Prio FstMinPolicy (prio, val)) 
data Prio FstMinPolicy (prio, val) = FMinP {} 
type Val FstMinPolicy (prio, val) = val 

data FstMaxPolicy Source

Policy type for a (prio, val) MaxPrioHeap.

Instances

Ord prio => HeapItem FstMaxPolicy (prio, val) 
Eq prio => Eq (Prio FstMaxPolicy (prio, val)) 
Ord prio => Ord (Prio FstMaxPolicy (prio, val)) 
Read prio => Read (Prio FstMaxPolicy (prio, val)) 
Show prio => Show (Prio FstMaxPolicy (prio, val)) 
data Prio FstMaxPolicy (prio, val) = FMaxP {} 
type Val FstMaxPolicy (prio, val) = val 

Query

isEmpty :: HeapT prio val -> Bool Source

O(1). Is the HeapT empty?

null :: HeapT prio val -> Bool Source

O(1). Is the HeapT empty?

size :: HeapT prio val -> Int Source

O(1). The total number of elements in the HeapT.

Construction

empty :: HeapT prio val Source

O(1). Construct an empty HeapT.

singleton :: HeapItem pol item => item -> Heap pol item Source

O(1). Create a singleton HeapT.

insert :: HeapItem pol item => item -> Heap pol item -> Heap pol item Source

O(log n). Insert a single item into the HeapT.

union :: Ord prio => HeapT prio val -> HeapT prio val -> HeapT prio val Source

O(log max(n, m)). Form the union of two HeapTs.

unions :: Ord prio => [HeapT prio val] -> HeapT prio val Source

Build the union of all given HeapTs.

Deconstruction

view :: HeapItem pol item => Heap pol item -> Maybe (item, Heap pol item) Source

O(1) for the head, O(log n) for the tail. Find the item with minimal associated priority and remove it from the Heap (i. e. find head and tail of the heap) if it is not empty. Otherwise, Nothing is returned.

viewHead :: HeapItem pol item => Heap pol item -> Maybe item Source

O(1). Find the item with minimal associated priority on the Heap (i. e. its head) if it is not empty. Otherwise, Nothing is returned.

viewTail :: HeapItem pol item => Heap pol item -> Maybe (Heap pol item) Source

O(log n). Remove the item with minimal associated priority and from the Heap (i. e. its tail) if it is not empty. Otherwise, Nothing is returned.

Filter

filter :: HeapItem pol item => (item -> Bool) -> Heap pol item -> Heap pol item Source

Remove all items from a HeapT not fulfilling a predicate.

partition :: HeapItem pol item => (item -> Bool) -> Heap pol item -> (Heap pol item, Heap pol item) Source

Partition the Heap into two. partition p h = (h1, h2): All items in h1 fulfil the predicate p, those in h2 don't. union h1 h2 = h.

Subranges

take :: HeapItem pol item => Int -> Heap pol item -> [item] Source

Take the first n items from the Heap.

drop :: HeapItem pol item => Int -> Heap pol item -> Heap pol item Source

Remove first n items from the Heap.

splitAt :: HeapItem pol item => Int -> Heap pol item -> ([item], Heap pol item) Source

splitAt n h: Return a list of the first n items of h and h, with those elements removed.

takeWhile :: HeapItem pol item => (item -> Bool) -> Heap pol item -> [item] Source

takeWhile p h: List the longest prefix of items in h that satisfy p.

dropWhile :: HeapItem pol item => (item -> Bool) -> Heap pol item -> Heap pol item Source

dropWhile p h: Remove the longest prefix of items in h that satisfy p.

span :: HeapItem pol item => (item -> Bool) -> Heap pol item -> ([item], Heap pol item) Source

span p h: Return the longest prefix of items in h that satisfy p and h, with those elements removed.

break :: HeapItem pol item => (item -> Bool) -> Heap pol item -> ([item], Heap pol item) Source

break p h: The longest prefix of items in h that do not satisfy p and h, with those elements removed.

Conversion

List

fromList :: HeapItem pol item => [item] -> Heap pol item Source

O(n log n). Build a Heap from the given items. Assuming you have a sorted list, you probably want to use fromDescList or fromAscList, they are faster than this function.

toList :: HeapItem pol item => Heap pol item -> [item] Source

O(n log n). List all items of the Heap in no specific order.

Ordered list

fromAscList :: HeapItem pol item => [item] -> Heap pol item Source

O(n). Create a Heap from a list providing its items in ascending order of priority (i. e. in the same order they will be removed from the Heap). This function is faster than fromList but not as fast as fromDescList.

The precondition is not checked.

toAscList :: HeapItem pol item => Heap pol item -> [item] Source

O(n log n). List the items of the Heap in ascending order of priority.

fromDescList :: HeapItem pol item => [item] -> Heap pol item Source

O(n). Create a Heap from a list providing its items in descending order of priority (i. e. they will be removed inversely from the Heap). Prefer this function over fromList and fromAscList, it's faster.

The precondition is not checked.

toDescList :: HeapItem pol item => Heap pol item -> [item] Source

O(n log n). List the items of the Heap in descending order of priority. Note that this function is not especially efficient (it is implemented in terms of reverse and toAscList), it is provided as a counterpart of the efficient fromDescList function.