pqueue-1.0.0: Reliable, persistent, fast priority queues.

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Data.PQueue.Min

Contents

Description

General purpose priority queue, supporting extract-minimum operations.

An amortized running time is given for each operation, with n referring to the length of the sequence and i being the integral index used by some operations. These bounds hold even in a persistent (shared) setting.

This implementation is based on a binomial heap augmented with a global root. The spine of the heap is maintained strictly, ensuring that computations happen as they are performed.

This implementation does not guarantee stable behavior.

WARNING: toList and toAscList are not equivalent, unlike for example Data.Map.

Synopsis

Documentation

data MinQueue a Source

A priority queue implementation. Implemented as a find-min wrapper around a binomial heap.

If you wish to perform folds on a priority queue that respect order, use foldrAsc or foldlAsc.

For any operation op in Eq or Ord, queue1 op queue2 is equivalent to toAscList queue1 op toAscList queue2.

Instances

Typeable1 MinQueue 
Ord a => Eq (MinQueue a) 
(Ord a, Data a) => Data (MinQueue a) 
Ord a => Ord (MinQueue a) 
Read a => Read (MinQueue a) 
(Ord a, Show a) => Show (MinQueue a) 
Ord a => Monoid (MinQueue a) 

Basic operations

empty :: MinQueue aSource

O(1). The empty priority queue.

null :: MinQueue a -> BoolSource

O(1). Is this the empty priority queue?

size :: MinQueue a -> IntSource

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

Query operations

Construction operations

singleton :: a -> MinQueue aSource

O(1). Construct a priority queue with a single element.

insert :: Ord a => a -> MinQueue a -> MinQueue aSource

Amortized O(1), worst-case O(log n). Insert an element into the priority queue.

union :: Ord a => MinQueue a -> MinQueue a -> MinQueue aSource

Amortized O(log (min(n,m))), worst-case O(log (max (n,m))). Take the union of two priority queues.

unions :: Ord a => [MinQueue a] -> MinQueue aSource

Takes the union of a list of priority queues. Equivalent to foldl union empty.

Subsets

Extracting subsets

(!!) :: Ord a => MinQueue a -> Int -> aSource

O(k log n). Index (subscript) operator, starting from 0. queue !! k returns the (k+1)th smallest element in the queue. Equivalent to toAscList queue !! k.

take :: Ord a => Int -> MinQueue a -> [a]Source

O(k log n). take k, applied to a queue queue, returns a list of the smallest k elements of queue, or all elements of queue itself if k >= size queue.

drop :: Ord a => Int -> MinQueue a -> MinQueue aSource

O(k log n). drop k, applied to a queue queue, returns queue with the smallest k elements deleted, or an empty queue if k >= size queue.

splitAt :: Ord a => Int -> MinQueue a -> ([a], MinQueue a)Source

O(k log n). Equivalent to (take k queue, drop k queue).

Predicates

takeWhile :: Ord a => (a -> Bool) -> MinQueue a -> [a]Source

takeWhile, applied to a predicate p and a queue queue, returns the longest prefix (possibly empty) of queue of elements that satisfy p.

dropWhile :: Ord a => (a -> Bool) -> MinQueue a -> MinQueue aSource

dropWhile p queue returns the queue remaining after takeWhile p queue.

span :: Ord a => (a -> Bool) -> MinQueue a -> ([a], MinQueue a)Source

span, applied to a predicate p and a queue queue, returns a tuple where first element is longest prefix (possibly empty) of queue of elements that satisfy p and second element is the remainder of the queue.

break :: Ord a => (a -> Bool) -> MinQueue a -> ([a], MinQueue a)Source

break, applied to a predicate p and a queue queue, returns a tuple where first element is longest prefix (possibly empty) of queue of elements that do not satisfy p and second element is the remainder of the queue.

Filter/Map

filter :: Ord a => (a -> Bool) -> MinQueue a -> MinQueue aSource

O(n). Returns the queue with all elements not satisfying p removed.

partition :: Ord a => (a -> Bool) -> MinQueue a -> (MinQueue a, MinQueue a)Source

O(n). Returns a pair where the first queue contains all elements satisfying p, and the second queue contains all elements not satisfying p.

mapMaybe :: Ord b => (a -> Maybe b) -> MinQueue a -> MinQueue bSource

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

mapEither :: (Ord b, Ord c) => (a -> Either b c) -> MinQueue a -> (MinQueue b, MinQueue c)Source

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

Fold/Functor/Traversable variations

map :: Ord b => (a -> b) -> MinQueue a -> MinQueue bSource

O(n). Creates a new priority queue containing the images of the elements of this queue. Equivalent to fromList . Data.List.map f . toList.

mapMonotonic :: (a -> b) -> MinQueue a -> MinQueue bSource

O(n). Assumes that the function it is given is monotonic, and applies this function to every element of the priority queue, as in fmap. If it is not, the result is undefined.

foldrAsc :: Ord a => (a -> b -> b) -> b -> MinQueue a -> bSource

O(n log n). Performs a right-fold on the elements of a priority queue in ascending order.

foldlAsc :: Ord a => (b -> a -> b) -> b -> MinQueue a -> bSource

O(n log n). Performs a left-fold on the elements of a priority queue in ascending order.

foldrDesc :: Ord a => (a -> b -> b) -> b -> MinQueue a -> bSource

O(n log n). Performs a right-fold on the elements of a priority queue in descending order. foldrDesc f z q == foldlAsc (flip f) z q.

foldlDesc :: Ord a => (b -> a -> b) -> b -> MinQueue a -> bSource

O(n log n). Performs a left-fold on the elements of a priority queue in descending order. foldlDesc f z q == foldrAsc (flip f) z q.

List operations

toList :: Ord a => MinQueue a -> [a]Source

O(n). Returns the elements of the priority queue in ascending order. Equivalent to toAscList.

If the order of the elements is irrelevant, consider using toListU.

toAscList :: Ord a => MinQueue a -> [a]Source

O(n log n). Extracts the elements of the priority queue in ascending order.

toDescList :: Ord a => MinQueue a -> [a]Source

O(n log n). Extracts the elements of the priority queue in descending order.

fromList :: Ord a => [a] -> MinQueue aSource

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

fromAscList :: [a] -> MinQueue aSource

O(n). Constructs a priority queue from an ascending list. Warning: Does not check the precondition.

fromDescList :: [a] -> MinQueue aSource

O(n). Constructs a priority queue from an descending list. Warning: Does not check the precondition.

Unordered operations

foldrU :: (a -> b -> b) -> b -> MinQueue a -> bSource

O(n). Unordered right fold on a priority queue.

foldlU :: (b -> a -> b) -> b -> MinQueue a -> bSource

traverseU :: (Applicative f, Ord b) => (a -> f b) -> MinQueue a -> f (MinQueue b)Source

Miscellaneous operations

keysQueue :: MinPQueue k a -> MinQueue kSource

Constructs a priority queue out of the keys of the specified MinPQueue.

seqSpine :: MinQueue a -> b -> bSource

Forces the spine of the priority queue.