hgeometry-0.7.0.0: Geometric Algorithms, Data structures, and Data types.

Copyright(c) Frank Staals
LicenseSee LICENCE file
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Point

Contents

Description

 
Synopsis

Documentation

>>> :{
let myVector :: Vector 3 Int
    myVector = Vector3 1 2 3
    myPoint = Point myVector
:}

A d-dimensional Point

newtype Point d r Source #

A d-dimensional point.

Constructors

Point 

Fields

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

Defined in Data.Geometry.Point

Methods

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

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

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

Defined in Data.Geometry.Point

Methods

fold :: Monoid m => Point d m -> 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

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)) # 
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)) # 
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 => Affine (Point d) Source # 
Instance details

Defined in Data.Geometry.Point

Associated Types

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

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

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

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

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 #

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

Defined in Data.Geometry.Point

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

Associated Types

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

Methods

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

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

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

Defined in Test.QuickCheck.HGeometryInstances

Methods

arbitrary :: Gen (Point d r) #

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

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

Defined in Data.Geometry.Point

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

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

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 #

IpeWriteText r => IpeWriteText (Point 2 r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Writer

Methods

ipeWriteText :: Point 2 r -> Maybe Text Source #

Coordinate r => IpeReadText (Point 2 r) Source # 
Instance details

Defined in Data.Geometry.Ipe.Reader

HasDefaultIpeOut (Point 2 r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (Point 2 r) :: * -> * Source #

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

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

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

type Diff (Point d) Source # 
Instance details

Defined in Data.Geometry.Point

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

Defined in Data.Geometry.Point

type Rep (Point d r) = D1 (MetaData "Point" "Data.Geometry.Point" "hgeometry-0.7.0.0-3y7zA7ljCTE9s6EHvXHItM" 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

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

Defined in Data.Geometry.Point

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

Defined in Data.Geometry.Ipe.IpeOut

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 ': ([] :: [*]))

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]

Accessing points

vector :: Lens' (Point 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]

unsafeCoord :: Arity d => Int -> Lens' (Point 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

coord :: forall proxy i d r. (1 <= i, i <= d, ((i - 1) + 1) ~ i, Arity (i - 1), Arity d) => proxy i -> Lens' (Point 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]

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

Constructs a point from a list of coordinates

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

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

Project a point down into a lower dimension.

Convenience functions to construct 2 and 3 dimensional points

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

We provide pattern synonyms Point2 and Point3 for 2 and 3 dimensional points. i.e. we can write:

>>> :{
  let
    f              :: Point 2 r -> r
    f (Point2 x y) = x
  in f (point2 1 2)
:}
1

if we want.

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

Similarly, we can write:

>>> :{
  let
    g                :: Point 3 r -> r
    g (Point3 x y z) = z
  in g myPoint
:}
3

point2 :: r -> r -> Point 2 r Source #

Construct a 2 dimensional point

>>> point2 1 2
Point2 [1,2]

_point2 :: Point 2 r -> (r, r) Source #

Destruct a 2 dimensional point

>>> _point2 $ point2 1 2
(1,2)

point3 :: r -> r -> r -> Point 3 r Source #

Construct a 3 dimensional point

>>> point3 1 2 3
Point3 [1,2,3]

_point3 :: Point 3 r -> (r, r, r) Source #

Destruct a 3 dimensional point

>>> _point3 $ point3 1 2 3
(1,2,3)

xCoord :: (1 <= d, Arity d) => 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) => 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) => 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]

Point Functors

class PointFunctor g where Source #

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

Minimal complete definition

pmap

Methods

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

Instances
PointFunctor (Point d) Source # 
Instance details

Defined in Data.Geometry.Point

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

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

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 #

Functions specific to Two Dimensional points

data CCW Source #

Constructors

CCW 
CoLinear 
CW 
Instances
Eq CCW Source # 
Instance details

Defined in Data.Geometry.Point

Methods

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

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

Show CCW Source # 
Instance details

Defined in Data.Geometry.Point

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.

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.

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

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. running time: O(n log n)

data Quadrant Source #

Quadrants of two dimensional points. in CCW order

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.

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. Points nearer to the center come before points further away.

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. Points nearer to the center come before points further away.

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

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.

running time: O(n)

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