PSQueue-1.1.1: Priority Search Queue
Safe HaskellSafe
LanguageHaskell2010

Data.PSQueue.Internal

Synopsis

Binding Type

data Binding k p Source #

k :-> p binds the key k with the priority p.

Constructors

k :-> p infix 0 

Instances

Instances details
(Read k, Read p) => Read (Binding k p) Source # 
Instance details

Defined in Data.PSQueue.Internal

(Show k, Show p) => Show (Binding k p) Source # 
Instance details

Defined in Data.PSQueue.Internal

Methods

showsPrec :: Int -> Binding k p -> ShowS #

show :: Binding k p -> String #

showList :: [Binding k p] -> ShowS #

(Eq k, Eq p) => Eq (Binding k p) Source # 
Instance details

Defined in Data.PSQueue.Internal

Methods

(==) :: Binding k p -> Binding k p -> Bool #

(/=) :: Binding k p -> Binding k p -> Bool #

(Ord k, Ord p) => Ord (Binding k p) Source # 
Instance details

Defined in Data.PSQueue.Internal

Methods

compare :: Binding k p -> Binding k p -> Ordering #

(<) :: Binding k p -> Binding k p -> Bool #

(<=) :: Binding k p -> Binding k p -> Bool #

(>) :: Binding k p -> Binding k p -> Bool #

(>=) :: Binding k p -> Binding k p -> Bool #

max :: Binding k p -> Binding k p -> Binding k p #

min :: Binding k p -> Binding k p -> Binding k p #

key :: Binding k p -> k Source #

The key of a binding

prio :: Binding k p -> p Source #

The priority of a binding

Priority Search Queue Type

data PSQ k p Source #

A mapping from keys k to priorites p.

Constructors

Void 
Winner k p (LTree k p) k 

Instances

Instances details
(Show k, Show p, Ord k, Ord p) => Show (PSQ k p) Source # 
Instance details

Defined in Data.PSQueue.Internal

Methods

showsPrec :: Int -> PSQ k p -> ShowS #

show :: PSQ k p -> String #

showList :: [PSQ k p] -> ShowS #

Query

size :: PSQ k p -> Int Source #

O(1) The number of bindings in a queue.

null :: PSQ k p -> Bool Source #

O(1) True if the queue is empty.

lookup :: (Ord k, Ord p) => k -> PSQ k p -> Maybe p Source #

O(log n) The priority of a given key, or Nothing if the key is not bound.

Construction

empty :: (Ord k, Ord p) => PSQ k p Source #

singleton :: (Ord k, Ord p) => k -> p -> PSQ k p Source #

O(1) Build a queue with one binding.

Insertion

insert :: (Ord k, Ord p) => k -> p -> PSQ k p -> PSQ k p Source #

O(log n) Insert a binding into the queue.

insertWith :: (Ord k, Ord p) => (p -> p -> p) -> k -> p -> PSQ k p -> PSQ k p Source #

O(log n) Insert a binding with a combining function.

insertWithKey :: (Ord k, Ord p) => (k -> p -> p -> p) -> k -> p -> PSQ k p -> PSQ k p Source #

O(log n) Insert a binding with a combining function.

Delete/Update

delete :: (Ord k, Ord p) => k -> PSQ k p -> PSQ k p Source #

O(log n) Remove a binding from the queue.

adjust :: (Ord p, Ord k) => (p -> p) -> k -> PSQ k p -> PSQ k p Source #

O(log n) Adjust the priority of a key.

adjustWithKey :: (Ord k, Ord p) => (k -> p -> p) -> k -> PSQ k p -> PSQ k p Source #

O(log n) Adjust the priority of a key.

update :: (Ord k, Ord p) => (p -> Maybe p) -> k -> PSQ k p -> PSQ k p Source #

O(log n) The expression (update f k q) updates the priority p bound k (if it is in the queue). If (f p) is Nothing, the binding is deleted. If it is (Just z), the key k is bound to the new priority z.

updateWithKey :: (Ord k, Ord p) => (k -> p -> Maybe p) -> k -> PSQ k p -> PSQ k p Source #

O(log n). The expression (updateWithKey f k q) updates the priority p bound k (if it is in the queue). If (f k p) is Nothing, the binding is deleted. If it is (Just z), the key k is bound to the new priority z.

alter :: (Ord k, Ord p) => (Maybe p -> Maybe p) -> k -> PSQ k p -> PSQ k p Source #

O(log n). The expression (alter f k q) alters the priority p bound to k, or absence thereof. alter can be used to insert, delete, or update a priority in a queue.

Conversion

keys :: (Ord k, Ord p) => PSQ k p -> [k] Source #

O(n) The keys of a priority queue

fromList :: (Ord k, Ord p) => [Binding k p] -> PSQ k p Source #

O(n log n) Build a queue from a list of bindings.

fromAscList :: (Ord k, Ord p) => [Binding k p] -> PSQ k p Source #

O(n) Build a queue from a list of bindings in order of ascending keys. The precondition that the keys are ascending is not checked.

fromDistinctAscList :: (Ord k, Ord p) => [Binding k p] -> PSQ k p Source #

O(n) Build a queue from a list of distinct bindings in order of ascending keys. The precondition that keys are distinct and ascending is not checked.

foldm :: (a -> a -> a) -> a -> [a] -> a Source #

toList :: (Ord k, Ord p) => PSQ k p -> [Binding k p] Source #

O(n) Convert a queue to a list.

toAscList :: (Ord k, Ord p) => PSQ k p -> [Binding k p] Source #

O(n) Convert a queue to a list in ascending order of keys.

toAscLists :: (Ord k, Ord p) => PSQ k p -> Sequ (Binding k p) Source #

toDescList :: (Ord k, Ord p) => PSQ k p -> [Binding k p] Source #

O(n) Convert a queue to a list in descending order of keys.

toDescLists :: (Ord k, Ord p) => PSQ k p -> Sequ (Binding k p) Source #

Priority Queue

findMin :: (Ord k, Ord p) => PSQ k p -> Maybe (Binding k p) Source #

O(1) The binding with the lowest priority.

deleteMin :: (Ord k, Ord p) => PSQ k p -> PSQ k p Source #

O(log n) Remove the binding with the lowest priority.

minView :: (Ord k, Ord p) => PSQ k p -> Maybe (Binding k p, PSQ k p) Source #

O(log n) Retrieve the binding with the least priority, and the rest of the queue stripped of that binding.

secondBest :: (Ord k, Ord p) => LTree k p -> k -> PSQ k p Source #

atMost :: (Ord k, Ord p) => p -> PSQ k p -> [Binding k p] Source #

O(r(log n - log r) atMost p q is a list of all the bindings in q with priority less than p, in order of ascending keys. Effectively,

  atMost p' q = filter (\(k:->p) -> p<=p') . toList

atMosts :: (Ord k, Ord p) => p -> PSQ k p -> Sequ (Binding k p) Source #

atMostRange :: (Ord k, Ord p) => p -> (k, k) -> PSQ k p -> [Binding k p] Source #

O(r(log n - log r)) atMostRange p (l,u) q is a list of all the bindings in q with a priority less than p and a key in the range (l,u) inclusive. Effectively,

   atMostRange p' (l,u) q = filter (\(k:->p) -> l<=k && k<=u ) . atMost p'

atMostRanges :: (Ord k, Ord p) => p -> (k, k) -> PSQ k p -> Sequ (Binding k p) Source #

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

Fold

foldr :: (Ord k, Ord p) => (Binding k p -> b -> b) -> b -> PSQ k p -> b Source #

Right fold over the bindings in the queue, in key order.

foldl :: (Ord k, Ord p) => (b -> Binding k p -> b) -> b -> PSQ k p -> b Source #

Left fold over the bindings in the queue, in key order.

Internals

type Size = Int Source #

data LTree k p Source #

Constructors

Start 
LLoser !Size !k !p (LTree k p) !k (LTree k p) 
RLoser !Size !k !p (LTree k p) !k (LTree k p) 

size' :: LTree k p -> Size Source #

left :: LTree a b -> LTree a b Source #

right :: LTree a b -> LTree a b Source #

maxKey :: PSQ k p -> k Source #

lloser :: k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rloser :: k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

lbalance :: (Ord k, Ord p) => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rbalance :: (Ord k, Ord p) => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

lbalanceLeft :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

lbalanceRight :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rbalanceLeft :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rbalanceRight :: Ord a => k -> a -> LTree k a -> k -> LTree k a -> LTree k a Source #

lsingleLeft :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rsingleLeft :: k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

lsingleRight :: k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rsingleRight :: Ord a => k -> a -> LTree k a -> k -> LTree k a -> LTree k a Source #

ldoubleLeft :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

ldoubleRight :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rdoubleLeft :: Ord p => k -> p -> LTree k p -> k -> LTree k p -> LTree k p Source #

rdoubleRight :: Ord a => k -> a -> LTree k a -> k -> LTree k a -> LTree k a Source #

play :: (Ord k, Ord p) => PSQ k p -> PSQ k p -> PSQ k p Source #

unsafePlay :: (Ord k, Ord p) => PSQ k p -> PSQ k p -> PSQ k p Source #

data TourView k p Source #

Constructors

Null 
Single k p 
(PSQ k p) `Play` (PSQ k p) 

tourView :: Ord k => PSQ k p -> TourView k p Source #