extended-containers-0.1.1.0: Heap and Vector container types
Safe HaskellNone
LanguageHaskell2010

Data.PrioHeap

Description

Finite priority heaps

The PrioHeap k a type represents a finite heap (or priority queue) from keys/priorities of type k to values of type a. A PrioHeap is strict in its spine. Unlike with maps, duplicate keys/priorities 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 PrioHeap 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 by:

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

Documentation

data PrioHeap k a Source #

A skew binomial heap with associated priorities.

Instances

Instances details
Show2 PrioHeap Source # 
Instance details

Defined in Data.PrioHeap

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> PrioHeap a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [PrioHeap a b] -> ShowS #

Functor (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

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

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

Foldable (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

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

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

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

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

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

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

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

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

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

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

null :: PrioHeap k a -> Bool #

length :: PrioHeap k a -> Int #

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

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

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

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

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

Traversable (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

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

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

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

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

Ord k => Eq1 (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

liftEq :: (a -> b -> Bool) -> PrioHeap k a -> PrioHeap k b -> Bool #

Ord k => Ord1 (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

liftCompare :: (a -> b -> Ordering) -> PrioHeap k a -> PrioHeap k b -> Ordering #

(Ord k, Read k) => Read1 (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (PrioHeap k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [PrioHeap k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (PrioHeap k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [PrioHeap k a] #

Show k => Show1 (PrioHeap k) Source # 
Instance details

Defined in Data.PrioHeap

Methods

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

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

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

Defined in Data.PrioHeap

Associated Types

type Item (PrioHeap k a) #

Methods

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

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

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

(Ord k, Eq a) => Eq (PrioHeap k a) Source # 
Instance details

Defined in Data.PrioHeap

Methods

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

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

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

Defined in Data.PrioHeap

Methods

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

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

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

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

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

max :: PrioHeap k a -> PrioHeap k a -> PrioHeap k a #

min :: PrioHeap k a -> PrioHeap k a -> PrioHeap k a #

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

Defined in Data.PrioHeap

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

Defined in Data.PrioHeap

Methods

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

show :: PrioHeap k a -> String #

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

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

Defined in Data.PrioHeap

Methods

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

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

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

Ord k => Monoid (PrioHeap k a) Source # 
Instance details

Defined in Data.PrioHeap

Methods

mempty :: PrioHeap k a #

mappend :: PrioHeap k a -> PrioHeap k a -> PrioHeap k a #

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

(NFData k, NFData a) => NFData (PrioHeap k a) Source # 
Instance details

Defined in Data.PrioHeap

Methods

rnf :: PrioHeap k a -> () #

type Item (PrioHeap k a) Source # 
Instance details

Defined in Data.PrioHeap

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

Construction

empty :: PrioHeap k a Source #

O(1). The empty heap.

empty = fromList []

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

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

singleton x = fromList [x]

fromHeap :: (k -> a) -> Heap k -> PrioHeap k a Source #

O(n). Create a heap from a Heap of keys and a function which computes the value for each key.

From Lists

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

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

Insertion/Union

insert :: Ord k => k -> a -> PrioHeap k a -> PrioHeap k a Source #

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

union :: Ord k => PrioHeap k a -> PrioHeap k a -> PrioHeap k a Source #

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

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

The union of a foldable of heaps.

unions = foldl union empty

Traversal/Filter

map :: (a -> b) -> PrioHeap k a -> PrioHeap k b Source #

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

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

O(n). Map a function that has access to the key associated with a value over the heap.

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

O(n). Traverse the heap with a function that has access to the key associated with a value.

filter :: Ord k => (a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #

O(n). Filter all elements that satisfy the predicate.

filterWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #

O(n). Filter all elements that satisfy the predicate.

partition :: Ord k => (a -> Bool) -> PrioHeap k a -> (PrioHeap k a, PrioHeap k 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.

partitionWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> (PrioHeap k a, PrioHeap k 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.

mapMaybe :: Ord k => (a -> Maybe b) -> PrioHeap k a -> PrioHeap k b Source #

O(n). Map and collect the Just results.

mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> PrioHeap k a -> PrioHeap k b Source #

O(n). Map and collect the Just results.

mapEither :: Ord k => (a -> Either b c) -> PrioHeap k a -> (PrioHeap k b, PrioHeap k c) Source #

O(n). Map and separate the Left and Right results.

mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> PrioHeap k a -> (PrioHeap k b, PrioHeap k c) Source #

O(n). Map and separate the Left and Right results.

Folds

foldMapWithKey :: Monoid m => (k -> a -> m) -> PrioHeap k a -> m Source #

O(n). Fold the keys and values in the heap, using the given monoid.

foldlWithKey :: (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #

O(n). Fold the keys and values in the heap, using the given left-associative function.

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

O(n). Fold the keys and values in the heap, using the given right-associative function.

foldlWithKey' :: (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #

O(n). A strict version of foldlWithKey. Each application of the function is evaluated before using the result in the next application.

foldrWithKey' :: (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #

O(n). A strict version of foldrWithKey. Each application of the function is evaluated before using the result in the next application.

foldMapOrd :: (Ord k, Monoid m) => (a -> m) -> PrioHeap k a -> m Source #

O(n * log n). Fold the values in the heap in order, using the given monoid.

foldlOrd :: Ord k => (b -> a -> b) -> b -> PrioHeap k a -> b Source #

O(n * log n). Fold the values in the heap in order, using the given left-associative function.

foldrOrd :: Ord k => (a -> b -> b) -> b -> PrioHeap k a -> b Source #

O(n * log n). Fold the values in the heap in order, using the given right-associative function.

foldlOrd' :: Ord k => (b -> a -> b) -> b -> PrioHeap k 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 k => (a -> b -> b) -> b -> PrioHeap k 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.

foldMapWithKeyOrd :: (Ord k, Monoid m) => (k -> a -> m) -> PrioHeap k a -> m Source #

O(n * log n). Fold the keys and values in the heap in order, using the given monoid.

foldlWithKeyOrd :: Ord k => (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #

O(n * log n). Fold the keys and values in the heap in order, using the given left-associative function.

foldrWithKeyOrd :: Ord k => (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #

O(n * log n). Fold the keys and values in the heap in order, using the given right-associative function.

foldlWithKeyOrd' :: Ord k => (b -> k -> a -> b) -> b -> PrioHeap k a -> b Source #

O(n). A strict version of foldlWithKeyOrd. Each application of the function is evaluated before using the result in the next application.

foldrWithKeyOrd' :: Ord k => (k -> a -> b -> b) -> b -> PrioHeap k a -> b Source #

O(n * log n). A strict version of foldrWithKeyOrd. Each application of the function is evaluated before using the result in the next application.

Query

size :: PrioHeap k a -> Int Source #

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

member :: Ord k => k -> PrioHeap k a -> Bool Source #

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

notMember :: Ord k => k -> PrioHeap k a -> Bool Source #

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

Min

adjustMin :: (a -> a) -> PrioHeap k a -> PrioHeap k a Source #

O(1). Adjust the value at the minimal key.

adjustMinWithKey :: (k -> a -> a) -> PrioHeap k a -> PrioHeap k a Source #

O(1). Adjust the value at the minimal key.

lookupMin :: PrioHeap k a -> Maybe (k, a) Source #

O(1). The minimal element in the heap or Nothing if the heap is empty.

findMin :: PrioHeap k a -> (k, a) Source #

O(1). The minimal element in the heap. Calls error if the heap is empty.

deleteMin :: Ord k => PrioHeap k a -> PrioHeap k a Source #

O(log n). Delete the minimal element. Returns the empty heap if the heap is empty.

deleteFindMin :: Ord k => PrioHeap k a -> ((k, a), PrioHeap k a) Source #

O(log n). Delete and find the minimal element. Calls error if the heap is empty.

deleteFindMin heap = (findMin heap, deleteMin heap)

updateMin :: Ord k => (a -> Maybe a) -> PrioHeap k a -> PrioHeap k a Source #

O(log n). Update the value at the minimal key.

updateMinWithKey :: Ord k => (k -> a -> Maybe a) -> PrioHeap k a -> PrioHeap k a Source #

O(log n). Update the value at the minimal key.

minView :: Ord k => PrioHeap k a -> Maybe ((k, a), PrioHeap k a) Source #

O(log n). Retrieves the minimal key/value pair of the heap and the heap stripped of that element or Nothing if the heap is empty.

Subranges

take :: Ord k => Int -> PrioHeap k a -> [(k, 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 k => Int -> PrioHeap k a -> PrioHeap k a Source #

O(n * log n). drop n heap drops the n smallest elements from heap.

splitAt :: Ord k => Int -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #

O(n * log n). splitAt n heap takes and drops the n smallest elements from heap.

takeWhile :: Ord k => (a -> Bool) -> PrioHeap k a -> [(k, a)] Source #

O(n * log n). takeWhile p heap takes the elements from heap in ascending order, while p holds.

takeWhileWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> [(k, a)] Source #

O(n * log n). takeWhileWithKey p heap takes the elements from heap in ascending order, while p holds.

dropWhile :: Ord k => (a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #

O(n * log n). dropWhile p heap drops the elements from heap in ascending order, while p holds.

dropWhileWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> PrioHeap k a Source #

O(n * log n). dropWhileWithKey p heap drops the elements from heap in ascending order, while p holds.

span :: Ord k => (a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #

O(n * log n). span p heap takes and drops the elements from heap, while p holds

spanWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #

O(n * log n). spanWithKey p heap takes and drops the elements from heap, while p holds

break :: Ord k => (a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #

O(n * log n). span, but with inverted predicate.

breakWithKey :: Ord k => (k -> a -> Bool) -> PrioHeap k a -> ([(k, a)], PrioHeap k a) Source #

O(n * log n). spanWithKey, but with inverted predicate.

nub :: Ord k => PrioHeap k a -> PrioHeap k a Source #

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

Conversion

keysHeap :: PrioHeap k a -> Heap k Source #

Create a Heap of all keys of the heap

To Lists

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

O(n). Create a list of key/value pairs from the heap.

toAscList :: Ord k => PrioHeap k a -> [(k, a)] Source #

O(n * log n). Create an ascending list of key/value pairs from the heap.

toDescList :: Ord k => PrioHeap k a -> [(k, a)] Source #

O(n * log n). Create a descending list of key/value pairs from the heap.