Copyright | (c) Louis Wasserman 2010 |
---|---|
License | BSD-style |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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 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 MinQueue a where
- empty :: MinQueue a
- null :: MinQueue a -> Bool
- size :: MinQueue a -> Int
- findMin :: MinQueue a -> a
- getMin :: MinQueue a -> Maybe a
- deleteMin :: Ord a => MinQueue a -> MinQueue a
- deleteFindMin :: Ord a => MinQueue a -> (a, MinQueue a)
- minView :: Ord a => MinQueue a -> Maybe (a, MinQueue a)
- singleton :: a -> MinQueue a
- insert :: Ord a => a -> MinQueue a -> MinQueue a
- union :: Ord a => MinQueue a -> MinQueue a -> MinQueue a
- unions :: Ord a => [MinQueue a] -> MinQueue a
- (!!) :: Ord a => MinQueue a -> Int -> a
- take :: Ord a => Int -> MinQueue a -> [a]
- drop :: Ord a => Int -> MinQueue a -> MinQueue a
- splitAt :: Ord a => Int -> MinQueue a -> ([a], MinQueue a)
- takeWhile :: Ord a => (a -> Bool) -> MinQueue a -> [a]
- dropWhile :: Ord a => (a -> Bool) -> MinQueue a -> MinQueue a
- span :: Ord a => (a -> Bool) -> MinQueue a -> ([a], MinQueue a)
- break :: Ord a => (a -> Bool) -> MinQueue a -> ([a], MinQueue a)
- filter :: Ord a => (a -> Bool) -> MinQueue a -> MinQueue a
- partition :: Ord a => (a -> Bool) -> MinQueue a -> (MinQueue a, MinQueue a)
- mapMaybe :: Ord b => (a -> Maybe b) -> MinQueue a -> MinQueue b
- mapEither :: (Ord b, Ord c) => (a -> Either b c) -> MinQueue a -> (MinQueue b, MinQueue c)
- map :: Ord b => (a -> b) -> MinQueue a -> MinQueue b
- foldrAsc :: Ord a => (a -> b -> b) -> b -> MinQueue a -> b
- foldlAsc :: Ord a => (b -> a -> b) -> b -> MinQueue a -> b
- foldrDesc :: Ord a => (a -> b -> b) -> b -> MinQueue a -> b
- foldlDesc :: Ord a => (b -> a -> b) -> b -> MinQueue a -> b
- toList :: Ord a => MinQueue a -> [a]
- toAscList :: Ord a => MinQueue a -> [a]
- toDescList :: Ord a => MinQueue a -> [a]
- fromList :: Ord a => [a] -> MinQueue a
- fromAscList :: [a] -> MinQueue a
- fromDescList :: [a] -> MinQueue a
- mapU :: (a -> b) -> MinQueue a -> MinQueue b
- foldrU :: (a -> b -> b) -> b -> MinQueue a -> b
- foldlU :: (b -> a -> b) -> b -> MinQueue a -> b
- foldlU' :: (b -> a -> b) -> b -> MinQueue a -> b
- foldMapU :: Monoid m => (a -> m) -> MinQueue a -> m
- elemsU :: MinQueue a -> [a]
- toListU :: MinQueue a -> [a]
- keysQueue :: MinPQueue k a -> MinQueue k
- seqSpine :: MinQueue a -> b -> b
Documentation
data MinQueue a where Source #
A priority queue with elements of type a
. Supports extracting the minimum element.
pattern Empty :: MinQueue a | A bidirectional pattern synonym for an empty priority queue. Since: 1.5.0 |
pattern (:<) :: Ord a => a -> MinQueue a -> MinQueue a infixr 5 | A bidirectional pattern synonym for working with the minimum view of a
Since: 1.5.0 |
Instances
(Ord a, Data a) => Data (MinQueue a) Source # | Treats the priority queue as an empty queue or a minimal element and a
priority queue. The constructors, conceptually, are |
Defined in Data.PQueue.Internals gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MinQueue a -> c (MinQueue a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MinQueue a) # toConstr :: MinQueue a -> Constr # dataTypeOf :: MinQueue a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MinQueue a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MinQueue a)) # gmapT :: (forall b. Data b => b -> b) -> MinQueue a -> MinQueue a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MinQueue a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MinQueue a -> r # gmapQ :: (forall d. Data d => d -> u) -> MinQueue a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MinQueue a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MinQueue a -> m (MinQueue a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MinQueue a -> m (MinQueue a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MinQueue a -> m (MinQueue a) # | |
Ord a => Monoid (MinQueue a) Source # | |
Ord a => Semigroup (MinQueue a) Source # | |
Read a => Read (MinQueue a) Source # | |
(Ord a, Show a) => Show (MinQueue a) Source # | |
NFData a => NFData (MinQueue a) Source # | |
Defined in Data.PQueue.Internals | |
Ord a => Eq (MinQueue a) Source # | |
Ord a => Ord (MinQueue a) Source # | |
Basic operations
Query operations
findMin :: MinQueue a -> a Source #
\(O(1)\). Returns the minimum element. Throws an error on an empty queue.
getMin :: MinQueue a -> Maybe a Source #
\(O(1)\). Returns the minimum element of the queue, if the queue is nonempty.
deleteMin :: Ord a => MinQueue a -> MinQueue a Source #
\(O(\log n)\). Deletes the minimum element. If the queue is empty, does nothing.
deleteFindMin :: Ord a => MinQueue a -> (a, MinQueue a) Source #
\(O(\log n)\). Extracts the minimum element. Throws an error on an empty queue.
minView :: Ord a => MinQueue a -> Maybe (a, MinQueue a) Source #
Retrieves the minimum element of the queue, and the queue stripped of that element,
or Nothing
if passed an empty queue.
Construction operations
insert :: Ord a => a -> MinQueue a -> MinQueue a Source #
Amortized \(O(1)\), worst-case \(O(\log n)\). Insert an element into the priority queue.
union :: Ord a => MinQueue a -> MinQueue a -> MinQueue a Source #
Amortized \(O(\log \min(n,m))\), worst-case \(O(\log \max(n,m))\). Take the union of two priority queues.
Subsets
Extracting subsets
(!!) :: Ord a => MinQueue a -> Int -> a Source #
\(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
.
drop :: Ord a => Int -> MinQueue a -> MinQueue a Source #
\(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
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
.
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 a Source #
\(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 b Source #
\(O(n)\). Map elements and collect the Just
results.
Fold/Functor/Traversable variations
foldrAsc :: Ord a => (a -> b -> b) -> b -> MinQueue a -> b Source #
\(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 -> b Source #
\(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 -> b Source #
\(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 -> b Source #
\(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
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 a Source #
\(O(n)\). Constructs a priority queue from an unordered list.
fromAscList :: [a] -> MinQueue a Source #
\(O(n)\). Constructs a priority queue from an ascending list. Warning: Does not check the precondition.
Performance note: Code using this function in a performance-sensitive context
with an argument that is a "good producer" for list fusion should be compiled
with -fspec-constr
or -O2
. For example, fromAscList . map f
needs one
of these options for best results.
fromDescList :: [a] -> MinQueue a Source #
\(O(n)\). Constructs a priority queue from an descending list. Warning: Does not check the precondition.
Unordered operations
mapU :: (a -> b) -> MinQueue a -> MinQueue b Source #
\(O(n)\). Assumes that the function it is given is (weakly) monotonic, and
applies this function to every element of the priority queue, as in fmap
.
If the function is not monotonic, the result is undefined.
foldrU :: (a -> b -> b) -> b -> MinQueue a -> b Source #
\(O(n)\). Unordered right fold on a priority queue.
foldlU' :: (b -> a -> b) -> b -> MinQueue a -> b Source #
\(O(n)\). Unordered strict left fold on a priority queue.
Since: 1.4.2
foldMapU :: Monoid m => (a -> m) -> MinQueue a -> m Source #
\(O(n)\). Unordered monoidal fold on a priority queue.
Since: 1.4.2
toListU :: MinQueue a -> [a] Source #
\(O(n)\). Returns the elements of the queue, in no particular order.
Miscellaneous operations
keysQueue :: MinPQueue k a -> MinQueue k Source #
Constructs a priority queue out of the keys of the specified MinPQueue
.
seqSpine :: MinQueue 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 MinQueue
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.