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

Safe HaskellNone
LanguageHaskell2010

Data.Queue.Binomial

Description

Simple binomial heaps, with a statically-enforced shape.

Synopsis

Documentation

data Binomial rk a Source #

A binomial heap, where the sizes of the nodes are enforced in the types.

The implementation is based on:

It is a list of binomial trees, equivalent to a binary number (stored least-significant-bit first).

Constructors

Nil

The empty heap

Skip (Binomial (S rk) a)

Skip a child tree (equivalent to a zero in the binary representation of the data structure).

(:-) !(Tree rk a) (Binomial (S rk) a) infixr 5

A child tree. Equivalent to a one in the binary representation.

Instances

Functor (Binomial rk) Source # 

Methods

fmap :: (a -> b) -> Binomial rk a -> Binomial rk b #

(<$) :: a -> Binomial rk b -> Binomial rk a #

Foldable (Binomial rk) Source # 

Methods

fold :: Monoid m => Binomial rk m -> m #

foldMap :: Monoid m => (a -> m) -> Binomial rk a -> m #

foldr :: (a -> b -> b) -> b -> Binomial rk a -> b #

foldr' :: (a -> b -> b) -> b -> Binomial rk a -> b #

foldl :: (b -> a -> b) -> b -> Binomial rk a -> b #

foldl' :: (b -> a -> b) -> b -> Binomial rk a -> b #

foldr1 :: (a -> a -> a) -> Binomial rk a -> a #

foldl1 :: (a -> a -> a) -> Binomial rk a -> a #

toList :: Binomial rk a -> [a] #

null :: Binomial rk a -> Bool #

length :: Binomial rk a -> Int #

elem :: Eq a => a -> Binomial rk a -> Bool #

maximum :: Ord a => Binomial rk a -> a #

minimum :: Ord a => Binomial rk a -> a #

sum :: Num a => Binomial rk a -> a #

product :: Num a => Binomial rk a -> a #

Traversable (Binomial rk) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Binomial rk a -> f (Binomial rk b) #

sequenceA :: Applicative f => Binomial rk (f a) -> f (Binomial rk a) #

mapM :: Monad m => (a -> m b) -> Binomial rk a -> m (Binomial rk b) #

sequence :: Monad m => Binomial rk (m a) -> m (Binomial rk a) #

Generic1 (Binomial n) Source # 

Associated Types

type Rep1 (Binomial n :: * -> *) :: * -> * #

Methods

from1 :: Binomial n a -> Rep1 (Binomial n) a #

to1 :: Rep1 (Binomial n) a -> Binomial n a #

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 #

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 #

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

Methods

(==) :: Binomial Z a -> Binomial Z a -> Bool #

(/=) :: Binomial Z a -> Binomial Z a -> Bool #

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

Methods

compare :: Binomial Z a -> Binomial Z a -> Ordering #

(<) :: Binomial Z a -> Binomial Z a -> Bool #

(<=) :: Binomial Z a -> Binomial Z a -> Bool #

(>) :: Binomial Z a -> Binomial Z a -> Bool #

(>=) :: Binomial Z a -> Binomial Z a -> Bool #

max :: Binomial Z a -> Binomial Z a -> Binomial Z a #

min :: Binomial Z a -> Binomial Z a -> Binomial Z a #

(Read a, Ord a) => Read (Binomial Z a) Source # 
(Show a, Ord a) => Show (Binomial Z a) Source # 

Methods

showsPrec :: Int -> Binomial Z a -> ShowS #

show :: Binomial Z a -> String #

showList :: [Binomial Z a] -> ShowS #

Generic (Binomial n a) Source # 

Associated Types

type Rep (Binomial n a) :: * -> * #

Methods

from :: Binomial n a -> Rep (Binomial n a) x #

to :: Rep (Binomial n a) x -> Binomial n a #

Ord a => Monoid (Binomial rk a) Source # 

Methods

mempty :: Binomial rk a #

mappend :: Binomial rk a -> Binomial rk a -> Binomial rk a #

mconcat :: [Binomial rk a] -> Binomial rk a #

NFData a => NFData (Binomial rk a) Source # 

Methods

rnf :: Binomial rk a -> () #

type Rep1 (Binomial n) Source # 
type Rep (Binomial n a) Source # 
type Rep (Binomial n a) = D1 (MetaData "Binomial" "Data.Queue.Binomial" "type-indexed-queues-0.1.0.1-GPaLldpmb1Q20PpM0x8M72" False) ((:+:) (C1 (MetaCons "Nil" PrefixI False) U1) ((:+:) (C1 (MetaCons "Skip" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Binomial (S n) a)))) (C1 (MetaCons ":-" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedUnpack) (Rec0 (Tree n a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Binomial (S n) a)))))))

data Node n a where Source #

A list of binomial trees, indexed by their sizes in ascending order.

Constructors

NilN :: Node Z a 
(:<) :: !(Tree n a) -> Node n a -> Node (S n) a 

Instances

Functor (Node rk) Source # 

Methods

fmap :: (a -> b) -> Node rk a -> Node rk b #

(<$) :: a -> Node rk b -> Node rk a #

Foldable (Node rk) Source # 

Methods

fold :: Monoid m => Node rk m -> m #

foldMap :: Monoid m => (a -> m) -> Node rk a -> m #

foldr :: (a -> b -> b) -> b -> Node rk a -> b #

foldr' :: (a -> b -> b) -> b -> Node rk a -> b #

foldl :: (b -> a -> b) -> b -> Node rk a -> b #

foldl' :: (b -> a -> b) -> b -> Node rk a -> b #

foldr1 :: (a -> a -> a) -> Node rk a -> a #

foldl1 :: (a -> a -> a) -> Node rk a -> a #

toList :: Node rk a -> [a] #

null :: Node rk a -> Bool #

length :: Node rk a -> Int #

elem :: Eq a => a -> Node rk a -> Bool #

maximum :: Ord a => Node rk a -> a #

minimum :: Ord a => Node rk a -> a #

sum :: Num a => Node rk a -> a #

product :: Num a => Node rk a -> a #

Traversable (Node rk) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Node rk a -> f (Node rk b) #

sequenceA :: Applicative f => Node rk (f a) -> f (Node rk a) #

mapM :: Monad m => (a -> m b) -> Node rk a -> m (Node rk b) #

sequence :: Monad m => Node rk (m a) -> m (Node rk a) #

NFData a => NFData (Node rk a) Source # 

Methods

rnf :: Node rk a -> () #

data Tree rk a Source #

A rose tree, where the children are indexed.

Constructors

Root a (Node rk a) 

Instances

Functor (Tree rk) Source # 

Methods

fmap :: (a -> b) -> Tree rk a -> Tree rk b #

(<$) :: a -> Tree rk b -> Tree rk a #

Foldable (Tree rk) Source # 

Methods

fold :: Monoid m => Tree rk m -> m #

foldMap :: Monoid m => (a -> m) -> Tree rk a -> m #

foldr :: (a -> b -> b) -> b -> Tree rk a -> b #

foldr' :: (a -> b -> b) -> b -> Tree rk a -> b #

foldl :: (b -> a -> b) -> b -> Tree rk a -> b #

foldl' :: (b -> a -> b) -> b -> Tree rk a -> b #

foldr1 :: (a -> a -> a) -> Tree rk a -> a #

foldl1 :: (a -> a -> a) -> Tree rk a -> a #

toList :: Tree rk a -> [a] #

null :: Tree rk a -> Bool #

length :: Tree rk a -> Int #

elem :: Eq a => a -> Tree rk a -> Bool #

maximum :: Ord a => Tree rk a -> a #

minimum :: Ord a => Tree rk a -> a #

sum :: Num a => Tree rk a -> a #

product :: Num a => Tree rk a -> a #

Traversable (Tree rk) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Tree rk a -> f (Tree rk b) #

sequenceA :: Applicative f => Tree rk (f a) -> f (Tree rk a) #

mapM :: Monad m => (a -> m b) -> Tree rk a -> m (Tree rk b) #

sequence :: Monad m => Tree rk (m a) -> m (Tree rk a) #

Generic1 (Tree n) Source # 

Associated Types

type Rep1 (Tree n :: * -> *) :: * -> * #

Methods

from1 :: Tree n a -> Rep1 (Tree n) a #

to1 :: Rep1 (Tree n) a -> Tree n a #

Generic (Tree n a) Source # 

Associated Types

type Rep (Tree n a) :: * -> * #

Methods

from :: Tree n a -> Rep (Tree n a) x #

to :: Rep (Tree n a) x -> Tree n a #

NFData a => NFData (Tree rk a) Source # 

Methods

rnf :: Tree rk a -> () #

type Rep1 (Tree n) Source # 
type Rep1 (Tree n) = D1 (MetaData "Tree" "Data.Queue.Binomial" "type-indexed-queues-0.1.0.1-GPaLldpmb1Q20PpM0x8M72" False) (C1 (MetaCons "Root" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (Node n)))))
type Rep (Tree n a) Source # 
type Rep (Tree n a) = D1 (MetaData "Tree" "Data.Queue.Binomial" "type-indexed-queues-0.1.0.1-GPaLldpmb1Q20PpM0x8M72" False) (C1 (MetaCons "Root" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node n a)))))