hgeometry-0.12.0.3: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.QuadTree

Description

 
Synopsis

Documentation

data QuadTree v p r Source #

QuadTree on the starting cell

Constructors

QuadTree 

Fields

Instances

Instances details
Functor (QuadTree v p) Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

fmap :: (a -> b) -> QuadTree v p a -> QuadTree v p b #

(<$) :: a -> QuadTree v p b -> QuadTree v p a #

Foldable (QuadTree v p) Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

fold :: Monoid m => QuadTree v p m -> m #

foldMap :: Monoid m => (a -> m) -> QuadTree v p a -> m #

foldMap' :: Monoid m => (a -> m) -> QuadTree v p a -> m #

foldr :: (a -> b -> b) -> b -> QuadTree v p a -> b #

foldr' :: (a -> b -> b) -> b -> QuadTree v p a -> b #

foldl :: (b -> a -> b) -> b -> QuadTree v p a -> b #

foldl' :: (b -> a -> b) -> b -> QuadTree v p a -> b #

foldr1 :: (a -> a -> a) -> QuadTree v p a -> a #

foldl1 :: (a -> a -> a) -> QuadTree v p a -> a #

toList :: QuadTree v p a -> [a] #

null :: QuadTree v p a -> Bool #

length :: QuadTree v p a -> Int #

elem :: Eq a => a -> QuadTree v p a -> Bool #

maximum :: Ord a => QuadTree v p a -> a #

minimum :: Ord a => QuadTree v p a -> a #

sum :: Num a => QuadTree v p a -> a #

product :: Num a => QuadTree v p a -> a #

Traversable (QuadTree v p) Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

traverse :: Applicative f => (a -> f b) -> QuadTree v p a -> f (QuadTree v p b) #

sequenceA :: Applicative f => QuadTree v p (f a) -> f (QuadTree v p a) #

mapM :: Monad m => (a -> m b) -> QuadTree v p a -> m (QuadTree v p b) #

sequence :: Monad m => QuadTree v p (m a) -> m (QuadTree v p a) #

(Eq r, Eq p, Eq v) => Eq (QuadTree v p r) Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

(==) :: QuadTree v p r -> QuadTree v p r -> Bool #

(/=) :: QuadTree v p r -> QuadTree v p r -> Bool #

(Show r, Show p, Show v) => Show (QuadTree v p r) Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

showsPrec :: Int -> QuadTree v p r -> ShowS #

show :: QuadTree v p r -> String #

showList :: [QuadTree v p r] -> ShowS #

Generic (QuadTree v p r) Source # 
Instance details

Defined in Data.Geometry.QuadTree

Associated Types

type Rep (QuadTree v p r) :: Type -> Type #

Methods

from :: QuadTree v p r -> Rep (QuadTree v p r) x #

to :: Rep (QuadTree v p r) x -> QuadTree v p r #

type Rep (QuadTree v p r) Source # 
Instance details

Defined in Data.Geometry.QuadTree

type Rep (QuadTree v p r) = D1 ('MetaData "QuadTree" "Data.Geometry.QuadTree" "hgeometry-0.12.0.3-Gb2wLRTYrhf1nclpqptDXl" 'False) (C1 ('MetaCons "QuadTree" 'PrefixI 'True) (S1 ('MetaSel ('Just "_startingCell") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Cell r)) :*: S1 ('MetaSel ('Just "_tree") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Tree v p))))

tree :: forall v p r v p. Lens (QuadTree v p r) (QuadTree v p r) (Tree v p) (Tree v p) Source #

startingCell :: forall v p r r. Lens (QuadTree v p r) (QuadTree v p r) (Cell r) (Cell r) Source #

Functions operating on the QuadTree (in terms of the Tree type)

withCells :: (Fractional r, Ord r) => QuadTree v p r -> QuadTree (v :+ Cell r) (p :+ Cell r) r Source #

withCellsTree :: (Fractional r, Ord r) => QuadTree v p r -> Tree (v :+ Cell r) (p :+ Cell r) Source #

buildOn :: Cell r -> (Cell r -> i -> Tree v p) -> i -> QuadTree v p r Source #

Given a starting cell, a Tree builder, and some input required by the builder, constructs a quadTree.

build :: (Fractional r, Ord r) => (Cell r -> i -> Split i v p) -> Cell r -> i -> QuadTree v p r Source #

The Equivalent of Tree.build for constructing a QuadTree

fromPointsBox :: (Fractional r, Ord r) => Cell r -> [Point 2 r :+ p] -> QuadTree () (Maybe (Point 2 r :+ p)) r Source #

Build a QuadtTree from a set of points.

pre: the points lie inside the initial given cell.

running time: \(O(nh)\), where \(n\) is the number of points and \(h\) is the height of the resulting quadTree.

fromPoints :: (RealFrac r, Ord r) => NonEmpty (Point 2 r :+ p) -> QuadTree () (Maybe (Point 2 r :+ p)) r Source #

findLeaf :: (Fractional r, Ord r) => Point 2 r -> QuadTree v p r -> Maybe (p :+ Cell r) Source #

Locates the cell containing the given point, if it exists.

running time: \(O(h)\), where \(h\) is the height of the quadTree

fromZeros :: (Fractional r, Ord r, Num a, Eq a, v ~ Quadrants Sign) => Cell r -> (Point 2 r -> a) -> QuadTree v (Either v Sign) r Source #

type Signs sign = Either (Corners sign) sign Source #

fromZerosWith' :: (Eq sign, Fractional r, Ord r) => Limiter r (Corners sign) (Corners sign) sign -> Cell r -> (Point 2 r -> sign) -> QuadTree (Quadrants sign) (Signs sign) r Source #

data Sign Source #

Constructors

Negative 
Zero 
Positive 

Instances

Instances details
Eq Sign Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

Ord Sign Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

compare :: Sign -> Sign -> Ordering #

(<) :: Sign -> Sign -> Bool #

(<=) :: Sign -> Sign -> Bool #

(>) :: Sign -> Sign -> Bool #

(>=) :: Sign -> Sign -> Bool #

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 
Instance details

Defined in Data.Geometry.QuadTree

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

fromOrdering :: Ordering -> Sign Source #

Interpret an ordering result as a Sign

fromSignum :: (Num a, Eq a) => (b -> a) -> b -> Sign Source #

shouldSplitZeros Source #

Arguments

:: forall r sign. (Fractional r, Eq sign) 
=> (Point 2 r -> sign)

The function we are evaluating

-> Splitter r (Quadrants sign) (Quadrants sign) sign 

Splitter that determines if we should split a cell based on the sign of the corners.

isZeroCell Source #

Arguments

:: Eq sign 
=> sign

the zero value

-> Either v sign 
-> Bool 

completeTree :: (Fractional r, Ord r) => Cell r -> QuadTree () () r Source #

Constructs an empty/complete tree from the starting width