min-max-pqueue-0.1.0.2: Double-ended priority queues.

MaintainerZiyang Liu <free@cofree.io>
Safe HaskellSafe
LanguageHaskell2010

Data.MinMaxQueue

Contents

Description

Double-ended priority queues, allowing efficient retrieval and removel from both ends of the queue.

A queue can be configured with a maximum size. Each time an insertion causes the queue to grow beyond the size limit, the greatest element will be automatically removed (rather than rejecting the insertion).

If the priority values are Ints, use Data.IntMinMaxQueue.

The implementation is backed by a Map prio (NonEmpty a). This means that certain operations, including peekMin, peekMax and fromList, are asymptotically more expensive than a mutable array based implementation. In a pure language like Haskell, a mutable array based implementation would be impure and need to operate inside monads. And in many applications, regardless of language, the additional time complexity would be a small or negligible price to pay to avoid destructive updates anyway.

If you only access one end of the queue (i.e., you need a regular priority queue), an implementation based on a kind of heap that is more amenable to purely functional implementations, such as binomial heap and pairing heap, is potentially more efficient. But always benchmark if performance is important; in my experience Map always wins, even for regular priority queues.

See README.md for more information.

Synopsis

MinMaxQueue type

data MinMaxQueue prio a Source #

A double-ended priority queue whose elements are of type a and are compared on prio.

Instances
Eq2 MinMaxQueue Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> MinMaxQueue a c -> MinMaxQueue b d -> Bool #

Ord2 MinMaxQueue Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> MinMaxQueue a c -> MinMaxQueue b d -> Ordering #

Show2 MinMaxQueue Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> MinMaxQueue a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [MinMaxQueue a b] -> ShowS #

Functor (MinMaxQueue prio) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

fmap :: (a -> b) -> MinMaxQueue prio a -> MinMaxQueue prio b #

(<$) :: a -> MinMaxQueue prio b -> MinMaxQueue prio a #

Foldable (MinMaxQueue prio) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

fold :: Monoid m => MinMaxQueue prio m -> m #

foldMap :: Monoid m => (a -> m) -> MinMaxQueue prio a -> m #

foldr :: (a -> b -> b) -> b -> MinMaxQueue prio a -> b #

foldr' :: (a -> b -> b) -> b -> MinMaxQueue prio a -> b #

foldl :: (b -> a -> b) -> b -> MinMaxQueue prio a -> b #

foldl' :: (b -> a -> b) -> b -> MinMaxQueue prio a -> b #

foldr1 :: (a -> a -> a) -> MinMaxQueue prio a -> a #

foldl1 :: (a -> a -> a) -> MinMaxQueue prio a -> a #

toList :: MinMaxQueue prio a -> [a] #

null :: MinMaxQueue prio a -> Bool #

length :: MinMaxQueue prio a -> Int #

elem :: Eq a => a -> MinMaxQueue prio a -> Bool #

maximum :: Ord a => MinMaxQueue prio a -> a #

minimum :: Ord a => MinMaxQueue prio a -> a #

sum :: Num a => MinMaxQueue prio a -> a #

product :: Num a => MinMaxQueue prio a -> a #

Eq prio => Eq1 (MinMaxQueue prio) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftEq :: (a -> b -> Bool) -> MinMaxQueue prio a -> MinMaxQueue prio b -> Bool #

Ord prio => Ord1 (MinMaxQueue prio) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftCompare :: (a -> b -> Ordering) -> MinMaxQueue prio a -> MinMaxQueue prio b -> Ordering #

(Ord prio, Read prio) => Read1 (MinMaxQueue prio) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (MinMaxQueue prio a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [MinMaxQueue prio a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (MinMaxQueue prio a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [MinMaxQueue prio a] #

Show prio => Show1 (MinMaxQueue prio) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> MinMaxQueue prio a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [MinMaxQueue prio a] -> ShowS #

(Eq prio, Eq a) => Eq (MinMaxQueue prio a) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

(==) :: MinMaxQueue prio a -> MinMaxQueue prio a -> Bool #

(/=) :: MinMaxQueue prio a -> MinMaxQueue prio a -> Bool #

(Data prio, Data a, Ord prio) => Data (MinMaxQueue prio a) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MinMaxQueue prio a -> c (MinMaxQueue prio a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MinMaxQueue prio a) #

toConstr :: MinMaxQueue prio a -> Constr #

dataTypeOf :: MinMaxQueue prio a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MinMaxQueue prio a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MinMaxQueue prio a)) #

gmapT :: (forall b. Data b => b -> b) -> MinMaxQueue prio a -> MinMaxQueue prio a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MinMaxQueue prio a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MinMaxQueue prio a -> r #

gmapQ :: (forall d. Data d => d -> u) -> MinMaxQueue prio a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MinMaxQueue prio a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MinMaxQueue prio a -> m (MinMaxQueue prio a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MinMaxQueue prio a -> m (MinMaxQueue prio a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MinMaxQueue prio a -> m (MinMaxQueue prio a) #

(Ord prio, Ord a) => Ord (MinMaxQueue prio a) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

compare :: MinMaxQueue prio a -> MinMaxQueue prio a -> Ordering #

(<) :: MinMaxQueue prio a -> MinMaxQueue prio a -> Bool #

(<=) :: MinMaxQueue prio a -> MinMaxQueue prio a -> Bool #

(>) :: MinMaxQueue prio a -> MinMaxQueue prio a -> Bool #

(>=) :: MinMaxQueue prio a -> MinMaxQueue prio a -> Bool #

max :: MinMaxQueue prio a -> MinMaxQueue prio a -> MinMaxQueue prio a #

min :: MinMaxQueue prio a -> MinMaxQueue prio a -> MinMaxQueue prio a #

(Ord prio, Read prio, Read a) => Read (MinMaxQueue prio a) Source # 
Instance details

Defined in Data.MinMaxQueue

(Show prio, Show a) => Show (MinMaxQueue prio a) Source # 
Instance details

Defined in Data.MinMaxQueue

Methods

showsPrec :: Int -> MinMaxQueue prio a -> ShowS #

show :: MinMaxQueue prio a -> String #

showList :: [MinMaxQueue prio a] -> ShowS #

Construction

empty :: MinMaxQueue prio a Source #

O(1). The empty queue.

singleton :: (a -> prio) -> a -> MinMaxQueue prio a Source #

O(1). A queue with a single element.

fromList :: Ord prio => [(prio, a)] -> MinMaxQueue prio a Source #

O(n * log n). Build a queue from a list of (priority, element) pairs.

fromListWith :: Ord prio => (a -> prio) -> [a] -> MinMaxQueue prio a Source #

O(n * log n). Build a queue from a list of elements and a function from elements to priorities.

fromMap :: Map prio (NonEmpty a) -> MinMaxQueue prio a Source #

O(n) (due to calculating the queue size).

Size

null :: MinMaxQueue prio a -> Bool Source #

O(1). Is the queue empty?

notNull :: MinMaxQueue prio a -> Bool Source #

O(1). Is the queue non-empty?

size :: MinMaxQueue prio a -> Int Source #

O(1). The total number of elements in the queue.

Maximum size

withMaxSize :: Ord prio => MinMaxQueue prio a -> Int -> MinMaxQueue prio a Source #

Return a queue that is limited to the given number of elements. If the original queue has more elements than the size limit, the greatest elements will be dropped until the size limit is satisfied.

maxSize :: MinMaxQueue prio a -> Maybe Int Source #

O(1). The size limit of the queue. It returns either Nothing (if the queue does not have a size limit) or Just n where n >= 0.

Queue operations

insert :: Ord prio => (a -> prio) -> a -> MinMaxQueue prio a -> MinMaxQueue prio a Source #

O(log n). Add the given element to the queue. If the queue has a size limit, and the insertion causes the queue to grow beyond its size limit, the greatest element will be removed from the queue, which may be the element just added.

peekMin :: Ord prio => MinMaxQueue prio a -> Maybe a Source #

O(log n). Retrieve the least element of the queue, if exists.

peekMax :: Ord prio => MinMaxQueue prio a -> Maybe a Source #

O(log n). Retrieve the greatest element of the queue, if exists.

deleteMin :: Ord prio => MinMaxQueue prio a -> MinMaxQueue prio a Source #

O(log n). Remove the least element of the queue, if exists.

deleteMax :: Ord prio => MinMaxQueue prio a -> MinMaxQueue prio a Source #

O(log n). Remove the greatest element of the queue, if exists.

pollMin :: Ord prio => MinMaxQueue prio a -> Maybe (a, MinMaxQueue prio a) Source #

O(log n). Remove and return the least element of the queue, if exists.

pollMax :: Ord prio => MinMaxQueue prio a -> Maybe (a, MinMaxQueue prio a) Source #

O(log n). Remove and return the greatest element of the queue, if exists.

takeMin :: Ord prio => Int -> MinMaxQueue prio a -> MinMaxQueue prio a Source #

takeMin n q returns a queue with the n least elements in q, or q itself if n >= size q.

takeMax :: Ord prio => Int -> MinMaxQueue prio a -> MinMaxQueue prio a Source #

takeMin n q returns a queue with the n greatest elements in q, or q itself if n >= size q.

dropMin :: Ord prio => Int -> MinMaxQueue prio a -> MinMaxQueue prio a Source #

dropMin n q returns a queue with the n least elements dropped from q, or empty if n >= size q.

dropMax :: Ord prio => Int -> MinMaxQueue prio a -> MinMaxQueue prio a Source #

dropMax n q returns a queue with the n greatest elements dropped from q, or empty if n >= size q.

Traversal

Map

map :: (a -> b) -> MinMaxQueue prio a -> MinMaxQueue prio b Source #

Map a function over all elements in the queue.

mapWithPriority :: (prio -> a -> b) -> MinMaxQueue prio a -> MinMaxQueue prio b Source #

Map a function over all elements in the queue.

Folds

foldr :: (a -> b -> b) -> b -> MinMaxQueue prio a -> b Source #

Fold the elements in the queue using the given right-associative binary operator, such that foldr f z == foldr f z . elems.

foldl :: (a -> b -> a) -> a -> MinMaxQueue prio b -> a Source #

Fold the elements in the queue using the given left-associative binary operator, such that foldl f z == foldl f z . elems.

foldrWithPriority :: (prio -> a -> b -> b) -> b -> MinMaxQueue prio a -> b Source #

Fold the elements in the queue using the given right-associative binary operator, such that foldrWithPriority f z == foldr (uncurry f) z . toAscList.

foldlWithPriority :: (a -> prio -> b -> a) -> a -> MinMaxQueue prio b -> a Source #

Fold the elements in the queue using the given left-associative binary operator, such that foldlWithPriority f z == foldr (uncurry . f) z . toAscList.

foldMapWithPriority :: Monoid m => (prio -> a -> m) -> MinMaxQueue prio a -> m Source #

Fold the elements in the queue using the given monoid, such that foldMapWithPriority f == foldMap (uncurry f) . elems.

Strict Folds

foldr' :: (a -> b -> b) -> b -> MinMaxQueue prio a -> b Source #

A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldl' :: (a -> b -> a) -> a -> MinMaxQueue prio b -> a Source #

A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldrWithPriority' :: (prio -> a -> b -> b) -> b -> MinMaxQueue prio a -> b Source #

A strict version of foldrWithPriority. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldlWithPriority' :: (a -> prio -> b -> a) -> a -> MinMaxQueue prio b -> a Source #

A strict version of foldlWithPriority. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Lists

elems :: MinMaxQueue prio a -> [a] Source #

Elements in the queue in ascending order of priority. Elements with the same priority are returned in no particular order.

toList :: MinMaxQueue prio a -> [(prio, a)] Source #

An alias for toAscList.

toAscList :: MinMaxQueue prio a -> [(prio, a)] Source #

Convert the queue to a list in ascending order of priority. Elements with the same priority are returned in no particular order.

toDescList :: MinMaxQueue prio a -> [(prio, a)] Source #

Convert the queue to a list in descending order of priority. Elements with the same priority are returned in no particular order.

Maps

toMap :: MinMaxQueue prio a -> Map prio (NonEmpty a) Source #

O(n). Convert the queue to a Map.