kdt-0.2.3: Fast and flexible k-d trees for various types of point queries.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.KdMap.Static

Contents

Synopsis

Usage

The KdMap is a variant of KdTree where each point in the tree is associated with some data. When talking about KdMaps, we'll refer to the points and their associated data as the points and values of the KdMap, respectively. It might help to think of KdTree and KdMap as being analogous to Set and Map.

Suppose you wanted to perform point queries on a set of 3D points, where each point is associated with a String. Here's how to build a KdMap of the data and perform a nearest neighbor query (if this doesn't make sense, start with the documentation for KdTree):

>>> let points = [(Point3d 0.0 0.0 0.0), (Point3d 1.0 1.0 1.0)]

>>> let valueStrings = ["First", "Second"]

>>> let pointValuePairs = zip points valueStrings

>>> let kdm = build point3dAsList pointValuePairs

>>> nearest kdm (Point3d 0.1 0.1 0.1)
[Point3d {x = 0.0, y = 0.0, z = 0.0}, "First"]

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 KdMap a p v Source

A k-d tree structure that stores points of type p with axis values of type a. Additionally, each point is associated with a value of type v.

Instances

Functor (KdMap a p) 
Foldable (KdMap a p) 
Traversable (KdMap a p) 
(Show a, Show p, Show v) => Show (KdMap a p v) 
Generic (KdMap a p v) 
(NFData a, NFData p, NFData v) => NFData (KdMap a p v) 
type Rep (KdMap a p v) 

k-d map construction

empty :: Real a => PointAsListFn a p -> KdMap a p v Source

Builds an empty KdMap.

emptyWithDist :: Real a => PointAsListFn a p -> SquaredDistanceFn a p -> KdMap a p v Source

Builds an empty KdMap using a user-specified squared distance function.

singleton :: Real a => PointAsListFn a p -> (p, v) -> KdMap a p v Source

Builds a KdMap with a single point-value pair.

singletonWithDist :: Real a => PointAsListFn a p -> SquaredDistanceFn a p -> (p, v) -> KdMap a p v Source

Builds a KdMap with a single point-value pair and a user-specified squared distance function.

build :: Real a => PointAsListFn a p -> [(p, v)] -> KdMap a p v Source

Builds a KdTree from a list of pairs of points (of type p) and values (of type v) using a default squared distance function defaultSqrDist.

Average complexity: O(n * log(n)) for n data points.

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

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

buildWithDist :: Real a => PointAsListFn a p -> SquaredDistanceFn a p -> [(p, v)] -> KdMap a p v Source

Builds a KdMap from a list of pairs of points (of type p) and values (of type v), using a user-specified squared distance function.

Average time complexity: O(n * log(n)) for n data points.

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

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

insertUnbalanced :: Real a => KdMap a p v -> p -> v -> KdMap a p v Source

Inserts a point-value pair into a KdMap. This can potentially cause the internal tree structure to become unbalanced. If the tree becomes too unbalanced, point queries will be very inefficient. If you need to perform lots of point insertions on an already existing k-d map, check out Data.KdMap.Dynamic.KdMap.

Average complexity: O(log(n)) for n data points.

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

batchInsertUnbalanced :: Real a => KdMap a p v -> [(p, v)] -> KdMap a p v Source

Inserts a list of point-value pairs into a KdMap. This can potentially cause the internal tree structure to become unbalanced, which leads to inefficient point queries.

Average complexity: O(n * log(n)) for n data points.

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

Query

nearest :: Real a => KdMap a p v -> p -> (p, v) Source

Given a KdMap and a query point, returns the point-value pair in the KdMap with the point nearest to the query.

Average time complexity: O(log(n)) for n data points.

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

Throws error if called on an empty KdMap.

inRadius Source

Arguments

:: Real a 
=> KdMap a p v 
-> a

radius

-> p

query point

-> [(p, v)]

list of point-value pairs with points within given radius of query

Given a KdMap, a query point, and a radius, returns all point-value pairs in the KdMap with points within the given radius of the query point.

Points are not returned in any particular order.

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

kNearest :: Real a => KdMap a p v -> Int -> p -> [(p, v)] Source

Given a KdMap, a query point, and a number k, returns the k point-value pairs with the nearest points to the query.

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

Average time complexity: log(k) * log(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 
=> KdMap a p v 
-> p

lower bounds of range

-> p

upper bounds of range

-> [(p, v)]

point-value pairs within given range

Finds all point-value pairs in a KdMap 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.

TODO: Maybe use known bounds on entire tree structure to be able to automatically count whole portions of tree as being within given range.

assocs :: KdMap a p v -> [(p, v)] Source

Returns a list of all the point-value pairs in the KdMap.

Time complexity: O(n) for n data points.

keys :: KdMap a p v -> [p] Source

Returns all points in the KdMap.

Time complexity: O(n) for n data points.

elems :: KdMap a p v -> [v] Source

Returns all values in the KdMap.

Time complexity: O(n) for n data points.

null :: KdMap a p v -> Bool Source

Returns True if the given KdMap is empty.

size :: KdMap a p v -> Int Source

Returns the number of point-value pairs in the KdMap.

Time complexity: O(1)

Folds

foldrWithKey :: ((p, v) -> b -> b) -> b -> KdMap a p v -> b Source

Performs a foldr over each point-value pair in the KdMap.

Utilities

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

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

Internal (for testing)

isValid :: Real a => KdMap a p v -> Bool Source

Returns True if tree structure adheres to k-d tree properties. For internal testing use.