pqueue-1.4.2.0: Reliable, persistent, fast priority queues.
Copyright(c) Louis Wasserman 2010
LicenseBSD-style
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.PQueue.Prio.Min

Description

General purpose priority queue. Each element is associated with a key, and the priority queue supports viewing and extracting the element with the minimum key.

A worst-case bound is given for each operation. In some cases, an amortized bound is also specified; these bounds hold even in a persistent context.

This implementation is based on a binomial heap augmented with a global root.

We do not guarantee stable behavior. Ties are broken arbitrarily -- that is, if k1 <= k2 and k2 <= k1, then there are no guarantees about the relative order in which k1, k2, and their associated elements are returned. (Unlike Data.Map, we allow multiple elements with the same key.)

This implementation offers a number of methods of the form xxxU, where U stands for unordered. No guarantees whatsoever are made on the execution or traversal order of these functions.

Synopsis

Documentation

data MinPQueue k a Source #

A priority queue where values of type a are annotated with keys of type k. The queue supports extracting the element with minimum key.

Instances

Instances details
Functor (MinPQueue k) Source # 
Instance details

Defined in Data.PQueue.Prio.Internals

Methods

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

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

Ord k => Foldable (MinPQueue k) Source # 
Instance details

Defined in Data.PQueue.Prio.Internals

Methods

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

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

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

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

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

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

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

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

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

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

null :: MinPQueue k a -> Bool #

length :: MinPQueue k a -> Int #

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

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

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

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

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

Ord k => Traversable (MinPQueue k) Source #

Traverses in ascending order. mapM is strictly accumulating like mapMWithKey.

Instance details

Defined in Data.PQueue.Prio.Internals

Methods

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

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

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

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

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

Defined in Data.PQueue.Prio.Internals

Methods

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

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

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

Defined in Data.PQueue.Prio.Internals

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MinPQueue k a -> c (MinPQueue k a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MinPQueue k a) #

toConstr :: MinPQueue k a -> Constr #

dataTypeOf :: MinPQueue k a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MinPQueue k a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MinPQueue k a)) #

gmapT :: (forall b. Data b => b -> b) -> MinPQueue k a -> MinPQueue k a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MinPQueue k a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MinPQueue k a -> r #

gmapQ :: (forall d. Data d => d -> u) -> MinPQueue k a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MinPQueue k a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MinPQueue k a -> m (MinPQueue k a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MinPQueue k a -> m (MinPQueue k a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MinPQueue k a -> m (MinPQueue k a) #

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

Defined in Data.PQueue.Prio.Internals

Methods

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

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

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

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

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

max :: MinPQueue k a -> MinPQueue k a -> MinPQueue k a #

min :: MinPQueue k a -> MinPQueue k a -> MinPQueue k a #

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

Defined in Data.PQueue.Prio.Internals

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

Defined in Data.PQueue.Prio.Internals

Methods

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

show :: MinPQueue k a -> String #

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

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

Defined in Data.PQueue.Prio.Internals

Methods

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

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

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

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

Defined in Data.PQueue.Prio.Internals

Methods

mempty :: MinPQueue k a #

mappend :: MinPQueue k a -> MinPQueue k a -> MinPQueue k a #

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

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

Defined in Data.PQueue.Prio.Internals

Methods

rnf :: MinPQueue k a -> () #

Construction

empty :: MinPQueue k a Source #

\(O(1)\). Returns the empty priority queue.

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

\(O(1)\). Constructs a singleton priority queue.

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

Amortized \(O(1)\), worst-case \(O(\log n)\). Inserts an element with the specified key into the queue.

insertBehind :: Ord k => k -> a -> MinPQueue k a -> MinPQueue k a Source #

\(O(n)\) (an earlier implementation had \(O(1)\) but was buggy). Insert an element with the specified key into the priority queue, putting it behind elements whose key compares equal to the inserted one.

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

Amortized \(O(\log \min(n_1,n_2))\), worst-case \(O(\log \max(n_1,n_2))\). Returns the union of the two specified queues.

unions :: Ord k => [MinPQueue k a] -> MinPQueue k a Source #

The union of a list of queues: (unions == foldl union empty).

Query

null :: MinPQueue k a -> Bool Source #

\(O(1)\). Checks if this priority queue is empty.

size :: MinPQueue k a -> Int Source #

\(O(1)\). Returns the size of this priority queue.

Minimum view

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

\(O(1)\). The minimal (key, element) in the queue. Calls error if empty.

getMin :: MinPQueue k a -> Maybe (k, a) Source #

\(O(1)\). The minimal (key, element) in the queue, if the queue is nonempty.

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

\(O(\log n)\). Deletes the minimal (key, element) in the queue. Returns an empty queue if the queue is empty.

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

\(O(\log n)\). Delete and find the element with the minimum key. Calls error if empty.

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

\(O(1)\). Alter the value at the minimum key. If the queue is empty, does nothing.

adjustMinA :: Applicative f => (a -> f a) -> MinPQueue k a -> f (MinPQueue k a) Source #

\(O(1)\). Alter the value at the minimum key in an Applicative context. If the queue is empty, does nothing.

Since: 1.4.2

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

\(O(1)\). Alter the value at the minimum key. If the queue is empty, does nothing.

adjustMinWithKeyA :: Applicative f => (k -> a -> f a) -> MinPQueue k a -> f (MinPQueue k a) Source #

\(O(1)\) per operation. Alter the value at the minimum key in an Applicative context. If the queue is empty, does nothing.

Since: 1.4.2

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

\(O(\log n)\). (Actually \(O(1)\) if there's no deletion.) Update the value at the minimum key. If the queue is empty, does nothing.

updateMinA :: (Applicative f, Ord k) => (a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a) Source #

\(O(\log n)\) per operation. (Actually \(O(1)\) if there's no deletion.) Update the value at the minimum key. If the queue is empty, does nothing.

Since: 1.4.2

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

\(O(\log n)\). (Actually \(O(1)\) if there's no deletion.) Update the value at the minimum key. If the queue is empty, does nothing.

updateMinWithKeyA :: (Applicative f, Ord k) => (k -> a -> f (Maybe a)) -> MinPQueue k a -> f (MinPQueue k a) Source #

\(O(\log n)\) per operation. (Actually \(O(1)\) if there's no deletion.) Update the value at the minimum key in an Applicative context. If the queue is empty, does nothing.

Since: 1.4.2

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

\(O(\log n)\). Retrieves the value associated with the minimal key of the queue, and the queue stripped of that element, or Nothing if passed an empty queue.

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

\(O(\log n)\). Retrieves the minimal (key, value) pair of the map, and the map stripped of that element, or Nothing if passed an empty map.

Traversal

Map

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

\(O(n)\). Map a function over all values in the queue.

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

\(O(n)\). Map a function over all values in the queue.

mapKeys :: Ord k' => (k -> k') -> MinPQueue k a -> MinPQueue k' a Source #

\(O(n)\). mapKeys f q is the queue obtained by applying f to each key of q.

mapKeysMonotonic :: (k -> k') -> MinPQueue k a -> MinPQueue k' a Source #

\(O(n)\). mapKeysMonotonic f q == mapKeys f q, but only works when f is strictly monotonic. The precondition is not checked. This function has better performance than mapKeys.

Fold

foldrWithKey :: Ord k => (k -> a -> b -> b) -> b -> MinPQueue k a -> b Source #

\(O(n \log n)\). Fold the keys and values in the map, such that foldrWithKey f z q == foldr (uncurry f) z (toAscList q).

If you do not care about the traversal order, consider using foldrWithKeyU.

foldlWithKey :: Ord k => (b -> k -> a -> b) -> b -> MinPQueue k a -> b Source #

\(O(n \log n)\). Fold the keys and values in the map, such that foldlWithKey f z q == foldl (uncurry . f) z (toAscList q).

If you do not care about the traversal order, consider using foldlWithKeyU.

Traverse

traverseWithKey :: (Ord k, Applicative f) => (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b) Source #

\(O(n \log n)\). Traverses the elements of the queue in ascending order by key. (traverseWithKey f q == fromAscList $ traverse (uncurry f) (toAscList q))

If you do not care about the order of the traversal, consider using traverseWithKeyU.

If you are working in a strict monad, consider using mapMWithKey.

mapMWithKey :: (Ord k, Monad m) => (k -> a -> m b) -> MinPQueue k a -> m (MinPQueue k b) Source #

A strictly accumulating version of traverseWithKey. This works well in IO and strict State, and is likely what you want for other "strict" monads, where ⊥ >>= pure () = ⊥.

Subsets

Indexed

take :: Ord k => Int -> MinPQueue k a -> [(k, a)] Source #

\(O(k \log n)\)/. Takes the first k (key, value) pairs in the queue, or the first n if k >= n. (take k q == take k (toAscList q))

drop :: Ord k => Int -> MinPQueue k a -> MinPQueue k a Source #

\(O(k \log n)\)/. Deletes the first k (key, value) pairs in the queue, or returns an empty queue if k >= n.

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

\(O(k \log n)\)/. Equivalent to (take k q, drop k q).

Predicates

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

Takes the longest possible prefix of elements satisfying the predicate. (takeWhile p q == takeWhile (p . snd) (toAscList q))

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

Takes the longest possible prefix of elements satisfying the predicate. (takeWhile p q == takeWhile (uncurry p) (toAscList q))

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

Removes the longest possible prefix of elements satisfying the predicate.

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

Removes the longest possible prefix of elements satisfying the predicate.

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

Equivalent to (takeWhile p q, dropWhile p q).

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

Equivalent to (takeWhileWithKey p q, dropWhileWithKey p q).

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

Equivalent to span (not . p).

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

Equivalent to spanWithKey ( k a -> not (p k a)) q.

Filter

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

\(O(n)\). Filter all values that satisfy the predicate.

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

\(O(n)\). Filter all values that satisfy the predicate.

partition :: Ord k => (a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a) Source #

\(O(n)\). Partition the queue according to a predicate. The first queue contains all elements which satisfy the predicate, the second all elements that fail the predicate.

partitionWithKey :: Ord k => (k -> a -> Bool) -> MinPQueue k a -> (MinPQueue k a, MinPQueue k a) Source #

\(O(n)\). Partition the queue according to a predicate. The first queue contains all elements which satisfy the predicate, the second all elements that fail the predicate.

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

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

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

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

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

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

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

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

List operations

Conversion from lists

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

\(O(n)\). Constructs a priority queue from an unordered list.

fromAscList :: [(k, a)] -> MinPQueue k a Source #

\(O(n)\). Build a priority queue from an ascending list of (key, value) pairs. The precondition is not checked.

fromDescList :: [(k, a)] -> MinPQueue k a Source #

\(O(n)\). Build a priority queue from a descending list of (key, value) pairs. The precondition is not checked.

Conversion to lists

keys :: Ord k => MinPQueue k a -> [k] Source #

\(O(n \log n)\). Return all keys of the queue in ascending order.

elems :: Ord k => MinPQueue k a -> [a] Source #

\(O(n \log n)\). Return all elements of the queue in ascending order by key.

assocs :: Ord k => MinPQueue k a -> [(k, a)] Source #

\(O(n \log n)\). Equivalent to toAscList.

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

\(O(n \log n)\). Return all (key, value) pairs in ascending order by key.

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

\(O(n \log n)\). Return all (key, value) pairs in descending order by key.

toList :: Ord k => MinPQueue k a -> [(k, a)] Source #

\(O(n \log n)\). Equivalent to toAscList.

If the traversal order is irrelevant, consider using toListU.

Unordered operations

foldrU :: (a -> b -> b) -> b -> MinPQueue k a -> b Source #

\(O(n)\). An unordered right fold over the elements of the queue, in no particular order.

foldMapWithKeyU :: Monoid m => (k -> a -> m) -> MinPQueue k a -> m Source #

\(O(n)\). An unordered monoidal fold over the elements of the queue, in no particular order.

Since: 1.4.2

foldrWithKeyU :: (k -> a -> b -> b) -> b -> MinPQueue k a -> b Source #

\(O(n)\). An unordered right fold over the elements of the queue, in no particular order.

foldlU :: (b -> a -> b) -> b -> MinPQueue k a -> b Source #

\(O(n)\). An unordered left fold over the elements of the queue, in no particular order. This is rarely what you want; foldrU and foldlU' are more likely to perform well.

foldlU' :: (b -> a -> b) -> b -> MinPQueue k a -> b Source #

\(O(n)\). An unordered strict left fold over the elements of the queue, in no particular order.

Since: 1.4.2

foldlWithKeyU :: (b -> k -> a -> b) -> b -> MinPQueue k a -> b Source #

\(O(n)\). An unordered left fold over the elements of the queue, in no particular order. This is rarely what you want; foldrWithKeyU and foldlWithKeyU' are more likely to perform well.

foldlWithKeyU' :: (b -> k -> a -> b) -> b -> MinPQueue k a -> b Source #

\(O(n)\). An unordered strict left fold over the elements of the queue, in no particular order.

Since: 1.4.2

traverseU :: Applicative f => (a -> f b) -> MinPQueue k a -> f (MinPQueue k b) Source #

\(O(n)\). An unordered traversal over a priority queue, in no particular order. While there is no guarantee in which order the elements are traversed, the resulting priority queue will be perfectly valid.

traverseWithKeyU :: Applicative f => (k -> a -> f b) -> MinPQueue k a -> f (MinPQueue k b) Source #

\(O(n)\). An unordered traversal over a priority queue, in no particular order. While there is no guarantee in which order the elements are traversed, the resulting priority queue will be perfectly valid.

keysU :: MinPQueue k a -> [k] Source #

\(O(n)\). Return all keys of the queue in no particular order.

elemsU :: MinPQueue k a -> [a] Source #

\(O(n)\). Return all elements of the queue in no particular order.

assocsU :: MinPQueue k a -> [(k, a)] Source #

\(O(n)\). Equivalent to toListU.

toListU :: MinPQueue k a -> [(k, a)] Source #

\(O(n)\). Returns all (key, value) pairs in the queue in no particular order.

Helper methods

seqSpine :: MinPQueue k a -> b -> b Source #

\(O(\log n)\). seqSpine q r forces the spine of q and returns r.

Note: The spine of a MinPQueue is stored somewhat lazily. Most operations take great care to prevent chains of thunks from accumulating along the spine to the detriment of performance. However, mapKeysMonotonic can leave expensive thunks in the structure and repeated applications of that function can create thunk chains.