kdt-0.2.5: Fast and flexible k-d trees for various types of point queries.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.KdTree.Dynamic

Synopsis

Usage

The KdTree is a dynamic variant of Data.KdTree.Static.KdTree that allows for insertion of new points into an existing KdTree. This algorithm was implemented using a static-to-dynamic transformation.

Here's an example of interleaving 3D point insertions and point queries using KdTree:

>>> let dkdt = singleton point3dAsList (Point3D 0.0 0.0 0.0)

>>> let dkdt' = insert dkdt (Point3D 1.0 1.0 1.0)

>>> nearest dkdt' (Point3D 0.4 0.4 0.4)
Point3D {x = 0.0, y = 0.0, z = 0.0}

>>> let dkdt'' = insert dkdt' (Point3D 0.5 0.5 0.5)

>>> nearest dkdt'' (Point3D 0.4 0.4 0.4)
Point3D {x = 0.5, y = 0.5, z = 0.5}

Check out Data.KdMap.Dynamic.KdMap if you want to associate a value with each point in your tree structure.

Reference

Types

type PointAsListFn a p = p -> [a] Source #

Converts a point of type p with axis values of type a into a list of axis values [a].

type SquaredDistanceFn a p = p -> p -> a Source #

Returns the squared distance between two points of type p with axis values of type a.

data KdTree a p Source #

A dynamic k-d tree structure that stores points of type p with axis values of type a.

Instances

Instances details
Foldable (KdTree a) Source # 
Instance details

Defined in Data.KdTree.Dynamic

Methods

fold :: Monoid m => KdTree a m -> m #

foldMap :: Monoid m => (a0 -> m) -> KdTree a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> KdTree a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> KdTree a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> KdTree a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> KdTree a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> KdTree a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> KdTree a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> KdTree a a0 -> a0 #

toList :: KdTree a a0 -> [a0] #

null :: KdTree a a0 -> Bool #

length :: KdTree a a0 -> Int #

elem :: Eq a0 => a0 -> KdTree a a0 -> Bool #

maximum :: Ord a0 => KdTree a a0 -> a0 #

minimum :: Ord a0 => KdTree a a0 -> a0 #

sum :: Num a0 => KdTree a a0 -> a0 #

product :: Num a0 => KdTree a a0 -> a0 #

(Show a, Show p) => Show (KdTree a p) Source # 
Instance details

Defined in Data.KdTree.Dynamic

Methods

showsPrec :: Int -> KdTree a p -> ShowS #

show :: KdTree a p -> String #

showList :: [KdTree a p] -> ShowS #

Dynamic k-d tree construction

empty :: Real a => PointAsListFn a p -> KdTree a p Source #

Generates an empty KdTree with the default distance function.

singleton :: Real a => PointAsListFn a p -> p -> KdTree a p Source #

Generates a KdTree with a single point using the default distance function.

emptyWithDist :: Real a => PointAsListFn a p -> SquaredDistanceFn a p -> KdTree a p Source #

Generates an empty KdTree with a user-specified distance function.

singletonWithDist :: Real a => PointAsListFn a p -> SquaredDistanceFn a p -> p -> KdTree a p Source #

Generates a KdTree with a single point using a user-specified distance function.

Insertion

insert :: Real a => KdTree a p -> p -> KdTree a p Source #

Adds a given point to a KdTree.

Average time complexity per insert for n inserts: O(log^2(n)).

Query

nearest :: Real a => KdTree a p -> p -> p Source #

Given a KdTree and a query point, returns the nearest point in the KdTree to the query point.

Average time complexity: O(log^2(n)).

inRadius :: Real a => KdTree a p -> a -> p -> [p] Source #

Given a KdTree, a query point, and a radius, returns all points in the KdTree that are within the given radius of the query points.

Points are not returned in any particular order.

Worst case time complexity: O(n) for n data points.

kNearest :: Real a => KdTree a p -> Int -> p -> [p] Source #

Given a KdTree, a query point, and a number k, returns the k nearest points in the KdTree to the query point.

Neighbors are returned in order of increasing distance from query point.

Average time complexity: log(k) * log^2(n) for k nearest neighbors on a structure with n data points.

Worst case time complexity: n * log(k) for k nearest neighbors on a structure with n data points.

inRange Source #

Arguments

:: Real a 
=> KdTree a p 
-> p

lower bounds of range

-> p

upper bounds of range

-> [p]

all points within given range

Finds all points in a KdTree with points within a given range, where the range is specified as a set of lower and upper bounds.

Points are not returned in any particular order.

Worst case time complexity: O(n) for n data points and a range that spans all the points.

toList :: KdTree a p -> [p] Source #

Returns a list of all the points in the KdTree.

Time complexity: O(n)

null :: KdTree a p -> Bool Source #

Returns whether the KdTree is empty.

size :: KdTree a p -> Int Source #

Returns the number of elements in the KdTree.

Time complexity: O(1)

Utilities

defaultSqrDist :: Num a => PointAsListFn a p -> SquaredDistanceFn a p Source #

A default implementation of squared distance given two points and a PointAsListFn.