| Copyright | (C) Frank Staals | 
|---|---|
| License | see the LICENSE file | 
| Maintainer | Frank Staals | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Geometry.Point
Description
\(d\)-dimensional points.
Synopsis
- newtype Point d r = Point {}
- origin :: (Arity d, Num r) => Point d r
- vector :: Lens' (Point d r) (Vector d r)
- pointFromList :: Arity d => [r] -> Maybe (Point d r)
- 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
- unsafeCoord :: Arity d => Int -> Lens' (Point d r) r
- projectPoint :: (Arity i, Arity d, i <= d) => Point d r -> Point i r
- pattern Point2 :: r -> r -> Point 2 r
- pattern Point3 :: r -> r -> r -> Point 3 r
- xCoord :: (1 <= d, Arity d) => Lens' (Point d r) r
- yCoord :: (2 <= d, Arity d) => Lens' (Point d r) r
- zCoord :: (3 <= d, Arity d) => Lens' (Point d r) r
- class PointFunctor g where
- data CCW
- ccw :: (Ord r, Num r) => Point 2 r -> Point 2 r -> Point 2 r -> CCW
- ccw' :: (Ord r, Num r) => (Point 2 r :+ a) -> (Point 2 r :+ b) -> (Point 2 r :+ c) -> CCW
- ccwCmpAround :: (Num r, Ord r) => (Point 2 r :+ qc) -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering
- cwCmpAround :: (Num r, Ord r) => (Point 2 r :+ qc) -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering
- ccwCmpAroundWith :: (Ord r, Num r) => Vector 2 r -> (Point 2 r :+ c) -> (Point 2 r :+ a) -> (Point 2 r :+ b) -> Ordering
- cwCmpAroundWith :: (Ord r, Num r) => Vector 2 r -> (Point 2 r :+ a) -> (Point 2 r :+ b) -> (Point 2 r :+ c) -> Ordering
- sortAround :: (Ord r, Num r) => (Point 2 r :+ q) -> [Point 2 r :+ p] -> [Point 2 r :+ p]
- insertIntoCyclicOrder :: (Ord r, Num r) => (Point 2 r :+ q) -> (Point 2 r :+ p) -> CList (Point 2 r :+ p) -> CList (Point 2 r :+ p)
- data Quadrant
- quadrantWith :: (Ord r, 1 <= d, 2 <= d, Arity d) => (Point d r :+ q) -> (Point d r :+ p) -> Quadrant
- quadrant :: (Ord r, Num r, 1 <= d, 2 <= d, Arity d) => (Point d r :+ p) -> Quadrant
- 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])
- cmpByDistanceTo :: (Ord r, Num r, Arity d) => (Point d r :+ c) -> (Point d r :+ p) -> (Point d r :+ q) -> Ordering
- squaredEuclideanDist :: (Num r, Arity d) => Point d r -> Point d r -> r
- euclideanDist :: (Floating r, Arity d) => Point d r -> Point d r -> r
Documentation
A d-dimensional point.
Instances
origin :: (Arity d, Num r) => Point d r Source #
Point representing the origin in d dimensions
>>>origin :: Point 4 IntPoint4 [0,0,0,0]
vector :: Lens' (Point d r) (Vector d r) Source #
Lens to access the vector corresponding to this point.
>>>(Point3 1 2 3) ^. vectorVector3 [1,2,3]>>>origin & vector .~ Vector3 1 2 3Point3 [1,2,3]
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]
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) .~ 10Point3 [10,2,3]>>>Point3 1 2 3 & coord (C :: C 3) %~ (+1)Point3 [1,2,4]
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 22
projectPoint :: (Arity i, Arity d, i <= d) => Point d r -> Point i r Source #
Project a point down into a lower dimension.
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
xCoord :: (1 <= d, Arity d) => Lens' (Point d r) r Source #
Shorthand to access the first coordinate C 1
>>>Point3 1 2 3 ^. xCoord1>>>Point2 1 2 & xCoord .~ 10Point2 [10,2]
yCoord :: (2 <= d, Arity d) => Lens' (Point d r) r Source #
Shorthand to access the second coordinate C 2
>>>Point2 1 2 ^. yCoord2>>>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 ^. zCoord3>>>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
Instances
| PointFunctor (Point d) Source # | |
| PointFunctor (ConvexPolygon p) Source # | |
| Defined in Data.Geometry.Polygon.Convex Methods pmap :: (Point (Dimension (ConvexPolygon p r)) r -> Point (Dimension (ConvexPolygon p s)) s) -> ConvexPolygon p r -> ConvexPolygon p s Source # | |
| PointFunctor (Box d p) Source # | |
| PointFunctor (LineSegment d p) Source # | |
| 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 # | |
| PointFunctor (Triangle d p) Source # | |
| PointFunctor (Polygon t p) Source # | |
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.
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 :+ 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 :+ 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 :+ 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 :+ 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)
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)
Quadrants of two dimensional points. in CCW order
Constructors
| TopRight | |
| TopLeft | |
| BottomLeft | |
| BottomRight | 
Instances
| Bounded Quadrant Source # | |
| Enum Quadrant Source # | |
| Defined in Data.Geometry.Point | |
| Eq Quadrant Source # | |
| Ord Quadrant Source # | |
| Defined in Data.Geometry.Point | |
| Read Quadrant Source # | |
| Show Quadrant Source # | |
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 :+ c) -> (Point d r :+ p) -> (Point d r :+ q) -> Ordering Source #
Compare by distance to the first argument