| Copyright | (c) Louis Wasserman 2010 | 
|---|---|
| License | BSD-style | 
| Maintainer | libraries@haskell.org | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.PQueue.Max
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.
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
- data MaxQueue a
- empty :: MaxQueue a
- null :: MaxQueue a -> Bool
- size :: MaxQueue a -> Int
- findMax :: MaxQueue a -> a
- getMax :: MaxQueue a -> Maybe a
- deleteMax :: Ord a => MaxQueue a -> MaxQueue a
- deleteFindMax :: Ord a => MaxQueue a -> (a, MaxQueue a)
- delete :: Ord a => MaxQueue a -> Maybe (MaxQueue a)
- maxView :: Ord a => MaxQueue a -> Maybe (a, MaxQueue a)
- singleton :: a -> MaxQueue a
- insert :: Ord a => a -> MaxQueue a -> MaxQueue a
- union :: Ord a => MaxQueue a -> MaxQueue a -> MaxQueue a
- unions :: Ord a => [MaxQueue a] -> MaxQueue a
- (!!) :: Ord a => MaxQueue a -> Int -> a
- take :: Ord a => Int -> MaxQueue a -> [a]
- drop :: Ord a => Int -> MaxQueue a -> MaxQueue a
- splitAt :: Ord a => Int -> MaxQueue a -> ([a], MaxQueue a)
- takeWhile :: Ord a => (a -> Bool) -> MaxQueue a -> [a]
- dropWhile :: Ord a => (a -> Bool) -> MaxQueue a -> MaxQueue a
- span :: Ord a => (a -> Bool) -> MaxQueue a -> ([a], MaxQueue a)
- break :: Ord a => (a -> Bool) -> MaxQueue a -> ([a], MaxQueue a)
- filter :: Ord a => (a -> Bool) -> MaxQueue a -> MaxQueue a
- partition :: Ord a => (a -> Bool) -> MaxQueue a -> (MaxQueue a, MaxQueue a)
- mapMaybe :: Ord b => (a -> Maybe b) -> MaxQueue a -> MaxQueue b
- mapEither :: (Ord b, Ord c) => (a -> Either b c) -> MaxQueue a -> (MaxQueue b, MaxQueue c)
- map :: Ord b => (a -> b) -> MaxQueue a -> MaxQueue b
- foldrAsc :: Ord a => (a -> b -> b) -> b -> MaxQueue a -> b
- foldlAsc :: Ord a => (b -> a -> b) -> b -> MaxQueue a -> b
- foldrDesc :: Ord a => (a -> b -> b) -> b -> MaxQueue a -> b
- foldlDesc :: Ord a => (b -> a -> b) -> b -> MaxQueue a -> b
- toList :: Ord a => MaxQueue a -> [a]
- toAscList :: Ord a => MaxQueue a -> [a]
- toDescList :: Ord a => MaxQueue a -> [a]
- fromList :: Ord a => [a] -> MaxQueue a
- fromAscList :: [a] -> MaxQueue a
- fromDescList :: [a] -> MaxQueue a
- mapU :: (a -> b) -> MaxQueue a -> MaxQueue b
- foldrU :: (a -> b -> b) -> b -> MaxQueue a -> b
- foldlU :: (b -> a -> b) -> b -> MaxQueue a -> b
- foldlU' :: (b -> a -> b) -> b -> MaxQueue a -> b
- foldMapU :: Monoid m => (a -> m) -> MaxQueue a -> m
- elemsU :: MaxQueue a -> [a]
- toListU :: MaxQueue a -> [a]
- keysQueue :: MaxPQueue k a -> MaxQueue k
- seqSpine :: MaxQueue a -> b -> b
Documentation
A priority queue with elements of type a. Supports extracting the maximum element.
 Implemented as a wrapper around MinQueue.
Instances
| (Data a, Ord a) => Data (MaxQueue a) Source # | |
| Defined in Data.PQueue.Max 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 :: forall r r'. (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 => Monoid (MaxQueue a) Source # | |
| Ord a => Semigroup (MaxQueue a) Source # | |
| Read a => Read (MaxQueue a) Source # | |
| (Ord a, Show a) => Show (MaxQueue a) Source # | |
| NFData a => NFData (MaxQueue a) Source # | |
| Defined in Data.PQueue.Max | |
| Ord a => Eq (MaxQueue a) Source # | |
| Ord a => Ord (MaxQueue a) Source # | |
Basic operations
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
insert :: Ord a => a -> MaxQueue a -> MaxQueue a Source #
\(O(1)\). Insert an element into the priority queue.
union :: Ord a => MaxQueue a -> MaxQueue a -> MaxQueue a Source #
\(O(\log min(n_1,n_2))\). Take the union of two priority queues.
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.
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.
Fold/Functor/Traversable variations
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 strict left fold on a priority queue.
Since: 1.4.2
foldMapU :: Monoid m => (a -> m) -> MaxQueue a -> m Source #
\(O(n)\). Unordered monoidal fold on a priority queue.
Since: 1.4.2
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 #
Deprecated: This function is no longer necessary or useful.
\(O(\log n)\). seqSpine q r forces the spine of q and returns r.
Note: The spine of a MaxQueue is stored somewhat lazily. In earlier
 versions of this package, some operations could produce chains of thunks
 along the spine, occasionally necessitating manual forcing. Now, all
 operations are careful to force enough to avoid this problem.