Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type PointAsListFn a p = p -> [a]
- type SquaredDistanceFn a p = p -> p -> a
- data KdMap a p v
- empty :: Real a => PointAsListFn a p -> KdMap a p v
- singleton :: Real a => PointAsListFn a p -> (p, v) -> KdMap a p v
- emptyWithDist :: PointAsListFn a p -> SquaredDistanceFn a p -> KdMap a p v
- singletonWithDist :: Real a => PointAsListFn a p -> SquaredDistanceFn a p -> (p, v) -> KdMap a p v
- insert :: Real a => KdMap a p v -> p -> v -> KdMap a p v
- insertPair :: Real a => KdMap a p v -> (p, v) -> KdMap a p v
- batchInsert :: Real a => KdMap a p v -> [(p, v)] -> KdMap a p v
- nearest :: Real a => KdMap a p v -> p -> (p, v)
- inRadius :: Real a => KdMap a p v -> a -> p -> [(p, v)]
- kNearest :: Real a => KdMap a p v -> Int -> p -> [(p, v)]
- inRange :: Real a => KdMap a p v -> p -> p -> [(p, v)]
- assocs :: KdMap a p v -> [(p, v)]
- keys :: KdMap a p v -> [p]
- elems :: KdMap a p v -> [v]
- null :: KdMap a p v -> Bool
- size :: KdMap a p v -> Int
- foldrWithKey :: ((p, v) -> b -> b) -> b -> KdMap a p v -> b
- defaultSqrDist :: Num a => PointAsListFn a p -> SquaredDistanceFn a p
- subtreeSizes :: KdMap a p v -> [Int]
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
String
s:
>>> 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
.
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
Foldable (KdMap a p) Source # | |
Defined in Data.KdMap.Dynamic 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 # | |
Traversable (KdMap a p) Source # | |
Defined in Data.KdMap.Dynamic | |
Functor (KdMap a p) Source # | |
Generic (KdMap a p v) Source # | |
(Show a, Show p, Show v) => Show (KdMap a p v) Source # | |
(NFData a, NFData p, NFData v) => NFData (KdMap a p v) Source # | |
Defined in Data.KdMap.Dynamic | |
type Rep (KdMap a p v) Source # | |
Defined in Data.KdMap.Dynamic type Rep (KdMap a p v) = D1 ('MetaData "KdMap" "Data.KdMap.Dynamic" "kdt-0.2.6-DTEnDnjaiNZ6y7vmavOcpy" '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
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.
:: 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.
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.