| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Data.OrdPSQ
Description
An OrdPSQ uses the Ord instance of the key type to build a priority
 search queue.
It is based on Ralf Hinze's work.
- Hinze, R., A Simple Implementation Technique for Priority Search Queues, ICFP 2001, pp. 110-121
http://citeseer.ist.psu.edu/hinze01simple.html
This means it is similar to the PSQueue package but our benchmarks showed it perform quite a bit faster.
Synopsis
- data OrdPSQ k p v
- null :: OrdPSQ k p v -> Bool
- size :: OrdPSQ k p v -> Int
- member :: Ord k => k -> OrdPSQ k p v -> Bool
- lookup :: Ord k => k -> OrdPSQ k p v -> Maybe (p, v)
- findMin :: OrdPSQ k p v -> Maybe (k, p, v)
- empty :: OrdPSQ k p v
- singleton :: k -> p -> v -> OrdPSQ k p v
- insert :: (Ord k, Ord p) => k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v
- delete :: (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v
- deleteMin :: (Ord k, Ord p) => OrdPSQ k p v -> OrdPSQ k p v
- alter :: (Ord k, Ord p) => (Maybe (p, v) -> (b, Maybe (p, v))) -> k -> OrdPSQ k p v -> (b, OrdPSQ k p v)
- alterMin :: (Ord k, Ord p) => (Maybe (k, p, v) -> (b, Maybe (k, p, v))) -> OrdPSQ k p v -> (b, OrdPSQ k p v)
- fromList :: (Ord k, Ord p) => [(k, p, v)] -> OrdPSQ k p v
- toList :: OrdPSQ k p v -> [(k, p, v)]
- toAscList :: OrdPSQ k p v -> [(k, p, v)]
- keys :: OrdPSQ k p v -> [k]
- insertView :: (Ord k, Ord p) => k -> p -> v -> OrdPSQ k p v -> (Maybe (p, v), OrdPSQ k p v)
- deleteView :: (Ord k, Ord p) => k -> OrdPSQ k p v -> Maybe (p, v, OrdPSQ k p v)
- minView :: (Ord k, Ord p) => OrdPSQ k p v -> Maybe (k, p, v, OrdPSQ k p v)
- atMostView :: (Ord k, Ord p) => p -> OrdPSQ k p v -> ([(k, p, v)], OrdPSQ k p v)
- map :: forall k p v w. (k -> p -> v -> w) -> OrdPSQ k p v -> OrdPSQ k p w
- unsafeMapMonotonic :: forall k p q v w. (k -> p -> v -> (q, w)) -> OrdPSQ k p v -> OrdPSQ k q w
- fold' :: (k -> p -> v -> a -> a) -> a -> OrdPSQ k p v -> a
- valid :: (Ord k, Ord p) => OrdPSQ k p v -> Bool
Type
A mapping from keys k to priorites p and values v. It is strict in
 keys, priorities and values.
Instances
| Functor (OrdPSQ k p) Source # | |
| Foldable (OrdPSQ k p) Source # | |
| Defined in Data.OrdPSQ.Internal Methods fold :: Monoid m => OrdPSQ k p m -> m # foldMap :: Monoid m => (a -> m) -> OrdPSQ k p a -> m # foldr :: (a -> b -> b) -> b -> OrdPSQ k p a -> b # foldr' :: (a -> b -> b) -> b -> OrdPSQ k p a -> b # foldl :: (b -> a -> b) -> b -> OrdPSQ k p a -> b # foldl' :: (b -> a -> b) -> b -> OrdPSQ k p a -> b # foldr1 :: (a -> a -> a) -> OrdPSQ k p a -> a # foldl1 :: (a -> a -> a) -> OrdPSQ k p a -> a # toList :: OrdPSQ k p a -> [a] # null :: OrdPSQ k p a -> Bool # length :: OrdPSQ k p a -> Int # elem :: Eq a => a -> OrdPSQ k p a -> Bool # maximum :: Ord a => OrdPSQ k p a -> a # minimum :: Ord a => OrdPSQ k p a -> a # | |
| Traversable (OrdPSQ k p) Source # | |
| Defined in Data.OrdPSQ.Internal | |
| (Ord k, Ord p, Eq v) => Eq (OrdPSQ k p v) Source # | |
| (Show k, Show p, Show v) => Show (OrdPSQ k p v) Source # | |
| (NFData k, NFData p, NFData v) => NFData (OrdPSQ k p v) Source # | |
| Defined in Data.OrdPSQ.Internal | |
Query
member :: Ord k => k -> OrdPSQ k p v -> Bool Source #
O(log n) Check if a key is present in the the queue.
lookup :: Ord k => k -> OrdPSQ k p v -> Maybe (p, v) Source #
O(log n) The priority and value of a given key, or Nothing if the key
 is not bound.
Construction
Insertion
insert :: (Ord k, Ord p) => k -> p -> v -> OrdPSQ k p v -> OrdPSQ k p v Source #
O(log n) Insert a new key, priority and value into the queue. If the key is already present in the queue, the associated priority and value are replaced with the supplied priority and value.
Delete/Update
delete :: (Ord k, Ord p) => k -> OrdPSQ k p v -> OrdPSQ k p v Source #
O(log n) Delete a key and its priority and value from the queue. When the key is not a member of the queue, the original queue is returned.
deleteMin :: (Ord k, Ord p) => OrdPSQ k p v -> OrdPSQ k p v Source #
O(log n) Delete the binding with the least priority, and return the rest of the queue stripped of that binding. In case the queue is empty, the empty queue is returned again.
alter :: (Ord k, Ord p) => (Maybe (p, v) -> (b, Maybe (p, v))) -> k -> OrdPSQ k p v -> (b, OrdPSQ k p v) Source #
O(log n) The expression alter f k queue alters the value x at k, or
 absence thereof. alter can be used to insert, delete, or update a value
 in a queue. It also allows you to calculate an additional value b.
alterMin :: (Ord k, Ord p) => (Maybe (k, p, v) -> (b, Maybe (k, p, v))) -> OrdPSQ k p v -> (b, OrdPSQ k p v) Source #
Conversion
fromList :: (Ord k, Ord p) => [(k, p, v)] -> OrdPSQ k p v Source #
O(n*log n) Build a queue from a list of (key, priority, value) tuples. If the list contains more than one priority and value for the same key, the last priority and value for the key is retained.
toList :: OrdPSQ k p v -> [(k, p, v)] Source #
O(n) Convert a queue to a list of (key, priority, value) tuples. The order of the list is not specified.
Views
insertView :: (Ord k, Ord p) => k -> p -> v -> OrdPSQ k p v -> (Maybe (p, v), OrdPSQ k p v) Source #
O(log n) Insert a new key, priority and value into the queue. If the key is already present in the queue, then the evicted priority and value can be found the first element of the returned tuple.
deleteView :: (Ord k, Ord p) => k -> OrdPSQ k p v -> Maybe (p, v, OrdPSQ k p v) Source #
O(log n) Delete a key and its priority and value from the queue. If the key was present, the associated priority and value are returned in addition to the updated queue.
minView :: (Ord k, Ord p) => OrdPSQ k p v -> Maybe (k, p, v, OrdPSQ k p v) Source #
O(log n) Retrieve the binding with the least priority, and the rest of the queue stripped of that binding.
atMostView :: (Ord k, Ord p) => p -> OrdPSQ k p v -> ([(k, p, v)], OrdPSQ k p v) Source #
Return a list of elements ordered by key whose priorities are at most pt,
 and the rest of the queue stripped of these elements.  The returned list of
 elements can be in any order: no guarantees there.
Traversals
map :: forall k p v w. (k -> p -> v -> w) -> OrdPSQ k p v -> OrdPSQ k p w Source #
O(n) Modify every value in the queue.
unsafeMapMonotonic :: forall k p q v w. (k -> p -> v -> (q, w)) -> OrdPSQ k p v -> OrdPSQ k q w Source #
O(n) Maps a function over the values and priorities of the queue.
 The function f must be monotonic with respect to the priorities. I.e. if
 x < y, then fst (f k x v) < fst (f k y v).
 The precondition is not checked. If f is not monotonic, then the result
 will be invalid.
fold' :: (k -> p -> v -> a -> a) -> a -> OrdPSQ k p v -> a Source #
O(n) Strict fold over every key, priority and value in the queue. The order in which the fold is performed is not specified.