hgeometry-0.7.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.BinaryTree

Contents

Synopsis

Documentation

data BinLeafTree v a Source #

Constructors

Leaf !a 
Node (BinLeafTree v a) !v (BinLeafTree v a) 
Instances
Measured v a => Measured v (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

measure :: BinLeafTree v a -> v Source #

Functor (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fmap :: (a -> b) -> BinLeafTree v a -> BinLeafTree v b #

(<$) :: a -> BinLeafTree v b -> BinLeafTree v a #

Foldable (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fold :: Monoid m => BinLeafTree v m -> m #

foldMap :: Monoid m => (a -> m) -> BinLeafTree v a -> m #

foldr :: (a -> b -> b) -> b -> BinLeafTree v a -> b #

foldr' :: (a -> b -> b) -> b -> BinLeafTree v a -> b #

foldl :: (b -> a -> b) -> b -> BinLeafTree v a -> b #

foldl' :: (b -> a -> b) -> b -> BinLeafTree v a -> b #

foldr1 :: (a -> a -> a) -> BinLeafTree v a -> a #

foldl1 :: (a -> a -> a) -> BinLeafTree v a -> a #

toList :: BinLeafTree v a -> [a] #

null :: BinLeafTree v a -> Bool #

length :: BinLeafTree v a -> Int #

elem :: Eq a => a -> BinLeafTree v a -> Bool #

maximum :: Ord a => BinLeafTree v a -> a #

minimum :: Ord a => BinLeafTree v a -> a #

sum :: Num a => BinLeafTree v a -> a #

product :: Num a => BinLeafTree v a -> a #

Traversable (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

sequenceA :: Applicative f => BinLeafTree v (f a) -> f (BinLeafTree v a) #

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

sequence :: Monad m => BinLeafTree v (m a) -> m (BinLeafTree v a) #

Foldable1 (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fold1 :: Semigroup m => BinLeafTree v m -> m #

foldMap1 :: Semigroup m => (a -> m) -> BinLeafTree v a -> m #

toNonEmpty :: BinLeafTree v a -> NonEmpty a #

(Eq a, Eq v) => Eq (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

(==) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(/=) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(Ord a, Ord v) => Ord (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

compare :: BinLeafTree v a -> BinLeafTree v a -> Ordering #

(<) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(<=) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(>) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(>=) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

max :: BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a #

min :: BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a #

(Read a, Read v) => Read (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

(Show a, Show v) => Show (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

showsPrec :: Int -> BinLeafTree v a -> ShowS #

show :: BinLeafTree v a -> String #

showList :: [BinLeafTree v a] -> ShowS #

Generic (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Associated Types

type Rep (BinLeafTree v a) :: * -> * #

Methods

from :: BinLeafTree v a -> Rep (BinLeafTree v a) x #

to :: Rep (BinLeafTree v a) x -> BinLeafTree v a #

Measured v a => Semigroup (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

(<>) :: BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a #

sconcat :: NonEmpty (BinLeafTree v a) -> BinLeafTree v a #

stimes :: Integral b => b -> BinLeafTree v a -> BinLeafTree v a #

(Arbitrary a, Arbitrary v) => Arbitrary (BinLeafTree v a) # 
Instance details

Defined in Test.QuickCheck.HGeometryInstances

Methods

arbitrary :: Gen (BinLeafTree v a) #

shrink :: BinLeafTree v a -> [BinLeafTree v a] #

(NFData v, NFData a) => NFData (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

rnf :: BinLeafTree v a -> () #

type Rep (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

class Semigroup v => Measured v a | a -> v where Source #

Minimal complete definition

measure

Methods

measure :: a -> v Source #

Instances
Measured Size (Elem a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

measure :: Elem a -> Size Source #

Measured v a => Measured v (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

measure :: BinLeafTree v a -> v Source #

Semigroup v => Measured v (NodeData d r v) Source # 
Instance details

Defined in Algorithms.Geometry.WellSeparatedPairDecomposition.Types

Methods

measure :: NodeData d r v -> v Source #

Measured [I a] (I a) Source # 
Instance details

Defined in Data.Geometry.SegmentTree.Generic

Methods

measure :: I a -> [I a] Source #

node :: Measured v a => BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a Source #

smart constructor

asBalancedBinLeafTree :: NonEmpty a -> BinLeafTree Size (Elem a) Source #

Create a balanced tree, i.e. a tree of height \(O(\log n)\) with the elements in the leaves.

\(O(n)\) time.

foldUp :: (b -> v -> b -> b) -> (a -> b) -> BinLeafTree v a -> b Source #

Given a function to combine internal nodes into b's and leafs into b's, traverse the tree bottom up, and combine everything into one b.

foldUpData :: (w -> v -> w -> w) -> (a -> w) -> BinLeafTree v a -> BinLeafTree w a Source #

Traverses the tree bottom up, recomputing the assocated values.

zipExactWith :: (u -> v -> w) -> (a -> b -> c) -> BinLeafTree u a -> BinLeafTree v b -> BinLeafTree w c Source #

Takes two trees, that have the same structure, and uses the provided functions to "zip" them together

newtype Size Source #

Constructors

Size Int 
Instances
Enum Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

succ :: Size -> Size #

pred :: Size -> Size #

toEnum :: Int -> Size #

fromEnum :: Size -> Int #

enumFrom :: Size -> [Size] #

enumFromThen :: Size -> Size -> [Size] #

enumFromTo :: Size -> Size -> [Size] #

enumFromThenTo :: Size -> Size -> Size -> [Size] #

Eq Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Integral Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

quot :: Size -> Size -> Size #

rem :: Size -> Size -> Size #

div :: Size -> Size -> Size #

mod :: Size -> Size -> Size #

quotRem :: Size -> Size -> (Size, Size) #

divMod :: Size -> Size -> (Size, Size) #

toInteger :: Size -> Integer #

Num Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Read Size Source # 
Instance details

Defined in Data.BinaryTree

Real Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

toRational :: Size -> Rational #

Show Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 
Instance details

Defined in Data.BinaryTree

Associated Types

type Rep Size :: * -> * #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

Semigroup Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

(<>) :: Size -> Size -> Size #

sconcat :: NonEmpty Size -> Size #

stimes :: Integral b => b -> Size -> Size #

Monoid Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

mempty :: Size #

mappend :: Size -> Size -> Size #

mconcat :: [Size] -> Size #

NFData Size Source # 
Instance details

Defined in Data.BinaryTree

Methods

rnf :: Size -> () #

Measured Size (Elem a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

measure :: Elem a -> Size Source #

type Rep Size Source # 
Instance details

Defined in Data.BinaryTree

type Rep Size = D1 (MetaData "Size" "Data.BinaryTree" "hgeometry-0.7.0.0-3y7zA7ljCTE9s6EHvXHItM" True) (C1 (MetaCons "Size" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype Elem a Source #

Constructors

Elem 

Fields

Instances
Functor Elem Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

Foldable Elem Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

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

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

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

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

toList :: Elem a -> [a] #

null :: Elem a -> Bool #

length :: Elem a -> Int #

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

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

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

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

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

Traversable Elem Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

Measured Size (Elem a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

measure :: Elem a -> Size Source #

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

Defined in Data.BinaryTree

Methods

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

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

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

Defined in Data.BinaryTree

Methods

compare :: Elem a -> Elem a -> Ordering #

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

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

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

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

max :: Elem a -> Elem a -> Elem a #

min :: Elem a -> Elem a -> Elem a #

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

Defined in Data.BinaryTree

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

Defined in Data.BinaryTree

Methods

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

show :: Elem a -> String #

showList :: [Elem a] -> ShowS #

data Sized a Source #

Constructors

Sized !Size a 
Instances
Functor Sized Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

Foldable Sized Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

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

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

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

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

toList :: Sized a -> [a] #

null :: Sized a -> Bool #

length :: Sized a -> Int #

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

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

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

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

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

Traversable Sized Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

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

Defined in Data.BinaryTree

Methods

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

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

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

Defined in Data.BinaryTree

Methods

compare :: Sized a -> Sized a -> Ordering #

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

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

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

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

max :: Sized a -> Sized a -> Sized a #

min :: Sized a -> Sized a -> Sized a #

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

Defined in Data.BinaryTree

Methods

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

show :: Sized a -> String #

showList :: [Sized a] -> ShowS #

Generic (Sized a) Source # 
Instance details

Defined in Data.BinaryTree

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Sized a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

(<>) :: Sized a -> Sized a -> Sized a #

sconcat :: NonEmpty (Sized a) -> Sized a #

stimes :: Integral b => b -> Sized a -> Sized a #

Monoid a => Monoid (Sized a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

mempty :: Sized a #

mappend :: Sized a -> Sized a -> Sized a #

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

NFData a => NFData (Sized a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

rnf :: Sized a -> () #

type Rep (Sized a) Source # 
Instance details

Defined in Data.BinaryTree

type Rep (Sized a) = D1 (MetaData "Sized" "Data.BinaryTree" "hgeometry-0.7.0.0-3y7zA7ljCTE9s6EHvXHItM" False) (C1 (MetaCons "Sized" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Size) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Converting into a Data.Tree

data RoseElem v a Source #

Constructors

InternalNode v 
LeafNode a 
Instances
Functor (RoseElem v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fmap :: (a -> b) -> RoseElem v a -> RoseElem v b #

(<$) :: a -> RoseElem v b -> RoseElem v a #

(Eq v, Eq a) => Eq (RoseElem v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

(==) :: RoseElem v a -> RoseElem v a -> Bool #

(/=) :: RoseElem v a -> RoseElem v a -> Bool #

(Show v, Show a) => Show (RoseElem v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

showsPrec :: Int -> RoseElem v a -> ShowS #

show :: RoseElem v a -> String #

showList :: [RoseElem v a] -> ShowS #

Internal Node Tree

data BinaryTree a Source #

Constructors

Nil 
Internal (BinaryTree a) !a (BinaryTree a) 
Instances
Functor BinaryTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

Foldable BinaryTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

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

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

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

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

toList :: BinaryTree a -> [a] #

null :: BinaryTree a -> Bool #

length :: BinaryTree a -> Int #

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

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

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

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

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

Traversable BinaryTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

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

Defined in Data.BinaryTree

Methods

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

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

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

Defined in Data.BinaryTree

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

Defined in Data.BinaryTree

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

Defined in Data.BinaryTree

Generic (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

Associated Types

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

Methods

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

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

Arbitrary a => Arbitrary (BinaryTree a) # 
Instance details

Defined in Test.QuickCheck.HGeometryInstances

NFData a => NFData (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

rnf :: BinaryTree a -> () #

type Rep (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

access :: BinaryTree a -> Maybe a Source #

Get the element stored at the root, if it exists

asBalancedBinTree :: [a] -> BinaryTree a Source #

Create a balanced binary tree

\(O(n)\)

foldBinaryUp :: b -> (a -> b -> b -> b) -> BinaryTree a -> BinaryTree (a, b) Source #