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

Algorithms.Geometry.WSPD

Description

Algorithm to construct a well separated pair decomposition (wspd).

Synopsis

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 NodeData d r a Source #

Data that we store in the split tree

Constructors

NodeData !Int !(Box d () r) !a 

Instances

Instances details
Semigroup v => Measured v (NodeData d r v) Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

measure :: NodeData d r v -> v #

Functor (NodeData d r) Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

fmap :: (a -> b) -> NodeData d r a -> NodeData d r b #

(<$) :: a -> NodeData d r b -> NodeData d r a #

Foldable (NodeData d r) Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

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 #

sum :: Num a => NodeData d r a -> a #

product :: Num a => NodeData d r a -> a #

Traversable (NodeData d r) Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

traverse :: Applicative f => (a -> f b) -> NodeData d r a -> f (NodeData d r b) #

sequenceA :: Applicative f => NodeData d r (f a) -> f (NodeData d r a) #

mapM :: Monad m => (a -> m b) -> NodeData d r a -> m (NodeData d r b) #

sequence :: Monad m => NodeData d r (m a) -> m (NodeData d r a) #

(Arity d, Eq r, Eq a) => Eq (NodeData d r a) Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

(==) :: NodeData d r a -> NodeData d r a -> Bool #

(/=) :: NodeData d r a -> NodeData d r a -> Bool #

(Arity d, Show r, Show a) => Show (NodeData d r a) Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

showsPrec :: Int -> NodeData d r a -> ShowS #

show :: NodeData d r a -> String #

showList :: [NodeData d r a] -> ShowS #

type WSP d p r a = (PointSet d p r a, PointSet d p r a) Source #

type SplitTree d p r a = BinLeafTree (NodeData d r a) (Point d r :+ p) Source #

nodeData :: forall d r a a. Lens (NodeData d r a) (NodeData d r a) a a Source #

data Level Source #

Constructors

Level 

Instances

Instances details
Eq Level Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Ord Level Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

(>=) :: Level -> Level -> Bool #

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Show Level Source # 
Instance details

Defined in Algorithms.Geometry.WSPD.Types

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

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.

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)) Source #

Assign the points to their the correct class. The Nothing class is considered the last class

distributePoints' Source #

Arguments

:: Int

number of classes

-> Vector (Maybe Level)

level assignment

-> PointSeq d (Idx :+ p) r

input points

-> Vector (PointSeq d (Idx :+ p) r) 

Assign the points to their the correct class. The Nothing class is considered the last class