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

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

Data.IntMinMaxQueue

Contents

Description

Double-ended priority queues where priority values are integers, 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).

The implementation is backed by an IntMap (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

IntMinMaxQueue type

data IntMinMaxQueue a Source #

A double-ended priority queue whose elements are compared on an Int field.

Instances
Functor IntMinMaxQueue Source # 
Instance details

Defined in Data.IntMinMaxQueue

Methods

fmap :: (a -> b) -> IntMinMaxQueue a -> IntMinMaxQueue b #

(<$) :: a -> IntMinMaxQueue b -> IntMinMaxQueue a #

Foldable IntMinMaxQueue Source # 
Instance details

Defined in Data.IntMinMaxQueue

Methods

fold :: Monoid m => IntMinMaxQueue m -> m #

foldMap :: Monoid m => (a -> m) -> IntMinMaxQueue a -> m #

foldr :: (a -> b -> b) -> b -> IntMinMaxQueue a -> b #

foldr' :: (a -> b -> b) -> b -> IntMinMaxQueue a -> b #

foldl :: (b -> a -> b) -> b -> IntMinMaxQueue a -> b #

foldl' :: (b -> a -> b) -> b -> IntMinMaxQueue a -> b #

foldr1 :: (a -> a -> a) -> IntMinMaxQueue a -> a #

foldl1 :: (a -> a -> a) -> IntMinMaxQueue a -> a #

toList :: IntMinMaxQueue a -> [a] #

null :: IntMinMaxQueue a -> Bool #

length :: IntMinMaxQueue a -> Int #

elem :: Eq a => a -> IntMinMaxQueue a -> Bool #

maximum :: Ord a => IntMinMaxQueue a -> a #

minimum :: Ord a => IntMinMaxQueue a -> a #

sum :: Num a => IntMinMaxQueue a -> a #

product :: Num a => IntMinMaxQueue a -> a #

Eq1 IntMinMaxQueue Source # 
Instance details

Defined in Data.IntMinMaxQueue

Methods

liftEq :: (a -> b -> Bool) -> IntMinMaxQueue a -> IntMinMaxQueue b -> Bool #

Ord1 IntMinMaxQueue Source # 
Instance details

Defined in Data.IntMinMaxQueue

Methods

liftCompare :: (a -> b -> Ordering) -> IntMinMaxQueue a -> IntMinMaxQueue b -> Ordering #

Read1 IntMinMaxQueue Source # 
Instance details

Defined in Data.IntMinMaxQueue

Show1 IntMinMaxQueue Source # 
Instance details

Defined in Data.IntMinMaxQueue

Methods

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

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

Eq a => Eq (IntMinMaxQueue a) Source # 
Instance details

Defined in Data.IntMinMaxQueue

Data a => Data (IntMinMaxQueue a) Source # 
Instance details

Defined in Data.IntMinMaxQueue

Methods

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

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

toConstr :: IntMinMaxQueue a -> Constr #

dataTypeOf :: IntMinMaxQueue a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (IntMinMaxQueue a) Source # 
Instance details

Defined in Data.IntMinMaxQueue

Read a => Read (IntMinMaxQueue a) Source # 
Instance details

Defined in Data.IntMinMaxQueue

Show a => Show (IntMinMaxQueue a) Source # 
Instance details

Defined in Data.IntMinMaxQueue

type Prio = Int Source #

Construction

empty :: IntMinMaxQueue a Source #

O(1). The empty queue.

singleton :: (a -> Prio) -> a -> IntMinMaxQueue a Source #

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

fromList :: [(Prio, a)] -> IntMinMaxQueue a Source #

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

fromListWith :: (a -> Prio) -> [a] -> IntMinMaxQueue a Source #

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

fromMap :: IntMap (NonEmpty a) -> IntMinMaxQueue a Source #

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

Size

null :: IntMinMaxQueue a -> Bool Source #

O(1). Is the queue empty?

notNull :: IntMinMaxQueue a -> Bool Source #

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

size :: IntMinMaxQueue a -> Int Source #

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

Maximum size

withMaxSize :: IntMinMaxQueue a -> Int -> IntMinMaxQueue 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 :: IntMinMaxQueue 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 :: (a -> Prio) -> a -> IntMinMaxQueue a -> IntMinMaxQueue 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 :: IntMinMaxQueue a -> Maybe a Source #

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

peekMax :: IntMinMaxQueue a -> Maybe a Source #

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

deleteMin :: IntMinMaxQueue a -> IntMinMaxQueue a Source #

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

deleteMax :: IntMinMaxQueue a -> IntMinMaxQueue a Source #

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

pollMin :: IntMinMaxQueue a -> Maybe (a, IntMinMaxQueue a) Source #

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

pollMax :: IntMinMaxQueue a -> Maybe (a, IntMinMaxQueue a) Source #

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

takeMin :: Int -> IntMinMaxQueue a -> IntMinMaxQueue a Source #

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

takeMax :: Int -> IntMinMaxQueue a -> IntMinMaxQueue a Source #

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

dropMin :: Int -> IntMinMaxQueue a -> IntMinMaxQueue a Source #

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

dropMax :: Int -> IntMinMaxQueue a -> IntMinMaxQueue 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) -> IntMinMaxQueue a -> IntMinMaxQueue b Source #

Map a function over all elements in the queue.

mapWithPriority :: (Prio -> a -> b) -> IntMinMaxQueue a -> IntMinMaxQueue b Source #

Map a function over all elements in the queue.

Folds

foldr :: (a -> b -> b) -> b -> IntMinMaxQueue 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 -> IntMinMaxQueue 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 -> IntMinMaxQueue 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 -> IntMinMaxQueue 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) -> IntMinMaxQueue 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 -> IntMinMaxQueue 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 -> IntMinMaxQueue 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 -> IntMinMaxQueue 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 -> IntMinMaxQueue 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 :: IntMinMaxQueue a -> [a] Source #

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

toList :: IntMinMaxQueue a -> [(Prio, a)] Source #

An alias for toAscList.

toAscList :: IntMinMaxQueue 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 :: IntMinMaxQueue 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 :: IntMinMaxQueue a -> IntMap (NonEmpty a) Source #

O(n). Convert the queue to an IntMap.