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

Data.Geometry.QuadTree.Cell

Description

 
Synopsis

Documentation

type WidthIndex = Int Source #

side lengths will be 2^i for some integer i

data Cell r Source #

A Cell corresponding to a node in the QuadTree

Constructors

Cell 

Instances

Instances details
Functor Cell Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

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

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

Foldable Cell Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Cell a -> m #

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

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

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

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

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

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

toList :: Cell a -> [a] #

null :: Cell a -> Bool #

length :: Cell a -> Int #

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

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

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

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

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

Traversable Cell Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

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

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

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

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

Eq r => Eq (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

(==) :: Cell r -> Cell r -> Bool #

(/=) :: Cell r -> Cell r -> Bool #

Show r => Show (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

showsPrec :: Int -> Cell r -> ShowS #

show :: Cell r -> String #

showList :: [Cell r] -> ShowS #

(Ord r, Fractional r) => HasIntersectionWith (Point 2 r) (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

intersects :: Point 2 r -> Cell r -> Bool #

(Ord r, Fractional r) => IsIntersectableWith (Point 2 r) (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

Methods

intersect :: Point 2 r -> Cell r -> Intersection (Point 2 r) (Cell r) #

nonEmptyIntersection :: proxy (Point 2 r) -> proxy (Cell r) -> Intersection (Point 2 r) (Cell r) -> Bool #

type NumType (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

type NumType (Cell r) = r
type Dimension (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

type Dimension (Cell r) = 2
type IntersectionOf (Point 2 r) (Cell r) Source # 
Instance details

Defined in Data.Geometry.QuadTree.Cell

type IntersectionOf (Point 2 r) (Cell r) = '[NoIntersection, Point 2 r]

lowerLeft :: forall r r. Lens (Cell r) (Cell r) (Point 2 r) (Point 2 r) Source #

fitsRectangle :: (RealFrac r, Ord r) => Rectangle p r -> Cell r Source #

Computes a cell that contains the given rectangle

toBox :: Fractional r => Cell r -> Box 2 () r Source #

inCell :: (Fractional r, Ord r) => (Point 2 r :+ p) -> Cell r -> Bool Source #

cellSides :: Fractional r => Cell r -> Sides (LineSegment 2 () r) Source #

Sides are open

partitionPoints :: (Fractional r, Ord r) => Cell r -> [Point 2 r :+ p] -> Quadrants [Point 2 r :+ p] Source #

Partitions the points into quadrants. See quadrantOf for the precise rules.

quadrantOf :: forall r. (Fractional r, Ord r) => Point 2 r -> Cell r -> InterCardinalDirection Source #

Computes the quadrant of the cell corresponding to the current point. Note that we decide the quadrant solely based on the midpoint. If the query point lies outside the cell, it is still assigned a quadrant.

  • The northEast quadrants includes its bottom and left side
  • The southEast quadrant includes its left side
  • The northWest quadrant includes its bottom side
  • The southWest quadrants does not include any of its sides.
>>> quadrantOf (Point2 9 9) (Cell 4 origin)
NorthEast
>>> quadrantOf (Point2 8 9) (Cell 4 origin)
NorthEast
>>> quadrantOf (Point2 8 8) (Cell 4 origin)
NorthEast
>>> quadrantOf (Point2 8 7) (Cell 4 origin)
SouthEast
>>> quadrantOf (Point2 4 7) (Cell 4 origin)
SouthWest
>>> quadrantOf (Point2 4 10) (Cell 4 origin)
NorthWest
>>> quadrantOf (Point2 4 40) (Cell 4 origin)
NorthEast
>>> quadrantOf (Point2 4 40) (Cell 4 origin)
NorthWest

relationTo :: (Fractional r, Ord r) => (p :+ Cell r) -> Cell r -> Sides (Maybe (p :+ Cell r)) Source #

Given two cells c and me, compute on which side of me the cell c is.

pre: c and me are non-overlapping