stable-heap-0.1.0.0: Purely functional stable heaps (fair priority queues)

Copyright(C) Jake McArthur 2015
LicenseMIT
MaintainerJake.McArthur@gmail.com
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Heap.Stable

Description

This module provides an implementation of stable heaps, or fair priority queues. The data structure is a fairly simple tweak to add stability to the lazy pairing heaps described in Purely Functional Data Structures, by Chris Okasaki.

Unless stated otherwise, the documented asymptotic efficiencies of functions on Heap assume that arguments are already in WHNF and that the result is to be evaluated to WHNF.

Synopsis

Documentation

data Heap k a Source

Semantically, Heap k a is equivalent to [(k, a)], but its operations have different efficiencies.

Instances

(Monoid k, Ord k) => Monad (Heap k) Source

Same semantics as WriterT k []

Functor (Heap k) Source 
(Monoid k, Ord k) => Applicative (Heap k) Source

Same semantics as WriterT k []

Foldable (Heap k) Source 
Traversable (Heap k) Source 
(Monoid k, Ord k) => Alternative (Heap k) Source
empty = empty
(<|>) = union
(Monoid k, Ord k) => MonadPlus (Heap k) Source
mzero = empty
mplus = union
Ord k => IsList (Heap k a) Source 
(Eq k, Eq a) => Eq (Heap k a) Source
xs == ys = toList xs == toList ys
(Ord k, Ord a) => Ord (Heap k a) Source
compare xs ys = compare (toList xs) (toList ys)
(Ord k, Read k, Read a) => Read (Heap k a) Source 
(Show k, Show a) => Show (Heap k a) Source 
Ord k => Monoid (Heap k a) Source
mempty  = empty
mappend = union
type Item (Heap k a) = (k, a) Source 

empty :: Heap k a Source

toList empty = []

singleton :: k -> a -> Heap k a Source

O(1).

toList (singleton k v) = [(k, v)]

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

O(1).

toList (xs `union` ys) = toList xs ++ toList ys

minViewWithKey :: Ord k => Heap k a -> Maybe (Heap k a, (k, a), Heap k a) Source

Split the Heap at the leftmost occurrence of the smallest key contained in the Heap.

When the Heap is empty, O(1). When the Heap is not empty, finding the key and value is O(1), and evaluating the remainder of the heap to the left or right of the key-value pair is amortized O(log n).

toList xs =
case minViewWithKey xs of
  Nothing -> []
  Just (l, kv, r) -> toList l ++ [kv] ++ toList r

cons :: Ord k => k -> a -> Heap k a -> Heap k a Source

O(1).

toList (cons k v xs) = (k, v) : toList xs

snoc :: Ord k => Heap k a -> k -> a -> Heap k a Source

O(1).

toList (snoc xs k v) = toList xs ++ [(k, v)]

foldrWithKey :: (k -> a -> b -> b) -> b -> Heap k a -> b Source

foldrWithKey f z xs = foldr (uncurry f) z (toList xs)

toList :: Heap k a -> [(k, a)] Source

List the key-value pairs in a Heap in occurrence order. This is the semantic function for Heap.

O(n) when the spine of the result is evaluated fully.

toListAsc :: Ord k => Heap k a -> [(k, a)] Source

List the key-value pairs in a Heap in key order.

O(n log n) when the spine of the result is evaluated fully.

fromList :: Ord k => [(k, a)] -> Heap k a Source

Construct a Heap from a list of key-value pairs.

O(n).

bimap :: Ord k2 => (k1 -> k2) -> (a -> b) -> Heap k1 a -> Heap k2 b Source

toList (bimap f g xs) = map (f *** g) (toList xs)

mapKeys :: Ord k2 => (k1 -> k2) -> Heap k1 a -> Heap k2 a Source

toList (mapKeys f xs) = map (first f) (toList xs)