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

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Point

Contents

Synopsis

Documentation

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

A d-dimensional Point

newtype Point d r Source

A d-dimensional point.

Constructors

Point 

Fields

toVec :: Vector d r
 

Instances

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 .~ v3 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. (Index' (i - 1) d, 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]

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)

type (<=.) i d = (Index' (i - 1) d, Arity d) Source

xCoord :: 1 <=. 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 => 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 => 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

Methods

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

Functions specific to Two Dimensional points

data CCW Source

Constructors

CCW 
CoLinear 
CW 

Instances

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.

sortArround :: (Ord r, Num r) => (Point 2 r :+ p) -> [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 :: (Arity d, Ord r, 1 <=. d, 2 <=. 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 :: (Arity d, Ord r, Num r, 1 <=. d, 2 <=. d) => (Point d r :+ p) -> Quadrant Source

Quadrants with respect to the origin

partitionIntoQuadrants :: (Ord r, Arity d, 1 <=. d, 2 <=. 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