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

Data.KdMap.Dynamic

Synopsis

Usage

The KdMap is a variant of Data.KdTree.Dynamic.KdTree where each point in the tree is associated with some data. It is the dynamic variant of Data.KdMap.Static.KdMap.

Here's an example of interleaving point-value insertions and point queries using KdMap, where points are 3D points and values are Strings:

>>> let dkdm = singleton point3dAsList ((Point3D 0.0 0.0 0.0), "First")

>>> let dkdm' = insert dkdm ((Point3D 1.0 1.0 1.0), "Second")

>>> nearest dkdm' (Point3D 0.4 0.4 0.4)
(Point3D {x = 0.0, y = 0.0, z = 0.0}, "First")

>>> let dkdm'' = insert dkdm' ((Point3D 0.5 0.5 0.5), "Third")

>>> nearest dkdm'' (Point3D 0.4 0.4 0.4)
(Point3D {x = 0.5, y = 0.5, z = 0.5}, "Third")

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 dynamic 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

Instances details
Functor (KdMap a p) Source # 
Instance details

Defined in Data.KdMap.Dynamic

Methods

fmap :: (a0 -> b) -> KdMap a p a0 -> KdMap a p b #

(<$) :: a0 -> KdMap a p b -> KdMap a p a0 #

Foldable (KdMap a p) Source # 
Instance details

Defined in Data.KdMap.Dynamic

Methods

fold :: Monoid m => KdMap a p m -> m #

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

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

foldr :: (a0 -> b -> b) -> b -> KdMap a p a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> KdMap a p a0 -> b #

foldl :: (b -> a0 -> b) -> b -> KdMap a p a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> KdMap a p a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> KdMap a p a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> KdMap a p a0 -> a0 #

toList :: KdMap a p a0 -> [a0] #

null :: KdMap a p a0 -> Bool #

length :: KdMap a p a0 -> Int #

elem :: Eq a0 => a0 -> KdMap a p a0 -> Bool #

maximum :: Ord a0 => KdMap a p a0 -> a0 #

minimum :: Ord a0 => KdMap a p a0 -> a0 #

sum :: Num a0 => KdMap a p a0 -> a0 #

product :: Num a0 => KdMap a p a0 -> a0 #

Traversable (KdMap a p) Source # 
Instance details

Defined in Data.KdMap.Dynamic

Methods

traverse :: Applicative f => (a0 -> f b) -> KdMap a p a0 -> f (KdMap a p b) #

sequenceA :: Applicative f => KdMap a p (f a0) -> f (KdMap a p a0) #

mapM :: Monad m => (a0 -> m b) -> KdMap a p a0 -> m (KdMap a p b) #

sequence :: Monad m => KdMap a p (m a0) -> m (KdMap a p a0) #

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

Defined in Data.KdMap.Dynamic

Methods

showsPrec :: Int -> KdMap a p v -> ShowS #

show :: KdMap a p v -> String #

showList :: [KdMap a p v] -> ShowS #

Generic (KdMap a p v) Source # 
Instance details

Defined in Data.KdMap.Dynamic

Associated Types

type Rep (KdMap a p v) :: Type -> Type #

Methods

from :: KdMap a p v -> Rep (KdMap a p v) x #

to :: Rep (KdMap a p v) x -> KdMap a p v #

(NFData a, NFData p, NFData v) => NFData (KdMap a p v) Source # 
Instance details

Defined in Data.KdMap.Dynamic

Methods

rnf :: KdMap a p v -> () #

type Rep (KdMap a p v) Source # 
Instance details

Defined in Data.KdMap.Dynamic

type Rep (KdMap a p v) = D1 ('MetaData "KdMap" "Data.KdMap.Dynamic" "kdt-0.2.5-inplace" 'False) (C1 ('MetaCons "KdMap" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_trees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [KdMap a p v]) :*: S1 ('MetaSel ('Just "_pointAsList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PointAsListFn a p))) :*: (S1 ('MetaSel ('Just "_distSqr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SquaredDistanceFn a p)) :*: S1 ('MetaSel ('Just "_numNodes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

Dynamic k-d map construction

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

Generates an empty KdMap with the default distance function.

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

Generates a KdMap with a single point-value pair using the default distance function.

emptyWithDist :: PointAsListFn a p -> SquaredDistanceFn a p -> KdMap a p v Source #

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

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

Generates a KdMap with a single point-value pair using a user-specified distance function.

Insertion

insert :: Real a => KdMap a p v -> p -> v -> KdMap a p v Source #

Adds a given point-value pair to a KdMap.

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

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

Same as insert, but takes point and value as a pair.

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

Inserts a list of point-value pairs into the KdMap.

TODO: This will be made far more efficient than simply repeatedly inserting.

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^2(n)).

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

Given a KdMap, a query point, and a radius, returns all point-value pairs in the KdTree 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.

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^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 
=> 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.

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 whether the KdMap is empty.

size :: KdMap a p v -> Int Source #

Returns the number of elements 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)

subtreeSizes :: KdMap a p v -> [Int] Source #

Returns size of each internal k-d tree that makes up the dynamic structure. For internal testing use.