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

Data.Geometry.Point

Description

\(d\)-dimensional points.

Synopsis

Documentation

newtype Point d r Source #

A d-dimensional point.

There are convenience pattern synonyms for 1, 2 and 3 dimensional points.

>>> let f (Point1 x) = x in f (Point1 1)
1
>>> let f (Point2 x y) = x in f (Point2 1 2)
1
>>> let f (Point3 x y z) = z in f (Point3 1 2 3)
3
>>> let f (Point3 x y z) = z in f (Point $ Vector3 1 2 3)
3

Constructors

Point 

Fields

Bundled Patterns

pattern Point1 :: r -> Point 1 r

A bidirectional pattern synonym for 1 dimensional points.

pattern Point2 :: r -> r -> Point 2 r

A bidirectional pattern synonym for 2 dimensional points.

pattern Point3 :: r -> r -> r -> Point 3 r

A bidirectional pattern synonym for 3 dimensional points.

Instances

Instances details
Arity d => Functor (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

fmap :: (a -> b) -> Point d a -> Point d b #

(<$) :: a -> Point d b -> Point d a #

Arity d => Applicative (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

pure :: a -> Point d a #

(<*>) :: Point d (a -> b) -> Point d a -> Point d b #

liftA2 :: (a -> b -> c) -> Point d a -> Point d b -> Point d c #

(*>) :: Point d a -> Point d b -> Point d b #

(<*) :: Point d a -> Point d b -> Point d a #

Arity d => Foldable (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

fold :: Monoid m => Point d m -> m #

foldMap :: Monoid m => (a -> m) -> Point d a -> m #

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

foldr :: (a -> b -> b) -> b -> Point d a -> b #

foldr' :: (a -> b -> b) -> b -> Point d a -> b #

foldl :: (b -> a -> b) -> b -> Point d a -> b #

foldl' :: (b -> a -> b) -> b -> Point d a -> b #

foldr1 :: (a -> a -> a) -> Point d a -> a #

foldl1 :: (a -> a -> a) -> Point d a -> a #

toList :: Point d a -> [a] #

null :: Point d a -> Bool #

length :: Point d a -> Int #

elem :: Eq a => a -> Point d a -> Bool #

maximum :: Ord a => Point d a -> a #

minimum :: Ord a => Point d a -> a #

sum :: Num a => Point d a -> a #

product :: Num a => Point d a -> a #

Arity d => Traversable (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

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

sequenceA :: Applicative f => Point d (f a) -> f (Point d a) #

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

sequence :: Monad m => Point d (m a) -> m (Point d a) #

(Arity d, Ord r) => Semigroup (CWMin (Point d r)) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

(<>) :: CWMin (Point d r) -> CWMin (Point d r) -> CWMin (Point d r) #

sconcat :: NonEmpty (CWMin (Point d r)) -> CWMin (Point d r) #

stimes :: Integral b => b -> CWMin (Point d r) -> CWMin (Point d r) #

(Arity d, Ord r) => Semigroup (CWMax (Point d r)) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

(<>) :: CWMax (Point d r) -> CWMax (Point d r) -> CWMax (Point d r) #

sconcat :: NonEmpty (CWMax (Point d r)) -> CWMax (Point d r) #

stimes :: Integral b => b -> CWMax (Point d r) -> CWMax (Point d r) #

Arity d => Arbitrary1 (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

liftArbitrary :: Gen a -> Gen (Point d a) #

liftShrink :: (a -> [a]) -> Point d a -> [Point d a] #

Arity d => Eq1 (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

liftEq :: (a -> b -> Bool) -> Point d a -> Point d b -> Bool #

Arity d => Read1 (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Point d a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Point d a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Point d a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Point d a] #

Arity d => Show1 (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Point d a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Point d a] -> ShowS #

Arity d => Affine (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Associated Types

type Diff (Point d) :: Type -> Type #

Methods

(.-.) :: Num a => Point d a -> Point d a -> Diff (Point d) a #

(.+^) :: Num a => Point d a -> Diff (Point d) a -> Point d a #

(.-^) :: Num a => Point d a -> Diff (Point d) a -> Point d a #

PointFunctor (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

pmap :: (Point (Dimension (Point d r)) r -> Point (Dimension (Point d s)) s) -> Point d r -> Point d s Source #

(Eq r, Arity d) => Eq (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

(==) :: Point d r -> Point d r -> Bool #

(/=) :: Point d r -> Point d r -> Bool #

(Ord r, Arity d) => Ord (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

compare :: Point d r -> Point d r -> Ordering #

(<) :: Point d r -> Point d r -> Bool #

(<=) :: Point d r -> Point d r -> Bool #

(>) :: Point d r -> Point d r -> Bool #

(>=) :: Point d r -> Point d r -> Bool #

max :: Point d r -> Point d r -> Point d r #

min :: Point d r -> Point d r -> Point d r #

(Read r, Arity d) => Read (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

(Show r, Arity d) => Show (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

showsPrec :: Int -> Point d r -> ShowS #

show :: Point d r -> String #

showList :: [Point d r] -> ShowS #

Generic (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Associated Types

type Rep (Point d r) :: Type -> Type #

Methods

from :: Point d r -> Rep (Point d r) x #

to :: Rep (Point d r) x -> Point d r #

(Arity d, Random r) => Random (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

randomR :: RandomGen g => (Point d r, Point d r) -> g -> (Point d r, g) #

random :: RandomGen g => g -> (Point d r, g) #

randomRs :: RandomGen g => (Point d r, Point d r) -> g -> [Point d r] #

randoms :: RandomGen g => g -> [Point d r] #

(Arity d, Arbitrary r) => Arbitrary (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

arbitrary :: Gen (Point d r) #

shrink :: Point d r -> [Point d r] #

(Arity d, Hashable r) => Hashable (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

hashWithSalt :: Int -> Point d r -> Int #

hash :: Point d r -> Int #

(ToJSON r, Arity d) => ToJSON (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

toJSON :: Point d r -> Value #

toEncoding :: Point d r -> Encoding #

toJSONList :: [Point d r] -> Value #

toEncodingList :: [Point d r] -> Encoding #

(FromJSON r, Arity d, KnownNat d) => FromJSON (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

parseJSON :: Value -> Parser (Point d r) #

parseJSONList :: Value -> Parser [Point d r] #

(Arity d, NFData r) => NFData (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

rnf :: Point d r -> () #

(Fractional r, Arity d, Arity (d + 1)) => IsTransformable (Point d r) Source # 
Instance details

Defined in Data.Geometry.Transformation

Methods

transformBy :: Transformation (Dimension (Point d r)) (NumType (Point d r)) -> Point d r -> Point d r Source #

IsBoxable (Point d r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

boundingBox :: Point d r -> Box (Dimension (Point d r)) () (NumType (Point d r)) Source #

(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) #

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

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

(Eq r, Fractional r, Arity d) => IsIntersectableWith (Point d r) (Line d r) Source # 
Instance details

Defined in Data.Geometry.Line

Methods

intersect :: Point d r -> Line d r -> Intersection (Point d r) (Line d r) #

intersects :: Point d r -> Line d r -> Bool #

nonEmptyIntersection :: proxy (Point d r) -> proxy (Line d r) -> Intersection (Point d r) (Line d r) -> Bool #

(Num r, Eq r, Arity d) => IsIntersectableWith (Point d r) (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

Methods

intersect :: Point d r -> HyperPlane d r -> Intersection (Point d r) (HyperPlane d r) #

intersects :: Point d r -> HyperPlane d r -> Bool #

nonEmptyIntersection :: proxy (Point d r) -> proxy (HyperPlane d r) -> Intersection (Point d r) (HyperPlane d r) -> Bool #

(Ord r, Fractional r, Arity d) => IsIntersectableWith (Point d r) (HalfLine d r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

Methods

intersect :: Point d r -> HalfLine d r -> Intersection (Point d r) (HalfLine d r) #

intersects :: Point d r -> HalfLine d r -> Bool #

nonEmptyIntersection :: proxy (Point d r) -> proxy (HalfLine d r) -> Intersection (Point d r) (HalfLine d r) -> Bool #

(Num r, Ord r, Arity d) => IsIntersectableWith (Point d r) (HalfSpace d r) Source # 
Instance details

Defined in Data.Geometry.HalfSpace

Methods

intersect :: Point d r -> HalfSpace d r -> Intersection (Point d r) (HalfSpace d r) #

intersects :: Point d r -> HalfSpace d r -> Bool #

nonEmptyIntersection :: proxy (Point d r) -> proxy (HalfSpace d r) -> Intersection (Point d r) (HalfSpace d r) -> Bool #

(Ord r, Num r) => IsIntersectableWith (Point 2 r) (Line 2 r) Source # 
Instance details

Defined in Data.Geometry.Line

Methods

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

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

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

(Arity d, Ord r) => IsIntersectableWith (Point d r) (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

intersect :: Point d r -> Box d p r -> Intersection (Point d r) (Box d p r) #

intersects :: Point d r -> Box d p r -> Bool #

nonEmptyIntersection :: proxy (Point d r) -> proxy (Box d p r) -> Intersection (Point d r) (Box d p r) -> Bool #

(Ord r, Fractional r, Arity d) => IsIntersectableWith (Point d r) (LineSegment d p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment.Internal

Methods

intersect :: Point d r -> LineSegment d p r -> Intersection (Point d r) (LineSegment d p r) #

intersects :: Point d r -> LineSegment d p r -> Bool #

nonEmptyIntersection :: proxy (Point d r) -> proxy (LineSegment d p r) -> Intersection (Point d r) (LineSegment d p r) -> Bool #

(Ord r, Num r) => IsIntersectableWith (Point 2 r) (LineSegment 2 p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment.Internal

Methods

intersect :: Point 2 r -> LineSegment 2 p r -> Intersection (Point 2 r) (LineSegment 2 p r) #

intersects :: Point 2 r -> LineSegment 2 p r -> Bool #

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

(Fractional r, Ord r) => IsIntersectableWith (Point 2 r) (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon

Methods

intersect :: Point 2 r -> Polygon t p r -> Intersection (Point 2 r) (Polygon t p r) #

intersects :: Point 2 r -> Polygon t p r -> Bool #

nonEmptyIntersection :: proxy (Point 2 r) -> proxy (Polygon t p r) -> Intersection (Point 2 r) (Polygon t p r) -> Bool #

Field1 (Triangle d p r) (Triangle d p r) (Point d r :+ p) (Point d r :+ p) Source # 
Instance details

Defined in Data.Geometry.Triangle

Methods

_1 :: Lens (Triangle d p r) (Triangle d p r) (Point d r :+ p) (Point d r :+ p) #

Field2 (Triangle d p r) (Triangle d p r) (Point d r :+ p) (Point d r :+ p) Source # 
Instance details

Defined in Data.Geometry.Triangle

Methods

_2 :: Lens (Triangle d p r) (Triangle d p r) (Point d r :+ p) (Point d r :+ p) #

Field3 (Triangle d p r) (Triangle d p r) (Point d r :+ p) (Point d r :+ p) Source # 
Instance details

Defined in Data.Geometry.Triangle

Methods

_3 :: Lens (Triangle d p r) (Triangle d p r) (Point d r :+ p) (Point d r :+ p) #

type Diff (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

type Diff (Point d) = Vector d
type Rep (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

type Rep (Point d r) = D1 ('MetaData "Point" "Data.Geometry.Point.Internal" "hgeometry-0.12.0.1-744QXwUb5uS54emseMX1Co" 'True) (C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "toVec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector d r))))
type NumType (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

type NumType (Point d r) = r
type Dimension (Point d r) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

type Dimension (Point d r) = d
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]
type IntersectionOf (Point d r) (Line d r) Source # 
Instance details

Defined in Data.Geometry.Line

type IntersectionOf (Point d r) (Line d r) = '[NoIntersection, Point d r]
type IntersectionOf (Point d r) (HyperPlane d r) Source # 
Instance details

Defined in Data.Geometry.HyperPlane

type IntersectionOf (Point d r) (HalfLine d r) Source # 
Instance details

Defined in Data.Geometry.HalfLine

type IntersectionOf (Point d r) (HalfLine d r) = '[NoIntersection, Point d r]
type IntersectionOf (Point d r) (HalfSpace d r) Source # 
Instance details

Defined in Data.Geometry.HalfSpace

type IntersectionOf (Point d r) (Box d p r) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

type IntersectionOf (Point d r) (Box d p r) = '[NoIntersection, Point d r]
type IntersectionOf (Point d r) (LineSegment d p r) Source # 
Instance details

Defined in Data.Geometry.LineSegment.Internal

type IntersectionOf (Point d r) (LineSegment d p r) = '[NoIntersection, Point d r]
type IntersectionOf (Point 2 r) (Polygon t p r) Source # 
Instance details

Defined in Data.Geometry.Polygon

type IntersectionOf (Point 2 r) (Polygon t p r) = '[NoIntersection, Point 2 r]

origin :: (Arity d, Num r) => Point d r Source #

Point representing the origin in d dimensions

>>> origin :: Point 4 Int
Point4 0 0 0 0

vector :: Lens (Point d r) (Point d r') (Vector d r) (Vector d r') Source #

Lens to access the vector corresponding to this point.

>>> (Point3 1 2 3) ^. vector
Vector3 1 2 3
>>> origin & vector .~ Vector3 1 2 3
Point3 1 2 3

pointFromList :: Arity d => [r] -> Maybe (Point d r) Source #

Constructs a point from a list of coordinates. The length of the list has to match the dimension exactly.

>>> pointFromList [1,2,3] :: Maybe (Point 3 Int)
Just (Point3 1 2 3)
>>> pointFromList [1] :: Maybe (Point 3 Int)
Nothing
>>> pointFromList [1,2,3,4] :: Maybe (Point 3 Int)
Nothing

projectPoint :: (Arity i, Arity d, i <= d) => Point d r -> Point i r Source #

Project a point down into a lower dimension.

xCoord :: (1 <= d, Arity d, AsAPoint point) => Lens' (point d r) r Source #

Shorthand to access the first coordinate C 1

>>> Point3 1 2 3 ^. xCoord
1
>>> Point2 1 2 & xCoord .~ 10
Point2 10 2

yCoord :: (2 <= d, Arity d, AsAPoint point) => Lens' (point d r) r Source #

Shorthand to access the second coordinate C 2

>>> Point2 1 2 ^. yCoord
2
>>> Point3 1 2 3 & yCoord %~ (+1)
Point3 1 3 3

zCoord :: (3 <= d, Arity d, AsAPoint point) => Lens' (point d r) r Source #

Shorthand to access the third coordinate C 3

>>> Point3 1 2 3 ^. zCoord
3
>>> Point3 1 2 3 & zCoord %~ (+1)
Point3 1 2 4

class PointFunctor g where Source #

Types that we can transform by mapping a function on each point in the structure

Methods

pmap :: (Point (Dimension (g r)) r -> Point (Dimension (g s)) s) -> g r -> g s Source #

Instances

Instances details
PointFunctor (Point d) Source # 
Instance details

Defined in Data.Geometry.Point.Internal

Methods

pmap :: (Point (Dimension (Point d r)) r -> Point (Dimension (Point d s)) s) -> Point d r -> Point d s Source #

PointFunctor (ConvexPolygon p) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

PointFunctor (Box d p) Source # 
Instance details

Defined in Data.Geometry.Box.Internal

Methods

pmap :: (Point (Dimension (Box d p r)) r -> Point (Dimension (Box d p s)) s) -> Box d p r -> Box d p s Source #

PointFunctor (LineSegment d p) Source # 
Instance details

Defined in Data.Geometry.LineSegment.Internal

Methods

pmap :: (Point (Dimension (LineSegment d p r)) r -> Point (Dimension (LineSegment d p s)) s) -> LineSegment d p r -> LineSegment d p s Source #

PointFunctor (PolyLine d p) Source # 
Instance details

Defined in Data.Geometry.PolyLine

Methods

pmap :: (Point (Dimension (PolyLine d p r)) r -> Point (Dimension (PolyLine d p s)) s) -> PolyLine d p r -> PolyLine d p s Source #

PointFunctor (BezierSpline n d) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

pmap :: (Point (Dimension (BezierSpline n d r)) r -> Point (Dimension (BezierSpline n d s)) s) -> BezierSpline n d r -> BezierSpline n d s Source #

PointFunctor (Triangle d p) Source # 
Instance details

Defined in Data.Geometry.Triangle

Methods

pmap :: (Point (Dimension (Triangle d p r)) r -> Point (Dimension (Triangle d p s)) s) -> Triangle d p r -> Triangle d p s Source #

PointFunctor (Polygon t p) Source # 
Instance details

Defined in Data.Geometry.Polygon.Core

Methods

pmap :: (Point (Dimension (Polygon t p r)) r -> Point (Dimension (Polygon t p s)) s) -> Polygon t p r -> Polygon t p s Source #

data CCW Source #

Data type for expressing the orientation of three points, with the option of allowing Colinearities.

Instances

Instances details
Eq CCW Source # 
Instance details

Defined in Data.Geometry.Point.Orientation.Degenerate

Methods

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

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

Show CCW Source # 
Instance details

Defined in Data.Geometry.Point.Orientation.Degenerate

Methods

showsPrec :: Int -> CCW -> ShowS #

show :: CCW -> String #

showList :: [CCW] -> ShowS #

ccw :: (Ord r, Num r) => Point 2 r -> Point 2 r -> Point 2 r -> CCW Source #

Given three points p q and r determine the orientation when going from p to r via q.

Be vary of numerical instability: >>> ccw (Point2 0 0.3) (Point2 1 0.6) (Point2 2 (0.9::Double)) CCW

>>> ccw (Point2 0 0.3) (Point2 1 0.6) (Point2 2 (0.9::Rational))
CoLinear

If you can't use Rational, try SafeDouble instead of Double: >>> ccw (Point2 0 0.3) (Point2 1 0.6) (Point2 2 (0.9::SafeDouble)) CoLinear

ccw' :: (Ord r, Num r) => (Point 2 r :+ a) -> (Point 2 r :+ b) -> (Point 2 r :+ c) -> CCW Source #

Given three points p q and r determine the orientation when going from p to r via q.

isCoLinear :: (Eq r, Num r) => Point 2 r -> Point 2 r -> Point 2 r -> Bool Source #

Given three points p q and r determine if the line from p to r via q is straight/colinear.

This is identical to `ccw p q r == CoLinear` but doesn't have the Ord constraint.

pattern CCW :: CCW Source #

CounterClockwise orientation. Also called a left-turn.

pattern CW :: CCW Source #

Clockwise orientation. Also called a right-turn.

pattern CoLinear :: CCW Source #

CoLinear orientation. Also called a straight line.

ccwCmpAround :: (Num r, Ord r) => Point 2 r -> Point 2 r -> Point 2 r -> Ordering Source #

Counter clockwise ordering of the points around c. Points are ordered with respect to the positive x-axis.

ccwCmpAround' :: (Num r, Ord r) => (Point 2 r :+ qc) -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering Source #

Counter clockwise ordering of the points around c. Points are ordered with respect to the positive x-axis.

cwCmpAround :: (Num r, Ord r) => Point 2 r -> Point 2 r -> Point 2 r -> Ordering Source #

Clockwise ordering of the points around c. Points are ordered with respect to the positive x-axis.

cwCmpAround' :: (Num r, Ord r) => (Point 2 r :+ qc) -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering Source #

Clockwise ordering of the points around c. Points are ordered with respect to the positive x-axis.

ccwCmpAroundWith :: (Ord r, Num r) => Vector 2 r -> Point 2 r -> Point 2 r -> Point 2 r -> Ordering Source #

Given a zero vector z, a center c, and two points p and q, compute the ccw ordering of p and q around c with this vector as zero direction.

pre: the points p,q /= c

ccwCmpAroundWith' :: (Ord r, Num r) => Vector 2 r -> (Point 2 r :+ c) -> (Point 2 r :+ a) -> (Point 2 r :+ b) -> Ordering Source #

Given a zero vector z, a center c, and two points p and q, compute the ccw ordering of p and q around c with this vector as zero direction.

pre: the points p,q /= c

cwCmpAroundWith :: (Ord r, Num r) => Vector 2 r -> Point 2 r -> Point 2 r -> Point 2 r -> Ordering Source #

Given a zero vector z, a center c, and two points p and q, compute the cw ordering of p and q around c with this vector as zero direction.

pre: the points p,q /= c

cwCmpAroundWith' :: (Ord r, Num r) => Vector 2 r -> (Point 2 r :+ a) -> (Point 2 r :+ b) -> (Point 2 r :+ c) -> Ordering Source #

Given a zero vector z, a center c, and two points p and q, compute the cw ordering of p and q around c with this vector as zero direction.

pre: the points p,q /= c

sortAround :: (Ord r, Num r) => Point 2 r -> [Point 2 r] -> [Point 2 r] Source #

\( O(n log n) \) Sort the points arround the given point p in counter clockwise order with respect to the rightward horizontal ray starting from p. If two points q and r are colinear with p, the closest one to p is reported first.

sortAround' :: (Ord r, Num r) => (Point 2 r :+ q) -> [Point 2 r :+ p] -> [Point 2 r :+ p] Source #

\( O(n log n) \) Sort the points arround the given point p in counter clockwise order with respect to the rightward horizontal ray starting from p. If two points q and r are colinear with p, the closest one to p is reported first.

insertIntoCyclicOrder :: (Ord r, Num r) => (Point 2 r :+ q) -> (Point 2 r :+ p) -> CList (Point 2 r :+ p) -> CList (Point 2 r :+ p) Source #

\( O(n) \) Given a center c, a new point p, and a list of points ps, sorted in counter clockwise order around c. Insert p into the cyclic order. The focus of the returned cyclic list is the new point p.

data Quadrant Source #

Quadrants of two dimensional points. in CCW order

Instances

Instances details
Bounded Quadrant Source # 
Instance details

Defined in Data.Geometry.Point.Quadrants

Enum Quadrant Source # 
Instance details

Defined in Data.Geometry.Point.Quadrants

Eq Quadrant Source # 
Instance details

Defined in Data.Geometry.Point.Quadrants

Ord Quadrant Source # 
Instance details

Defined in Data.Geometry.Point.Quadrants

Read Quadrant Source # 
Instance details

Defined in Data.Geometry.Point.Quadrants

Show Quadrant Source # 
Instance details

Defined in Data.Geometry.Point.Quadrants

quadrantWith :: (Ord r, 1 <= d, 2 <= d, Arity d) => (Point d r :+ q) -> (Point d r :+ p) -> Quadrant Source #

Quadrants around point c; quadrants are closed on their "previous" boundary (i..e the boundary with the previous quadrant in the CCW order), open on next boundary. The origin itself is assigned the topRight quadrant

quadrant :: (Ord r, Num r, 1 <= d, 2 <= d, Arity d) => (Point d r :+ p) -> Quadrant Source #

Quadrants with respect to the origin

partitionIntoQuadrants :: (Ord r, 1 <= d, 2 <= d, Arity d) => (Point d r :+ q) -> [Point d r :+ p] -> ([Point d r :+ p], [Point d r :+ p], [Point d r :+ p], [Point d r :+ p]) Source #

Given a center point c, and a set of points, partition the points into quadrants around c (based on their x and y coordinates). The quadrants are reported in the order topLeft, topRight, bottomLeft, bottomRight. The points are in the same order as they were in the original input lists. Points with the same x-or y coordinate as p, are "rounded" to above.

cmpByDistanceTo :: (Ord r, Num r, Arity d) => Point d r -> Point d r -> Point d r -> Ordering Source #

Compare by distance to the first argument

cmpByDistanceTo' :: (Ord r, Num r, Arity d) => (Point d r :+ c) -> (Point d r :+ p) -> (Point d r :+ q) -> Ordering Source #

Compare by distance to the first argument

squaredEuclideanDist :: (Num r, Arity d) => Point d r -> Point d r -> r Source #

Squared Euclidean distance between two points

euclideanDist :: (Floating r, Arity d) => Point d r -> Point d r -> r Source #

Euclidean distance between two points

coord :: (1 <= i, i <= d, KnownNat i, Arity d, AsAPoint p) => proxy i -> Lens' (p d r) r Source #

Get the coordinate in a given dimension

>>> Point3 1 2 3 ^. coord (C :: C 2)
2
>>> Point3 1 2 3 & coord (C :: C 1) .~ 10
Point3 10 2 3
>>> Point3 1 2 3 & coord (C :: C 3) %~ (+1)
Point3 1 2 4

unsafeCoord :: (Arity d, AsAPoint p) => Int -> Lens' (p d r) r Source #

Get the coordinate in a given dimension. This operation is unsafe in the sense that no bounds are checked. Consider using coord instead.

>>> Point3 1 2 3 ^. unsafeCoord 2
2