fingertree-0.1.4.1: Generic finger-tree structure, with example instances

Copyright(c) Ross Paterson 2008
LicenseBSD-style
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilitynon-portable (MPTCs and functional dependencies)
Safe HaskellSafe
LanguageHaskell2010

Data.PriorityQueue.FingerTree

Contents

Description

Min-priority queues implemented using the FingerTree type, following section 4.6 of

These have the same big-O complexity as skew heap implementations, but are approximately an order of magnitude slower. On the other hand, they are stable, so they can be used for fair queueing. They are also shallower, so that fmap consumes less space.

An amortized running time is given for each operation, with n referring to the size of the priority queue. These bounds hold even in a persistent (shared) setting.

Note: Many of these operations have the same names as similar operations on lists in the Prelude. The ambiguity may be resolved using either qualification or the hiding clause.

Synopsis

Documentation

data PQueue k v Source #

Priority queues.

Instances

Ord k => Functor (PQueue k) Source # 

Methods

fmap :: (a -> b) -> PQueue k a -> PQueue k b #

(<$) :: a -> PQueue k b -> PQueue k a #

Ord k => Foldable (PQueue k) Source #

In ascending order of keys.

Methods

fold :: Monoid m => PQueue k m -> m #

foldMap :: Monoid m => (a -> m) -> PQueue k a -> m #

foldr :: (a -> b -> b) -> b -> PQueue k a -> b #

foldr' :: (a -> b -> b) -> b -> PQueue k a -> b #

foldl :: (b -> a -> b) -> b -> PQueue k a -> b #

foldl' :: (b -> a -> b) -> b -> PQueue k a -> b #

foldr1 :: (a -> a -> a) -> PQueue k a -> a #

foldl1 :: (a -> a -> a) -> PQueue k a -> a #

toList :: PQueue k a -> [a] #

null :: PQueue k a -> Bool #

length :: PQueue k a -> Int #

elem :: Eq a => a -> PQueue k a -> Bool #

maximum :: Ord a => PQueue k a -> a #

minimum :: Ord a => PQueue k a -> a #

sum :: Num a => PQueue k a -> a #

product :: Num a => PQueue k a -> a #

(Ord k, Eq v) => Eq (PQueue k v) Source # 

Methods

(==) :: PQueue k v -> PQueue k v -> Bool #

(/=) :: PQueue k v -> PQueue k v -> Bool #

(Ord k, Ord v) => Ord (PQueue k v) Source #

Lexicographical ordering

Methods

compare :: PQueue k v -> PQueue k v -> Ordering #

(<) :: PQueue k v -> PQueue k v -> Bool #

(<=) :: PQueue k v -> PQueue k v -> Bool #

(>) :: PQueue k v -> PQueue k v -> Bool #

(>=) :: PQueue k v -> PQueue k v -> Bool #

max :: PQueue k v -> PQueue k v -> PQueue k v #

min :: PQueue k v -> PQueue k v -> PQueue k v #

(Ord k, Show k, Show v) => Show (PQueue k v) Source #

In ascending key order

Methods

showsPrec :: Int -> PQueue k v -> ShowS #

show :: PQueue k v -> String #

showList :: [PQueue k v] -> ShowS #

Generic (PQueue k v) Source # 

Associated Types

type Rep (PQueue k v) :: * -> * #

Methods

from :: PQueue k v -> Rep (PQueue k v) x #

to :: Rep (PQueue k v) x -> PQueue k v #

Ord k => Semigroup (PQueue k v) Source # 

Methods

(<>) :: PQueue k v -> PQueue k v -> PQueue k v #

sconcat :: NonEmpty (PQueue k v) -> PQueue k v #

stimes :: Integral b => b -> PQueue k v -> PQueue k v #

Ord k => Monoid (PQueue k v) Source #

empty and union

Methods

mempty :: PQueue k v #

mappend :: PQueue k v -> PQueue k v -> PQueue k v #

mconcat :: [PQueue k v] -> PQueue k v #

type Rep (PQueue k v) Source # 
type Rep (PQueue k v)

Construction

empty :: Ord k => PQueue k v Source #

O(1). The empty priority queue.

singleton :: Ord k => k -> v -> PQueue k v Source #

O(1). A singleton priority queue.

union :: Ord k => PQueue k v -> PQueue k v -> PQueue k v Source #

O(log(min(n1,n2))). Concatenate two priority queues. union is associative, with identity empty.

If there are entries with the same priority in both arguments, minView of union xs ys will return those from xs before those from ys.

insert :: Ord k => k -> v -> PQueue k v -> PQueue k v Source #

O(log n). Add a (priority, value) pair to the front of a priority queue.

If q contains entries with the same priority k, minView of insert k v q will return them after this one.

add :: Ord k => k -> v -> PQueue k v -> PQueue k v Source #

O(log n). Add a (priority, value) pair to the back of a priority queue.

If q contains entries with the same priority k, minView of add k v q will return them before this one.

fromList :: Ord k => [(k, v)] -> PQueue k v Source #

O(n). Create a priority queue from a finite list of priorities and values.

Deconstruction

null :: Ord k => PQueue k v -> Bool Source #

O(1). Is this the empty priority queue?

minView :: Ord k => PQueue k v -> Maybe (v, PQueue k v) Source #

O(1) for the element, O(log(n)) for the reduced queue. Returns Nothing for an empty map, or the value associated with the minimal priority together with the rest of the priority queue.

minViewWithKey :: Ord k => PQueue k v -> Maybe ((k, v), PQueue k v) Source #

O(1) for the element, O(log(n)) for the reduced queue. Returns Nothing for an empty map, or the minimal (priority, value) pair together with the rest of the priority queue.