stable-heap-0.2.1.0: Purely functional stable heaps (fair priority queues)
Copyright(C) 2015-2016 Jake McArthur
LicenseMIT
MaintainerJake.McArthur@gmail.com
Stabilityexperimental
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Heap.Stable

Description

A simple implementation of stable heaps (fair priority queues), modeled as a sequence of key-value pairs, allowing duplicates, with efficient access to the leftmost key-value pair having the smallest key.

The data structure is a modification of the lazy pairing heaps described in Chris Okasaki's Purely Functional Data Structures.

A Heap has both heap-like and sequence-like properties. Most of the traversals defined in this module work in sequence order; those that work in key order are explicitly documented as such.

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

We use QuickCheck to verify the properties given in this documentation. Here is the necessary setup code:

>>> import Test.QuickCheck
>>> import Test.QuickCheck.Function
>>> :{
instance (Arbitrary k, Arbitrary v, Ord k) => Arbitrary (Heap k v) where
  arbitrary = fromList <$> arbitrary
  shrink = map fromList . shrink . toList
:}

Here are some example values used in the documentation for this module:

>>> let the   = fromList (zip "the"   [0..])
>>> let quick = fromList (zip "quick" [0..])
>>> let brown = fromList (zip "brown" [0..])
>>> let fox   = fromList (zip "fox"   [0..])
>>> the
fromList [('t',0),('h',1),('e',2)]
>>> quick
fromList [('q',0),('u',1),('i',2),('c',3),('k',4)]
>>> brown
fromList [('b',0),('r',1),('o',2),('w',3),('n',4)]
>>> fox
fromList [('f',0),('o',1),('x',2)]

data Heap k a Source #

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

Instances

Instances details
Foldable (Heap k) Source # 
Instance details

Defined in Data.Heap.Stable

Methods

fold :: Monoid m => Heap k m -> m #

foldMap :: Monoid m => (a -> m) -> Heap k a -> m #

foldMap' :: Monoid m => (a -> m) -> Heap k a -> m #

foldr :: (a -> b -> b) -> b -> Heap k a -> b #

foldr' :: (a -> b -> b) -> b -> Heap k a -> b #

foldl :: (b -> a -> b) -> b -> Heap k a -> b #

foldl' :: (b -> a -> b) -> b -> Heap k a -> b #

foldr1 :: (a -> a -> a) -> Heap k a -> a #

foldl1 :: (a -> a -> a) -> Heap k a -> a #

toList :: Heap k a -> [a] #

null :: Heap k a -> Bool #

length :: Heap k a -> Int #

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

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

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

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

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

Traversable (Heap k) Source # 
Instance details

Defined in Data.Heap.Stable

Methods

traverse :: Applicative f => (a -> f b) -> Heap k a -> f (Heap k b) #

sequenceA :: Applicative f => Heap k (f a) -> f (Heap k a) #

mapM :: Monad m => (a -> m b) -> Heap k a -> m (Heap k b) #

sequence :: Monad m => Heap k (m a) -> m (Heap k a) #

(Monoid k, Ord k) => Alternative (Heap k) Source #

Formed from empty and append

Instance details

Defined in Data.Heap.Stable

Methods

empty :: Heap k a #

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

some :: Heap k a -> Heap k [a] #

many :: Heap k a -> Heap k [a] #

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

Equivalent to WriterT k []

Instance details

Defined in Data.Heap.Stable

Methods

pure :: a -> Heap k a #

(<*>) :: Heap k (a -> b) -> Heap k a -> Heap k b #

liftA2 :: (a -> b -> c) -> Heap k a -> Heap k b -> Heap k c #

(*>) :: Heap k a -> Heap k b -> Heap k b #

(<*) :: Heap k a -> Heap k b -> Heap k a #

Functor (Heap k) Source # 
Instance details

Defined in Data.Heap.Stable

Methods

fmap :: (a -> b) -> Heap k a -> Heap k b #

(<$) :: a -> Heap k b -> Heap k a #

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

Equivalent to WriterT k []

Instance details

Defined in Data.Heap.Stable

Methods

(>>=) :: Heap k a -> (a -> Heap k b) -> Heap k b #

(>>) :: Heap k a -> Heap k b -> Heap k b #

return :: a -> Heap k a #

(Monoid k, Ord k) => MonadPlus (Heap k) Source #

Formed from empty and append

Instance details

Defined in Data.Heap.Stable

Methods

mzero :: Heap k a #

mplus :: Heap k a -> Heap k a -> Heap k a #

Ord k => Monoid (Heap k a) Source #

Formed from empty and append

Instance details

Defined in Data.Heap.Stable

Methods

mempty :: Heap k a #

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

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

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

Defined in Data.Heap.Stable

Methods

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

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

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

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

Defined in Data.Heap.Stable

Associated Types

type Item (Heap k a) #

Methods

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

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

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

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

Defined in Data.Heap.Stable

Methods

readsPrec :: Int -> ReadS (Heap k a) #

readList :: ReadS [Heap k a] #

readPrec :: ReadPrec (Heap k a) #

readListPrec :: ReadPrec [Heap k a] #

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

Defined in Data.Heap.Stable

Methods

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

show :: Heap k a -> String #

showList :: [Heap k a] -> ShowS #

(Eq k, Eq a) => Eq (Heap k a) Source #
(xs == ys) == (toList xs == toList ys)
Instance details

Defined in Data.Heap.Stable

Methods

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

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

(Ord k, Ord a) => Ord (Heap k a) Source #
compare xs ys == compare (toList xs) (toList ys)
Instance details

Defined in Data.Heap.Stable

Methods

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

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

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

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

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

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

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

type Item (Heap k a) Source # 
Instance details

Defined in Data.Heap.Stable

type Item (Heap k a) = (k, a)

Query

null :: Heap k a -> Bool Source #

True if the Heap is empty and False otherwise.

O(1).

>>> any null [the, quick, brown, fox]
False
>>> null empty
True
null xs == Data.List.null (toList xs)

size :: Heap k a -> Int Source #

The number of key-value pairs in the heap.

O(1).

>>> map size [the, quick, brown, fox]
[3,5,5,3]
>>> size empty
0
size xs == length (toList xs)

Construction

empty :: Heap k a Source #

An empty heap.

>>> empty
fromList []

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

Construct a heap containing a single key-value pair.

O(1).

>>> singleton "foo" 42
fromList [("foo",42)]
toList (singleton k v) == [(k, v)]

append :: Ord k => Heap k a -> Heap k a -> Heap k a Source #

Append two heaps, preserving sequential ordering.

O(1).

>>> append empty the
fromList [('t',0),('h',1),('e',2)]
>>> append the empty
fromList [('t',0),('h',1),('e',2)]
>>> append the fox
fromList [('t',0),('h',1),('e',2),('f',0),('o',1),('x',2)]
toList (xs `append` ys) == toList xs ++ toList ys

appends :: Ord k => [Heap k a] -> Heap k a Source #

Sequentially append an arbitrary number of heaps.

O(m), where m is the length of the input list.

>>> appends [the, quick, fox]
fromList [('t',0),('h',1),('e',2),('q',0),('u',1),('i',2),('c',3),('k',4),('f',0),('o',1),('x',2)]
toList (appends xss) == concatMap toList xss

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

Prepend a key-value pair to the beginning of a Heap.

O(1).

>>> cons 'a' 0 fox
fromList [('a',0),('f',0),('o',1),('x',2)]
toList (cons k v xs) == (k, v) : toList xs

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

Append a key-value pair to the end of a Heap.

O(1).

>>> snoc fox 'y' 0
fromList [('f',0),('o',1),('x',2),('y',0)]
toList (snoc xs k v) == toList xs ++ [(k, v)]

Minimum view

data MinView k v Source #

View of the minimum key of a heap, split out from everything occurring to its left and to its right in the sequence.

Constructors

EmptyView 
MinView (Heap k v) k v (Heap k v) 

Instances

Instances details
(Show k, Show v) => Show (MinView k v) Source # 
Instance details

Defined in Data.Heap.Stable

Methods

showsPrec :: Int -> MinView k v -> ShowS #

show :: MinView k v -> String #

showList :: [MinView k v] -> ShowS #

(Eq k, Eq v) => Eq (MinView k v) Source # 
Instance details

Defined in Data.Heap.Stable

Methods

(==) :: MinView k v -> MinView k v -> Bool #

(/=) :: MinView k v -> MinView k v -> Bool #

minView :: Ord k => Heap k a -> MinView 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).

>>> minView empty
EmptyView
>>> minView the
MinView (fromList [('t',0),('h',1)]) 'e' 2 (fromList [])
>>> minView (append the the)
MinView (fromList [('t',0),('h',1)]) 'e' 2 (fromList [('t',0),('h',1),('e',2)])
>>> minView quick
MinView (fromList [('q',0),('u',1),('i',2)]) 'c' 3 (fromList [('k',4)])
>>> minView brown
MinView (fromList []) 'b' 0 (fromList [('r',1),('o',2),('w',3),('n',4)])
>>> minView fox
MinView (fromList []) 'f' 0 (fromList [('o',1),('x',2)])

Here is a model implementation of minView:

>>> :{
let { minViewModel xs =
        case toList xs of
          []        -> EmptyView
          keyValues ->
            let minKey          = minimum (map fst keyValues)
                (l, (k, v) : r) = break (\(key, _) -> key == minKey) keyValues
            in MinView (fromList l) k v (fromList r)
    }
:}

The following property looks different from the others in this module due to working around a limitation of doctest.

>>> quickCheck $ \xs -> minView (xs :: Heap Integer Integer) == minViewModel xs
+++ OK, passed 100 tests.

Traversal

Map

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

>>> bimap succ (*10) fox
fromList [('g',0),('p',10),('y',20)]
toList (bimap (apply f) (apply g) xs) == map (\(k, v) -> (apply f k, apply g v)) (toList xs)

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

>>> mapKeys succ fox
fromList [('g',0),('p',1),('y',2)]
toList (mapKeys (apply f) xs) == map (\(k, v) -> (apply f k, v)) (toList xs)

mapWithKey :: (k -> a -> b) -> Heap k a -> Heap k b Source #

Map a function over all values in a heap.

O(1) when evaluating to WHNF. O(n) when evaluating to NF.

>>> mapWithKey (\k v -> (k,v)) fox
fromList [('f',('f',0)),('o',('o',1)),('x',('x',2))]
let f k v = g `apply` k `apply` v in mapWithKey f xs == fromList (map (\(k, v) -> (k, f k v)) (toList xs))

traverseKeys :: (Applicative f, Ord k2) => (k1 -> f k2) -> Heap k1 a -> f (Heap k2 a) Source #

Behaves exactly like a regular traverse except that it's over the keys instead of the values.

O(n).

>>> traverseKeys (\k -> print k >> return (succ k)) fox
'f'
'o'
'x'
fromList [('g',0),('p',1),('y',2)]
traverseKeys (apply f) xs == (fromList <$> traverse (\(k, v) -> flip (,) v <$> (apply f k :: ([Integer], Integer))) (toList xs))

traverseWithKey :: Applicative f => (k -> a -> f b) -> Heap k a -> f (Heap k b) Source #

Behaves exactly like a regular traverse except that the traversing function also has access to the key associated with a value, such that

O(n).

>>> traverseWithKey (\k v -> print (k, v) >> return (succ k, v)) fox
('f',0)
('o',1)
('x',2)
fromList [('f',('g',0)),('o',('p',1)),('x',('y',2))]
let f k v = g `apply` k `apply` v :: ([Integer], Integer) in traverseWithKey f xs == (fromList <$> traverse (\(k, v) -> (,) k <$> f k v) (toList xs))

Fold

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

Like foldr, but provides access to the key for each value in the folding function.

>>> foldrWithKey (\k v kvs -> (k, v) : kvs) [] fox
[('f',0),('o',1),('x',2)]
let f k v acc = g `apply` k `apply` v `apply` acc in foldrWithKey f z xs == foldr (uncurry f) z (toList xs)

foldMapWithKey :: Monoid b => (k -> a -> b) -> Heap k a -> b Source #

Fold the keys and values in the heap using the given monoid, such that

O(n).

>>> foldMapWithKey (\k v -> [(k,v)]) fox
[('f',0),('o',1),('x',2)]
let f k v = g `apply` k `apply` v :: [Integer] in foldMapWithKey f xs == Data.Foldable.fold (mapWithKey f xs)

List operations

Conversion from lists

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

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

O(n).

>>> fromList (zip [0..3] [4..])
fromList [(0,4),(1,5),(2,6),(3,7)]
toList (fromList xs) == xs
fromList (toList xs) == xs

Conversion to lists

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

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

>>> toList empty
[]
>>> toList the
[('t',0),('h',1),('e',2)]
>>> toList quick
[('q',0),('u',1),('i',2),('c',3),('k',4)]
>>> toList brown
[('b',0),('r',1),('o',2),('w',3),('n',4)]
>>> toList fox
[('f',0),('o',1),('x',2)]

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

toList (fromList xs) == xs
fromList (toList xs) == xs

toAscList :: 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.

>>> toAscList empty
[]
>>> toAscList the
[('e',2),('h',1),('t',0)]
>>> toAscList quick
[('c',3),('i',2),('k',4),('q',0),('u',1)]
>>> toAscList brown
[('b',0),('n',4),('o',2),('r',1),('w',3)]
>>> toAscList fox
[('f',0),('o',1),('x',2)]
toAscList xs == Data.List.sortOn fst (toList xs)