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

Copyright(c) Louis Wasserman 2010
LicenseBSD-style
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.PQueue.Max

Contents

Description

General purpose priority queue, supporting view-maximum operations.

An amortized running time is given for each operation, with n referring to the length of the sequence and k 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 lazily. To force the spine of the heap, use seqSpine.

This implementation does not guarantee stable behavior.

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 MaxQueue a Source #

A priority queue with elements of type a. Supports extracting the maximum element. Implemented as a wrapper around MinQueue.

Instances

Ord a => Eq (MaxQueue a) Source # 

Methods

(==) :: MaxQueue a -> MaxQueue a -> Bool #

(/=) :: MaxQueue a -> MaxQueue a -> Bool #

(Ord a, Data a) => Data (MaxQueue a) Source # 

Methods

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

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

toConstr :: MaxQueue a -> Constr #

dataTypeOf :: MaxQueue a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (MaxQueue a) Source # 

Methods

compare :: MaxQueue a -> MaxQueue a -> Ordering #

(<) :: MaxQueue a -> MaxQueue a -> Bool #

(<=) :: MaxQueue a -> MaxQueue a -> Bool #

(>) :: MaxQueue a -> MaxQueue a -> Bool #

(>=) :: MaxQueue a -> MaxQueue a -> Bool #

max :: MaxQueue a -> MaxQueue a -> MaxQueue a #

min :: MaxQueue a -> MaxQueue a -> MaxQueue a #

Read a => Read (MaxQueue a) Source # 
(Ord a, Show a) => Show (MaxQueue a) Source # 

Methods

showsPrec :: Int -> MaxQueue a -> ShowS #

show :: MaxQueue a -> String #

showList :: [MaxQueue a] -> ShowS #

Ord a => Monoid (MaxQueue a) Source # 

Methods

mempty :: MaxQueue a #

mappend :: MaxQueue a -> MaxQueue a -> MaxQueue a #

mconcat :: [MaxQueue a] -> MaxQueue a #

NFData a => NFData (MaxQueue a) Source # 

Methods

rnf :: MaxQueue a -> () #

Basic operations

empty :: MaxQueue a Source #

O(1). The empty priority queue.

null :: MaxQueue a -> Bool Source #

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

size :: MaxQueue a -> Int Source #

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

Query operations

findMax :: MaxQueue a -> a Source #

O(1). Returns the maximum element of the queue. Throws an error on an empty queue.

getMax :: MaxQueue a -> Maybe a Source #

O(1). The top (maximum) element of the queue, if there is one.

deleteMax :: Ord a => MaxQueue a -> MaxQueue a Source #

O(log n). Deletes the maximum element of the queue. Does nothing on an empty queue.

deleteFindMax :: Ord a => MaxQueue a -> (a, MaxQueue a) Source #

O(log n). Extracts the maximum element of the queue. Throws an error on an empty queue.

delete :: Ord a => MaxQueue a -> Maybe (MaxQueue a) Source #

O(log n). Delete the top (maximum) element of the sequence, if there is one.

maxView :: Ord a => MaxQueue a -> Maybe (a, MaxQueue a) Source #

O(log n). Extract the top (maximum) element of the sequence, if there is one.

Construction operations

singleton :: a -> MaxQueue a Source #

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

insert :: Ord a => a -> MaxQueue a -> MaxQueue a Source #

O(1). Insert an element into the priority queue.

insertBehind :: Ord a => a -> MaxQueue a -> MaxQueue a Source #

Amortized O(1), worst-case O(log n). Insert an element into the priority queue, putting it behind elements that compare equal to the inserted one.

union :: Ord a => MaxQueue a -> MaxQueue a -> MaxQueue a Source #

O(log (min(n1,n2))). Take the union of two priority queues.

unions :: Ord a => [MaxQueue a] -> MaxQueue a Source #

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

Subsets

Extracting subsets

(!!) :: Ord a => MaxQueue a -> Int -> a Source #

O(k log n). Returns the (k+1)th largest element of the queue.

take :: Ord a => Int -> MaxQueue a -> [a] Source #

O(k log n). Returns the list of the k largest elements of the queue, in descending order, or all elements of the queue, if k >= n.

drop :: Ord a => Int -> MaxQueue a -> MaxQueue a Source #

O(k log n). Returns the queue with the k largest elements deleted, or the empty queue if k >= n.

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

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

Predicates

takeWhile :: Ord a => (a -> Bool) -> MaxQueue 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) -> MaxQueue a -> MaxQueue a Source #

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

span :: Ord a => (a -> Bool) -> MaxQueue a -> ([a], MaxQueue 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) -> MaxQueue a -> ([a], MaxQueue 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) -> MaxQueue a -> MaxQueue a Source #

O(n). Returns a queue of those elements which satisfy the predicate.

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

O(n). Returns a pair of queues, where the left queue contains those elements that satisfy the predicate, and the right queue contains those that do not.

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

O(n). Maps a function over the elements of the queue, and collects the Just values.

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

O(n). Maps a function over the elements of the queue, and separates the Left and Right values.

Fold/Functor/Traversable variations

map :: (a -> b) -> [a] -> [b] #

map f xs is the list obtained by applying f to each element of xs, i.e.,

map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
map f [x1, x2, ...] == [f x1, f x2, ...]

foldrAsc :: Ord a => (a -> b -> b) -> b -> MaxQueue a -> b Source #

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

foldlAsc :: Ord a => (b -> a -> b) -> b -> MaxQueue a -> b Source #

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

foldrDesc :: Ord a => (a -> b -> b) -> b -> MaxQueue a -> b Source #

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

foldlDesc :: Ord a => (b -> a -> b) -> b -> MaxQueue a -> b Source #

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

List operations

toList :: Ord a => MaxQueue a -> [a] Source #

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

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

toAscList :: Ord a => MaxQueue a -> [a] Source #

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

toDescList :: Ord a => MaxQueue a -> [a] Source #

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

fromList :: Ord a => [a] -> MaxQueue a Source #

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

fromAscList :: [a] -> MaxQueue a Source #

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

fromDescList :: [a] -> MaxQueue a Source #

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

Unordered operations

mapU :: (a -> b) -> MaxQueue a -> MaxQueue b Source #

O(n). Assumes that the function it is given is monotonic, and applies this function to every element of the priority queue. Does not check the precondition.

foldrU :: (a -> b -> b) -> b -> MaxQueue a -> b Source #

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

foldlU :: (b -> a -> b) -> b -> MaxQueue a -> b Source #

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

elemsU :: MaxQueue a -> [a] Source #

Equivalent to toListU.

toListU :: MaxQueue a -> [a] Source #

O(n). Returns a list of the elements of the priority queue, in no particular order.

Miscellaneous operations

keysQueue :: MaxPQueue k a -> MaxQueue k Source #

O(n). Constructs a priority queue from the keys of a MaxPQueue.

seqSpine :: MaxQueue a -> b -> b Source #

O(log n). Forces the spine of the heap.