Octree-0.6.0.0: Simple unbalanced Octree for storing data about 3D points

Safe HaskellSafe
LanguageHaskell98

Data.Octree

Synopsis

Documentation

data Octree a Source #

Datatype for nodes within Octree.

Instances

Functor Octree Source # 

Methods

fmap :: (a -> b) -> Octree a -> Octree b #

(<$) :: a -> Octree b -> Octree a #

Foldable Octree Source # 

Methods

fold :: Monoid m => Octree m -> m #

foldMap :: Monoid m => (a -> m) -> Octree a -> m #

foldr :: (a -> b -> b) -> b -> Octree a -> b #

foldr' :: (a -> b -> b) -> b -> Octree a -> b #

foldl :: (b -> a -> b) -> b -> Octree a -> b #

foldl' :: (b -> a -> b) -> b -> Octree a -> b #

foldr1 :: (a -> a -> a) -> Octree a -> a #

foldl1 :: (a -> a -> a) -> Octree a -> a #

toList :: Octree a -> [a] #

null :: Octree a -> Bool #

length :: Octree a -> Int #

elem :: Eq a => a -> Octree a -> Bool #

maximum :: Ord a => Octree a -> a #

minimum :: Ord a => Octree a -> a #

sum :: Num a => Octree a -> a #

product :: Num a => Octree a -> a #

Traversable Octree Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Octree a -> f (Octree b) #

sequenceA :: Applicative f => Octree (f a) -> f (Octree a) #

mapM :: Monad m => (a -> m b) -> Octree a -> m (Octree b) #

sequence :: Monad m => Octree (m a) -> m (Octree a) #

Show a => Show (Octree a) Source # 

Methods

showsPrec :: Int -> Octree a -> ShowS #

show :: Octree a -> String #

showList :: [Octree a] -> ShowS #

Generic (Octree a) Source # 

Associated Types

type Rep (Octree a) :: * -> * #

Methods

from :: Octree a -> Rep (Octree a) x #

to :: Rep (Octree a) x -> Octree a #

NFData a => NFData (Octree a) Source # 

Methods

rnf :: Octree a -> () #

type Rep (Octree a) Source # 

dist :: V3 Double -> V3 Double -> Double Source #

distance between two vectors

fromList :: [(V3 Double, a)] -> Octree a Source #

Creates an Octree from a list of (index, payload) tuples.

toList :: Octree t -> [(V3 Double, t)] Source #

Creates an Octree from list, trying to keep split points near centers | of mass for each subtree.

lookup :: Octree a -> V3 Double -> Maybe (V3 Double, a) Source #

Finds a given point, if it is in the tree.

insert :: (V3 Double, a) -> Octree a -> Octree a Source #

Inserts a point into an Octree. | NOTE: insert accepts duplicate points, but lookup would not find them - use withinRange in such case.

delete :: Eq a => (V3 Double, a) -> Octree a -> Octree a Source #

Deletes a point from an Octree. | NOTE: If there are duplicate points, it only deletes one of them.

deleteBy :: ((V3 Double, a) -> (V3 Double, a) -> Bool) -> (V3 Double, a) -> Octree a -> Octree a Source #

Deletes a point from an Octree with the provided equality check. | NOTE: If there are duplicate points, it only deletes one of them.

nearest :: Octree a -> V3 Double -> Maybe (V3 Double, a) Source #

Finds nearest neighbour for a given point.

withinRange :: Octree a -> Double -> V3 Double -> [(V3 Double, a)] Source #

Returns all points within Octree that are within a given distance from argument.