Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data NodeData v r = NodeData {}
- newtype RangeTree v q r = RangeTree {
- _unRangeTree :: BinLeafTree (NodeData v r) (NodeData (v, q) r)
- createTree :: (Ord r, Measured v p, Semigroup p) => NonEmpty (r :+ p) -> RangeTree v p r
- createTree' :: (Ord r, Measured v p) => NonEmpty (r :+ p) -> RangeTree v p r
- toAscList :: RangeTree v p r -> NonEmpty (r :+ p)
- search :: (Ord r, Monoid v) => Range r -> RangeTree v p r -> v
- search' :: Ord r => Range r -> RangeTree v p r -> [v]
- search'' :: Ord r => Range r -> BinLeafTree (NodeData v r) (NodeData (v, q) r) -> [v]
- rangeOf :: BinLeafTree (NodeData v r) (NodeData v' r) -> Range r
- rangeOf' :: NodeData v r -> Range r
- createReportingTree :: Ord r => NonEmpty (r :+ [p]) -> RangeTree (Report p) (Report p) r
- report :: Ord r => Range r -> RangeTree (Report p) q r -> [p]
- newtype CountOf p = CountOf [p]
- createCountingTree :: Ord r => NonEmpty (r :+ [p]) -> RangeTree (Count p) (CountOf p) r
- count :: Ord r => Range r -> RangeTree (Count p) q r -> Int
Documentation
newtype RangeTree v q r Source #
A generic (1D) range tree. The r
parameter indicates the type
of the coordinates of the points. The q
represents any associated
data values with those points (stored in the leaves), and the v
types represents the data stored at internal nodes.
RangeTree | |
|
createTree :: (Ord r, Measured v p, Semigroup p) => NonEmpty (r :+ p) -> RangeTree v p r Source #
Creates a range tree
createTree' :: (Ord r, Measured v p) => NonEmpty (r :+ p) -> RangeTree v p r Source #
pre: input is sorted and grouped by x-coord
Converting to a List
toAscList :: RangeTree v p r -> NonEmpty (r :+ p) Source #
Lists all points in increasing order
running time: \(O(n)\)
Querying x
search :: (Ord r, Monoid v) => Range r -> RangeTree v p r -> v Source #
Range search
running time: \(O(\log n)\)
search' :: Ord r => Range r -> RangeTree v p r -> [v] Source #
Range search, report the (associated data structures of the) \(O(\log n)\) nodes that form the disjoint union of the range we are querying with.
running time: \(O(\log n)\)
search'' :: Ord r => Range r -> BinLeafTree (NodeData v r) (NodeData (v, q) r) -> [v] Source #
The actual search
rangeOf :: BinLeafTree (NodeData v r) (NodeData v' r) -> Range r Source #
Helper function to get the range of a binary leaf tree
Updates
CountOf [p] |
Instances
Functor CountOf Source # | |
Foldable CountOf Source # | |
Defined in Data.Geometry.RangeTree.Generic fold :: Monoid m => CountOf m -> m # foldMap :: Monoid m => (a -> m) -> CountOf a -> m # foldMap' :: Monoid m => (a -> m) -> CountOf a -> m # foldr :: (a -> b -> b) -> b -> CountOf a -> b # foldr' :: (a -> b -> b) -> b -> CountOf a -> b # foldl :: (b -> a -> b) -> b -> CountOf a -> b # foldl' :: (b -> a -> b) -> b -> CountOf a -> b # foldr1 :: (a -> a -> a) -> CountOf a -> a # foldl1 :: (a -> a -> a) -> CountOf a -> a # elem :: Eq a => a -> CountOf a -> Bool # maximum :: Ord a => CountOf a -> a # minimum :: Ord a => CountOf a -> a # | |
Eq p => Eq (CountOf p) Source # | |
Ord p => Ord (CountOf p) Source # | |
Defined in Data.Geometry.RangeTree.Generic | |
Show p => Show (CountOf p) Source # | |
Semigroup (CountOf p) Source # | |
Monoid (CountOf p) Source # | |
Measured (Count p) (CountOf p) Source # | |
Defined in Data.Geometry.RangeTree.Generic |