type-indexed-queues-0.2.0.0: Queues with verified and unverified versions.

Safe HaskellNone
LanguageHaskell2010

Data.Queue.Class

Description

Classes for the various heaps, mainly to avoid name clashing.

Synopsis

Documentation

class Queue h a where Source #

A class for queues. Conforming members can have their own definition of order on their contents. (i.e., Ord is not required)

Minimal complete definition

minView, insert, empty

Methods

minView :: h a -> Maybe (a, h a) Source #

Return the first element, and the remaining elements, or Nothing if the queue is empty. For most queues, this will be the minimal element

insert :: a -> h a -> h a Source #

Insert an element into the queue.

empty :: h a Source #

The empty queue.

singleton :: a -> h a Source #

A queue with one element.

toList :: h a -> [a] Source #

Return a list of the contents of the queue, in order, from smallest to largest.

fromList :: [a] -> h a Source #

Create a heap from a list.

heapSort :: p h -> [a] -> [a] Source #

Perform heap sort on a list of items.

Instances

Queue [] a Source # 

Methods

minView :: [a] -> Maybe (a, [a]) Source #

insert :: a -> [a] -> [a] Source #

empty :: [a] Source #

singleton :: a -> [a] Source #

toList :: [a] -> [a] Source #

fromList :: [a] -> [a] Source #

heapSort :: p [] -> [a] -> [a] Source #

Ord a => Queue Set a Source # 

Methods

minView :: Set a -> Maybe (a, Set a) Source #

insert :: a -> Set a -> Set a Source #

empty :: Set a Source #

singleton :: a -> Set a Source #

toList :: Set a -> [a] Source #

fromList :: [a] -> Set a Source #

heapSort :: p Set -> [a] -> [a] Source #

Ord a => Queue Leftist a Source # 

Methods

minView :: Leftist a -> Maybe (a, Leftist a) Source #

insert :: a -> Leftist a -> Leftist a Source #

empty :: Leftist a Source #

singleton :: a -> Leftist a Source #

toList :: Leftist a -> [a] Source #

fromList :: [a] -> Leftist a Source #

heapSort :: p Leftist -> [a] -> [a] Source #

Ord a => Queue Pairing a Source # 

Methods

minView :: Pairing a -> Maybe (a, Pairing a) Source #

insert :: a -> Pairing a -> Pairing a Source #

empty :: Pairing a Source #

singleton :: a -> Pairing a Source #

toList :: Pairing a -> [a] Source #

fromList :: [a] -> Pairing a Source #

heapSort :: p Pairing -> [a] -> [a] Source #

Ord a => Queue Braun a Source # 

Methods

minView :: Braun a -> Maybe (a, Braun a) Source #

insert :: a -> Braun a -> Braun a Source #

empty :: Braun a Source #

singleton :: a -> Braun a Source #

toList :: Braun a -> [a] Source #

fromList :: [a] -> Braun a Source #

heapSort :: p Braun -> [a] -> [a] Source #

Ord a => Queue Skew a Source # 

Methods

minView :: Skew a -> Maybe (a, Skew a) Source #

insert :: a -> Skew a -> Skew a Source #

empty :: Skew a Source #

singleton :: a -> Skew a Source #

toList :: Skew a -> [a] Source #

fromList :: [a] -> Skew a Source #

heapSort :: p Skew -> [a] -> [a] Source #

Ord a => Queue Splay a Source # 

Methods

minView :: Splay a -> Maybe (a, Splay a) Source #

insert :: a -> Splay a -> Splay a Source #

empty :: Splay a Source #

singleton :: a -> Splay a Source #

toList :: Splay a -> [a] Source #

fromList :: [a] -> Splay a Source #

heapSort :: p Splay -> [a] -> [a] Source #

IndexedQueue h a => Queue (ErasedSize h) a Source # 

Methods

minView :: ErasedSize h a -> Maybe (a, ErasedSize h a) Source #

insert :: a -> ErasedSize h a -> ErasedSize h a Source #

empty :: ErasedSize h a Source #

singleton :: a -> ErasedSize h a Source #

toList :: ErasedSize h a -> [a] Source #

fromList :: [a] -> ErasedSize h a Source #

heapSort :: p (ErasedSize h) -> [a] -> [a] Source #

Queue f a => Queue (WithDict f) a Source # 

Methods

minView :: WithDict f a -> Maybe (a, WithDict f a) Source #

insert :: a -> WithDict f a -> WithDict f a Source #

empty :: WithDict f a Source #

singleton :: a -> WithDict f a Source #

toList :: WithDict f a -> [a] Source #

fromList :: [a] -> WithDict f a Source #

heapSort :: p (WithDict f) -> [a] -> [a] Source #

Ord a => Queue (Binomial Z) a Source # 

Methods

minView :: Binomial Z a -> Maybe (a, Binomial Z a) Source #

insert :: a -> Binomial Z a -> Binomial Z a Source #

empty :: Binomial Z a Source #

singleton :: a -> Binomial Z a Source #

toList :: Binomial Z a -> [a] Source #

fromList :: [a] -> Binomial Z a Source #

heapSort :: p (Binomial Z) -> [a] -> [a] Source #

class Queue h a => MeldableQueue h a where Source #

A class for meldable queues. Conforming members should form a monoid under merge and empty.

Minimal complete definition

merge

Methods

merge :: h a -> h a -> h a Source #

Merge two heaps. This operation is associative, and has the identity of empty.

merge x (merge y z) = merge (merge x y) z
merge x empty = merge empty x = x

fromFoldable :: Foldable f => f a -> h a Source #

Create a heap from a Foldable container. This operation is provided to allow the use of foldMap, which may be asymptotically more efficient. The default definition uses foldMap.

Instances

MeldableQueue [] a Source # 

Methods

merge :: [a] -> [a] -> [a] Source #

fromFoldable :: Foldable f => f a -> [a] Source #

Ord a => MeldableQueue Set a Source # 

Methods

merge :: Set a -> Set a -> Set a Source #

fromFoldable :: Foldable f => f a -> Set a Source #

Ord a => MeldableQueue Leftist a Source # 

Methods

merge :: Leftist a -> Leftist a -> Leftist a Source #

fromFoldable :: Foldable f => f a -> Leftist a Source #

Ord a => MeldableQueue Pairing a Source # 

Methods

merge :: Pairing a -> Pairing a -> Pairing a Source #

fromFoldable :: Foldable f => f a -> Pairing a Source #

Ord a => MeldableQueue Skew a Source # 

Methods

merge :: Skew a -> Skew a -> Skew a Source #

fromFoldable :: Foldable f => f a -> Skew a Source #

Ord a => MeldableQueue Splay a Source # 

Methods

merge :: Splay a -> Splay a -> Splay a Source #

fromFoldable :: Foldable f => f a -> Splay a Source #

MeldableIndexedQueue h a => MeldableQueue (ErasedSize h) a Source # 

Methods

merge :: ErasedSize h a -> ErasedSize h a -> ErasedSize h a Source #

fromFoldable :: Foldable f => f a -> ErasedSize h a Source #

MeldableQueue f a => MeldableQueue (WithDict f) a Source # 

Methods

merge :: WithDict f a -> WithDict f a -> WithDict f a Source #

fromFoldable :: Foldable f => f a -> WithDict f a Source #

Ord a => MeldableQueue (Binomial Z) a Source # 

Methods

merge :: Binomial Z a -> Binomial Z a -> Binomial Z a Source #

fromFoldable :: Foldable f => f a -> Binomial Z a Source #

showsPrecQueue :: (Queue h a, Show a) => Int -> h a -> ShowS Source #

A default definition for showsPrec.

readPrecQueue :: (Read a, Queue h a) => Int -> ReadS (h a) Source #

A default definition for readsPrec.

eqQueue :: (Eq a, Queue h a) => h a -> h a -> Bool Source #

A default definition of ==.

cmpQueue :: (Ord a, Queue h a) => h a -> h a -> Ordering Source #

A default definition of compare.