Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Algorithm to construct a well separated pair decomposition (wspd).
Synopsis
- fairSplitTree :: (Fractional r, Ord r, Arity d, 1 <= d, Show r, Show p) => NonEmpty (Point d r :+ p) -> SplitTree d p r ()
- wellSeparatedPairs :: (Floating r, Ord r, Arity d, Arity (d + 1)) => r -> SplitTree d p r a -> [WSP d p r a]
- data NodeData d r a = NodeData !Int !(Box d () r) !a
- type WSP d p r a = (PointSet d p r a, PointSet d p r a)
- type SplitTree d p r a = BinLeafTree (NodeData d r a) (Point d r :+ p)
- nodeData :: forall d r a a. Lens (NodeData d r a) (NodeData d r a) a a
- data Level = Level {
- _unLevel :: Int
- _widestDim :: Maybe Int
- reIndexPoints :: (Arity d, 1 <= d) => Vector d (PointSeq d (Idx :+ p) r) -> Vector d (PointSeq d (Idx :+ p) r)
- distributePoints :: (Arity d, Show r, Show p) => Int -> Vector (Maybe Level) -> Vector d (PointSeq d (Idx :+ p) r) -> Vector (Vector d (PointSeq d (Idx :+ p) r))
- distributePoints' :: Int -> Vector (Maybe Level) -> PointSeq d (Idx :+ p) r -> Vector (PointSeq d (Idx :+ p) r)
Documentation
fairSplitTree :: (Fractional r, Ord r, Arity d, 1 <= d, Show r, Show p) => NonEmpty (Point d r :+ p) -> SplitTree d p r () Source #
Construct a split tree
running time: \(O(n \log n)\)
wellSeparatedPairs :: (Floating r, Ord r, Arity d, Arity (d + 1)) => r -> SplitTree d p r a -> [WSP d p r a] Source #
Given a split tree, generate the Well separated pairs
running time: \(O(s^d n)\)
Data that we store in the split tree
Instances
Semigroup v => Measured v (NodeData d r v) Source # | |
Defined in Algorithms.Geometry.WSPD.Types | |
Functor (NodeData d r) Source # | |
Foldable (NodeData d r) Source # | |
Defined in Algorithms.Geometry.WSPD.Types fold :: Monoid m => NodeData d r m -> m # foldMap :: Monoid m => (a -> m) -> NodeData d r a -> m # foldMap' :: Monoid m => (a -> m) -> NodeData d r a -> m # foldr :: (a -> b -> b) -> b -> NodeData d r a -> b # foldr' :: (a -> b -> b) -> b -> NodeData d r a -> b # foldl :: (b -> a -> b) -> b -> NodeData d r a -> b # foldl' :: (b -> a -> b) -> b -> NodeData d r a -> b # foldr1 :: (a -> a -> a) -> NodeData d r a -> a # foldl1 :: (a -> a -> a) -> NodeData d r a -> a # toList :: NodeData d r a -> [a] # null :: NodeData d r a -> Bool # length :: NodeData d r a -> Int # elem :: Eq a => a -> NodeData d r a -> Bool # maximum :: Ord a => NodeData d r a -> a # minimum :: Ord a => NodeData d r a -> a # | |
Traversable (NodeData d r) Source # | |
Defined in Algorithms.Geometry.WSPD.Types | |
(Arity d, Eq r, Eq a) => Eq (NodeData d r a) Source # | |
(Arity d, Show r, Show a) => Show (NodeData d r a) Source # | |
reIndexPoints :: (Arity d, 1 <= d) => Vector d (PointSeq d (Idx :+ p) r) -> Vector d (PointSeq d (Idx :+ p) r) Source #
Given a sequence of points, whose index is increasing in the first dimension, i.e. if idx p < idx q, then p[0] < q[0]. Reindex the points so that they again have an index in the range [0,..,n'], where n' is the new number of points.
running time: O(n' * d) (more or less; we are actually using an intmap for the lookups)
alternatively: I can unsafe freeze and thaw an existing vector to pass it
along to use as mapping. Except then I would have to force the evaluation
order, i.e. we cannot be in reIndexPoints
for two of the nodes at the same
time.
so, basically, run reIndex points in ST as well.