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

Safe HaskellNone
LanguageHaskell2010

Data.Queue.Leftist

Description

Leftist heaps.

Synopsis

Documentation

data Leftist a Source #

A simple, unchecked, weight-biased leftist heap. Based on implementation from here.

Constructors

Leaf 
Node !Int a (Leftist a) (Leftist a) 

Instances

Functor Leftist Source # 

Methods

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

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

Foldable Leftist Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Leftist a -> [a] #

null :: Leftist a -> Bool #

length :: Leftist a -> Int #

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

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

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

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

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

Traversable Leftist Source # 

Methods

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

sequenceA :: Applicative f => Leftist (f a) -> f (Leftist a) #

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

sequence :: Monad m => Leftist (m a) -> m (Leftist a) #

Generic1 Leftist Source # 

Associated Types

type Rep1 (Leftist :: * -> *) :: * -> * #

Methods

from1 :: Leftist a -> Rep1 Leftist a #

to1 :: Rep1 Leftist a -> Leftist a #

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 => 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 => Eq (Leftist a) Source # 

Methods

(==) :: Leftist a -> Leftist a -> Bool #

(/=) :: Leftist a -> Leftist a -> Bool #

Data a => Data (Leftist a) Source # 

Methods

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

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

toConstr :: Leftist a -> Constr #

dataTypeOf :: Leftist a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Leftist a) Source # 

Methods

compare :: Leftist a -> Leftist a -> Ordering #

(<) :: Leftist a -> Leftist a -> Bool #

(<=) :: Leftist a -> Leftist a -> Bool #

(>) :: Leftist a -> Leftist a -> Bool #

(>=) :: Leftist a -> Leftist a -> Bool #

max :: Leftist a -> Leftist a -> Leftist a #

min :: Leftist a -> Leftist a -> Leftist a #

(Read a, Ord a) => Read (Leftist a) Source # 
(Show a, Ord a) => Show (Leftist a) Source # 

Methods

showsPrec :: Int -> Leftist a -> ShowS #

show :: Leftist a -> String #

showList :: [Leftist a] -> ShowS #

Generic (Leftist a) Source # 

Associated Types

type Rep (Leftist a) :: * -> * #

Methods

from :: Leftist a -> Rep (Leftist a) x #

to :: Rep (Leftist a) x -> Leftist a #

Ord a => Monoid (Leftist a) Source # 

Methods

mempty :: Leftist a #

mappend :: Leftist a -> Leftist a -> Leftist a #

mconcat :: [Leftist a] -> Leftist a #

NFData a => NFData (Leftist a) Source # 

Methods

rnf :: Leftist a -> () #

type Rep1 Leftist Source # 
type Rep (Leftist a) Source # 

zygoLeftist :: b1 -> (Int -> a -> b1 -> b1 -> b1) -> b -> (Int -> a -> b1 -> b -> b1 -> b -> b) -> Leftist a -> b Source #

A zygomorphism over the heap. Useful for checking shape properties.