hgeometry-0.13: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.QuadTree.Tree

Description

 
Synopsis

Documentation

data Tree v p Source #

Our cells use Rational numbers as their numeric type type CellR = Cell (RealNumber 10)

The Actual Tree type representing a quadTree

Constructors

Leaf !p 
Node !v (Quadrants (Tree v p)) 

Instances

Instances details
Bifunctor Tree Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

bimap :: (a -> b) -> (c -> d) -> Tree a c -> Tree b d #

first :: (a -> b) -> Tree a c -> Tree b c #

second :: (b -> c) -> Tree a b -> Tree a c #

Bitraversable Tree Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tree a b -> f (Tree c d) #

Bifoldable Tree Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

bifold :: Monoid m => Tree m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Tree a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Tree a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Tree a b -> c #

Bitraversable1 Tree Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Tree a c -> f (Tree b d) #

bisequence1 :: Apply f => Tree (f a) (f b) -> f (Tree a b) #

Bifoldable1 Tree Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

bifold1 :: Semigroup m => Tree m m -> m #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Tree a b -> m #

(Eq p, Eq v) => Eq (Tree v p) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

(==) :: Tree v p -> Tree v p -> Bool #

(/=) :: Tree v p -> Tree v p -> Bool #

(Show p, Show v) => Show (Tree v p) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Tree

Methods

showsPrec :: Int -> Tree v p -> ShowS #

show :: Tree v p -> String #

showList :: [Tree v p] -> ShowS #

_Node :: forall v p v. Prism (Tree v p) (Tree v p) (v, Quadrants (Tree v p)) (v, Quadrants (Tree v p)) Source #

_Leaf :: forall v p. Prism' (Tree v p) p Source #

foldTree :: (p -> b) -> (v -> Quadrants b -> b) -> Tree v p -> b Source #

Fold on the Tree type.

leaves :: Tree v p -> NonEmpty p Source #

Produce a list of all leaves of a quad tree

toRoseTree :: Tree v p -> Tree (TreeNode v p) Source #

Converts into a RoseTree

height :: Tree v p -> Integer Source #

Computes the height of the quadtree

Functions operating on the QuadTree (in temrs of the Tree type)

build :: Fractional r => Splitter r pts v p -> Cell r -> pts -> Tree v p Source #

Builds a QuadTree

withCells :: Fractional r => Cell r -> Tree v p -> Tree (v :+ Cell r) (p :+ Cell r) Source #

Annotate the tree with its corresponing cells

fromPoints :: (Fractional r, Ord r) => Cell r -> [Point 2 r :+ p] -> Tree () (Maybe (Point 2 r :+ p)) Source #

Build a QuadtTree from a set of points.

pre: the points lie inside the initial given cell.

running time: \(O(nh)\), where \(n\) is the number of points and \(h\) is the height of the resulting quadTree.

fromPointsF :: (Fractional r, Ord r) => Splitter r [Point 2 r :+ p] () (Maybe (Point 2 r :+ p)) Source #

The function that can be used to build a quadTree fromPoints