| Copyright | (c) Marco Zocca 2020 |
|---|---|
| License | BSD3-style (see LICENSE) |
| Maintainer | @ocramz |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.DEPQ
Description
Double-ended priority queue (DEPQ)
Allows for efficiently finding and removing both the minimum and maximum priority elements, due to the min-heap invariant property of the underlying representation.
See https://en.wikipedia.org/wiki/Double-ended_priority_queue for definitions; the current implementation is based on the "dual structure" method outlined in the wikipedia page.
Based on IntPSQ : https://hackage.haskell.org/package/psqueues-0.2.7.2/docs/Data-IntPSQ.html
Usage
Populate a DEPQ (either from a Foldable collection such as a list or array or by inserting incrementally) and query either of its extremes (with findMin, findMax, popMin, popMax, topK, bottomK).
Note
Import this module qualified (e.g. import qualified Data.DEPQ as DQ or similar), as some of the function names are pretty common (e.g. lookup, empty), and might collide with similar functions imported from other libraries.
Synopsis
- data DEPQ p a
- empty :: DEPQ p a
- fromList :: (Foldable t, Ord p) => t (Int, p, a) -> DEPQ p a
- toList :: DEPQ p v -> [(Int, p, v)]
- null :: DEPQ p v -> Bool
- valid :: Ord p => DEPQ p v -> Bool
- size :: DEPQ p a -> Int
- insert :: Ord p => Int -> p -> a -> DEPQ p a -> DEPQ p a
- delete :: Ord p => Int -> DEPQ p a -> DEPQ p a
- deleteMin :: Ord p => DEPQ p a -> DEPQ p a
- deleteMax :: Ord p => DEPQ p a -> DEPQ p a
- popMin :: Ord p => DEPQ p v -> Maybe ((Int, p, v), DEPQ p v)
- popMax :: Ord p => DEPQ p v -> Maybe ((Int, p, v), DEPQ p v)
- lookup :: Int -> DEPQ p v -> Maybe (p, v)
- findMin :: Ord p => DEPQ p v -> Maybe (Int, p, v)
- findMax :: Ord p => DEPQ p v -> Maybe (Int, p, v)
- topK :: Ord p => Int -> DEPQ p v -> Seq (Int, p, v)
- bottomK :: Ord p => Int -> DEPQ p v -> Seq (Int, p, v)
Documentation
A double-ended priority queue
Instances
| Foldable (DEPQ p) Source # | |
Defined in Data.DEPQ Methods fold :: Monoid m => DEPQ p m -> m # foldMap :: Monoid m => (a -> m) -> DEPQ p a -> m # foldMap' :: Monoid m => (a -> m) -> DEPQ p a -> m # foldr :: (a -> b -> b) -> b -> DEPQ p a -> b # foldr' :: (a -> b -> b) -> b -> DEPQ p a -> b # foldl :: (b -> a -> b) -> b -> DEPQ p a -> b # foldl' :: (b -> a -> b) -> b -> DEPQ p a -> b # foldr1 :: (a -> a -> a) -> DEPQ p a -> a # foldl1 :: (a -> a -> a) -> DEPQ p a -> a # elem :: Eq a => a -> DEPQ p a -> Bool # maximum :: Ord a => DEPQ p a -> a # minimum :: Ord a => DEPQ p a -> a # | |
| (Ord p, Eq a) => Eq (DEPQ p a) Source # | |
| (Show p, Show a) => Show (DEPQ p a) Source # | |
| (Ord p, Arbitrary p, Arbitrary a) => Arbitrary (DEPQ p a) Source # | |
| (NFData p, NFData a) => NFData (DEPQ p a) Source # | |
Creation
Conversion from/to lists
Populate a DEPQ from a Foldable container (e.g. a list)
toList :: DEPQ p v -> [(Int, p, v)] Source #
Produce a list of (key, priority, value) triples with the entries of the DEPQ
Note : the order of the output list is undefined
Predicates
Properties
Modification
Insert an element
Delete a (key, priority, value) triple from the queue. When the key is not a member of the queue, the original queue is returned.
popMin :: Ord p => DEPQ p v -> Maybe ((Int, p, v), DEPQ p v) Source #
Return the minimum along with a new DEPQ without that element
popMax :: Ord p => DEPQ p v -> Maybe ((Int, p, v), DEPQ p v) Source #
Return the maximum along with a new DEPQ without that element
Lookup
findMin :: Ord p => DEPQ p v -> Maybe (Int, p, v) Source #
O(1) Find the minimum-priority element in the DEPQ
findMax :: Ord p => DEPQ p v -> Maybe (Int, p, v) Source #
O(1) Find the maximum-priority element in the DEPQ