Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Tree v p
- _Node :: forall v p v. Prism (Tree v p) (Tree v p) (v, Quadrants (Tree v p)) (v, Quadrants (Tree v p))
- _Leaf :: forall v p. Prism' (Tree v p) p
- foldTree :: (p -> b) -> (v -> Quadrants b -> b) -> Tree v p -> b
- leaves :: Tree v p -> NonEmpty p
- toRoseTree :: Tree v p -> Tree (TreeNode v p)
- height :: Tree v p -> Integer
- build :: Fractional r => Splitter r pts v p -> Cell r -> pts -> Tree v p
- withCells :: Fractional r => Cell r -> Tree v p -> Tree (v :+ Cell r) (p :+ Cell r)
- fromPoints :: (Fractional r, Ord r) => Cell r -> [Point 2 r :+ p] -> Tree () (Maybe (Point 2 r :+ p))
- fromPointsF :: (Fractional r, Ord r) => Splitter r [Point 2 r :+ p] () (Maybe (Point 2 r :+ p))
Documentation
Our cells use Rational numbers as their numeric type type CellR = Cell (RealNumber 10)
The Actual Tree type representing a quadTree
Instances
Bifunctor Tree Source # | |
Bitraversable Tree Source # | |
Defined in Data.Geometry.QuadTree.Tree bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tree a b -> f (Tree c d) # | |
Bifoldable Tree Source # | |
Bitraversable1 Tree Source # | |
Defined in Data.Geometry.QuadTree.Tree 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 # | |
Defined in Data.Geometry.QuadTree.Tree | |
(Eq p, Eq v) => Eq (Tree v p) Source # | |
(Show p, Show v) => Show (Tree v p) Source # | |
_Node :: forall v p v. Prism (Tree v p) (Tree v p) (v, Quadrants (Tree v p)) (v, Quadrants (Tree v p)) Source #
Functions operating on the QuadTree (in temrs of the Tree
type)
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