Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data QuadTree v p r = QuadTree {
- _startingCell :: !(Cell r)
- _tree :: !(Tree v p)
- tree :: forall v p r v p. Lens (QuadTree v p r) (QuadTree v p r) (Tree v p) (Tree v p)
- startingCell :: forall v p r r. Lens (QuadTree v p r) (QuadTree v p r) (Cell r) (Cell r)
- withCells :: (Fractional r, Ord r) => QuadTree v p r -> QuadTree (v :+ Cell r) (p :+ Cell r) r
- withCellsTree :: (Fractional r, Ord r) => QuadTree v p r -> Tree (v :+ Cell r) (p :+ Cell r)
- leaves :: QuadTree v p r -> NonEmpty p
- perLevel :: QuadTree v p r -> NonEmpty (NonEmpty (TreeNode v p))
- buildOn :: Cell r -> (Cell r -> i -> Tree v p) -> i -> QuadTree v p r
- build :: (Fractional r, Ord r) => (Cell r -> i -> Split i v p) -> Cell r -> i -> QuadTree v p r
- fromPointsBox :: (Fractional r, Ord r) => Cell r -> [Point 2 r :+ p] -> QuadTree () (Maybe (Point 2 r :+ p)) r
- fromPoints :: (RealFrac r, Ord r) => NonEmpty (Point 2 r :+ p) -> QuadTree () (Maybe (Point 2 r :+ p)) r
- findLeaf :: (Fractional r, Ord r) => Point 2 r -> QuadTree v p r -> Maybe (p :+ Cell r)
- fromZeros :: (Fractional r, Ord r, Num a, Eq a, v ~ Quadrants Sign) => Cell r -> (Point 2 r -> a) -> QuadTree v (Either v Sign) r
- fromZerosWith :: (Fractional r, Ord r, Eq a, Num a) => Limiter r (Corners Sign) (Corners Sign) Sign -> Cell r -> (Point 2 r -> a) -> QuadTree (Quadrants Sign) (Signs Sign) r
- type Signs sign = Either (Corners sign) sign
- fromZerosWith' :: (Eq sign, Fractional r, Ord r) => Limiter r (Corners sign) (Corners sign) sign -> Cell r -> (Point 2 r -> sign) -> QuadTree (Quadrants sign) (Signs sign) r
- data Sign
- fromOrdering :: Ordering -> Sign
- fromSignum :: (Num a, Eq a) => (b -> a) -> b -> Sign
- shouldSplitZeros :: forall r sign. (Fractional r, Eq sign) => (Point 2 r -> sign) -> Splitter r (Quadrants sign) (Quadrants sign) sign
- isZeroCell :: Eq sign => sign -> Either v sign -> Bool
- completeTree :: (Fractional r, Ord r) => Cell r -> QuadTree () () r
Documentation
QuadTree on the starting cell
QuadTree | |
|
Instances
Functor (QuadTree v p) Source # | |
Foldable (QuadTree v p) Source # | |
Defined in Data.Geometry.QuadTree fold :: Monoid m => QuadTree v p m -> m # foldMap :: Monoid m => (a -> m) -> QuadTree v p a -> m # foldr :: (a -> b -> b) -> b -> QuadTree v p a -> b # foldr' :: (a -> b -> b) -> b -> QuadTree v p a -> b # foldl :: (b -> a -> b) -> b -> QuadTree v p a -> b # foldl' :: (b -> a -> b) -> b -> QuadTree v p a -> b # foldr1 :: (a -> a -> a) -> QuadTree v p a -> a # foldl1 :: (a -> a -> a) -> QuadTree v p a -> a # toList :: QuadTree v p a -> [a] # null :: QuadTree v p a -> Bool # length :: QuadTree v p a -> Int # elem :: Eq a => a -> QuadTree v p a -> Bool # maximum :: Ord a => QuadTree v p a -> a # minimum :: Ord a => QuadTree v p a -> a # | |
Traversable (QuadTree v p) Source # | |
Defined in Data.Geometry.QuadTree | |
(Eq r, Eq p, Eq v) => Eq (QuadTree v p r) Source # | |
(Show r, Show p, Show v) => Show (QuadTree v p r) Source # | |
Generic (QuadTree v p r) Source # | |
type Rep (QuadTree v p r) Source # | |
Defined in Data.Geometry.QuadTree type Rep (QuadTree v p r) = D1 (MetaData "QuadTree" "Data.Geometry.QuadTree" "hgeometry-0.11.0.0-5Q7X7STHtn33ZJbJEL0QVy" False) (C1 (MetaCons "QuadTree" PrefixI True) (S1 (MetaSel (Just "_startingCell") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Cell r)) :*: S1 (MetaSel (Just "_tree") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Tree v p)))) |
Functions operating on the QuadTree (in terms of the Tree
type)
withCells :: (Fractional r, Ord r) => QuadTree v p r -> QuadTree (v :+ Cell r) (p :+ Cell r) r Source #
withCellsTree :: (Fractional r, Ord r) => QuadTree v p r -> Tree (v :+ Cell r) (p :+ Cell r) Source #
buildOn :: Cell r -> (Cell r -> i -> Tree v p) -> i -> QuadTree v p r Source #
Given a starting cell, a Tree builder, and some input required by the builder, constructs a quadTree.
build :: (Fractional r, Ord r) => (Cell r -> i -> Split i v p) -> Cell r -> i -> QuadTree v p r Source #
The Equivalent of Tree.build for constructing a QuadTree
fromPointsBox :: (Fractional r, Ord r) => Cell r -> [Point 2 r :+ p] -> QuadTree () (Maybe (Point 2 r :+ p)) r 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.
fromPoints :: (RealFrac r, Ord r) => NonEmpty (Point 2 r :+ p) -> QuadTree () (Maybe (Point 2 r :+ p)) r Source #
findLeaf :: (Fractional r, Ord r) => Point 2 r -> QuadTree v p r -> Maybe (p :+ Cell r) Source #
Locates the cell containing the given point, if it exists.
running time: \(O(h)\), where \(h\) is the height of the quadTree
fromZeros :: (Fractional r, Ord r, Num a, Eq a, v ~ Quadrants Sign) => Cell r -> (Point 2 r -> a) -> QuadTree v (Either v Sign) r Source #
fromZerosWith :: (Fractional r, Ord r, Eq a, Num a) => Limiter r (Corners Sign) (Corners Sign) Sign -> Cell r -> (Point 2 r -> a) -> QuadTree (Quadrants Sign) (Signs Sign) r Source #
fromZerosWith' :: (Eq sign, Fractional r, Ord r) => Limiter r (Corners sign) (Corners sign) sign -> Cell r -> (Point 2 r -> sign) -> QuadTree (Quadrants sign) (Signs sign) r Source #
fromOrdering :: Ordering -> Sign Source #
Interpret an ordering result as a Sign
:: (Fractional r, Eq sign) | |
=> (Point 2 r -> sign) | The function we are evaluating |
-> Splitter r (Quadrants sign) (Quadrants sign) sign |
Splitter that determines if we should split a cell based on the sign of the corners.
completeTree :: (Fractional r, Ord r) => Cell r -> QuadTree () () r Source #
Constructs an empty/complete tree from the starting width