Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
A Polygon data type and some basic functions to interact with them.
Synopsis
- data PolygonType
- data Polygon (t :: PolygonType) p r where
- _SimplePolygon :: Prism' (Polygon Simple p r) (CSeq (Point 2 r :+ p))
- _MultiPolygon :: Prism' (Polygon Multi p r) (CSeq (Point 2 r :+ p), [Polygon Simple p r])
- type SimplePolygon = Polygon Simple
- type MultiPolygon = Polygon Multi
- type SomePolygon p r = Either (Polygon Simple p r) (Polygon Multi p r)
- fromPoints :: [Point 2 r :+ p] -> SimplePolygon p r
- polygonVertices :: Polygon t p r -> NonEmpty (Point 2 r :+ p)
- listEdges :: Polygon t p r -> [LineSegment 2 p r]
- outerBoundary :: forall t p r. Lens' (Polygon t p r) (CSeq (Point 2 r :+ p))
- outerBoundaryEdges :: Polygon t p r -> CSeq (LineSegment 2 p r)
- outerVertex :: Int -> Lens' (Polygon t p r) (Point 2 r :+ p)
- outerBoundaryEdge :: Int -> Polygon t p r -> LineSegment 2 p r
- polygonHoles :: forall p r. Lens' (Polygon Multi p r) [Polygon Simple p r]
- polygonHoles' :: Traversal' (Polygon t p r) [Polygon Simple p r]
- holeList :: Polygon t p r -> [Polygon Simple p r]
- inPolygon :: forall t p r. (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> PointLocationResult
- insidePolygon :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool
- onBoundary :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool
- area :: Fractional r => Polygon t p r -> r
- signedArea :: Fractional r => SimplePolygon p r -> r
- centroid :: Fractional r => SimplePolygon p r -> Point 2 r
- pickPoint :: (Ord r, Fractional r) => Polygon p t r -> Point 2 r
- isTriangle :: Polygon p t r -> Bool
- isStarShaped :: (MonadRandom m, Ord r, Fractional r) => SimplePolygon p r -> m (Maybe (Point 2 r))
- isCounterClockwise :: (Eq r, Fractional r) => Polygon t p r -> Bool
- toCounterClockWiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r
- toCounterClockWiseOrder' :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r
- toClockwiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r
- toClockwiseOrder' :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r
- reverseOuterBoundary :: Polygon t p r -> Polygon t p r
- findDiagonal :: (Ord r, Fractional r) => Polygon t p r -> LineSegment 2 p r
- withIncidentEdges :: Polygon t p r -> Polygon t (Two (LineSegment 2 p r)) r
- numberVertices :: Polygon t p r -> Polygon t (SP Int p) r
- asSimplePolygon :: Polygon t p r -> SimplePolygon p r
- extremesLinear :: (Ord r, Num r) => Vector 2 r -> Polygon t p r -> (Point 2 r :+ p, Point 2 r :+ p)
- cmpExtreme :: (Num r, Ord r) => Vector 2 r -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering
Documentation
data PolygonType Source #
We distinguish between simple polygons (without holes) and Polygons with holes.
data Polygon (t :: PolygonType) p r where Source #
SimplePolygon :: CSeq (Point 2 r :+ p) -> Polygon Simple p r | |
MultiPolygon :: CSeq (Point 2 r :+ p) -> [Polygon Simple p r] -> Polygon Multi p r |
Instances
_SimplePolygon :: Prism' (Polygon Simple p r) (CSeq (Point 2 r :+ p)) Source #
Prism to test
if we are a simple polygon
_MultiPolygon :: Prism' (Polygon Multi p r) (CSeq (Point 2 r :+ p), [Polygon Simple p r]) Source #
Prism to test
if we are a Multi polygon
type SimplePolygon = Polygon Simple Source #
type MultiPolygon = Polygon Multi Source #
type SomePolygon p r = Either (Polygon Simple p r) (Polygon Multi p r) Source #
Either a simple or multipolygon
fromPoints :: [Point 2 r :+ p] -> SimplePolygon p r Source #
Creates a simple polygon from the given list of vertices.
pre: the input list constains no repeated vertices.
polygonVertices :: Polygon t p r -> NonEmpty (Point 2 r :+ p) Source #
The vertices in the polygon. No guarantees are given on the order in which they appear!
listEdges :: Polygon t p r -> [LineSegment 2 p r] Source #
Lists all edges. The edges on the outer boundary are given before the ones on the holes. However, no other guarantees are given on the order.
running time: \(O(n)\)
outerBoundaryEdges :: Polygon t p r -> CSeq (LineSegment 2 p r) Source #
The edges along the outer boundary of the polygon. The edges are half open.
running time: \(O(n)\)
outerVertex :: Int -> Lens' (Polygon t p r) (Point 2 r :+ p) Source #
Access the i^th vertex on the outer boundary
outerBoundaryEdge :: Int -> Polygon t p r -> LineSegment 2 p r Source #
polygonHoles' :: Traversal' (Polygon t p r) [Polygon Simple p r] Source #
inPolygon :: forall t p r. (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> PointLocationResult Source #
Check if a point lies inside a polygon, on the boundary, or outside of the polygon. Running time: O(n).
>>>
Point2 1 1 `inPolygon` simplePoly
Inside>>>
Point2 0 0 `inPolygon` simplePoly
OnBoundary>>>
Point2 10 0 `inPolygon` simplePoly
OnBoundary>>>
Point2 5 13 `inPolygon` simplePoly
Inside>>>
Point2 5 10 `inPolygon` simplePoly
Inside>>>
Point2 10 5 `inPolygon` simplePoly
OnBoundary>>>
Point2 20 5 `inPolygon` simplePoly
Outside
TODO: Add some testcases with multiPolygons TODO: Add some more onBoundary testcases
insidePolygon :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool Source #
Test if a point lies strictly inside the polgyon.
onBoundary :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool Source #
Test if q lies on the boundary of the polygon. Running time: O(n)
>>>
Point2 1 1 `onBoundary` simplePoly
False>>>
Point2 0 0 `onBoundary` simplePoly
True>>>
Point2 10 0 `onBoundary` simplePoly
True>>>
Point2 5 13 `onBoundary` simplePoly
False>>>
Point2 5 10 `onBoundary` simplePoly
False>>>
Point2 10 5 `onBoundary` simplePoly
True>>>
Point2 20 5 `onBoundary` simplePoly
False
TODO: testcases multipolygon
area :: Fractional r => Polygon t p r -> r Source #
Compute the area of a polygon
signedArea :: Fractional r => SimplePolygon p r -> r Source #
Compute the signed area of a simple polygon. The the vertices are in clockwise order, the signed area will be negative, if the verices are given in counter clockwise order, the area will be positive.
centroid :: Fractional r => SimplePolygon p r -> Point 2 r Source #
Compute the centroid of a simple polygon.
pickPoint :: (Ord r, Fractional r) => Polygon p t r -> Point 2 r Source #
Pick a point that is inside the polygon.
(note: if the polygon is degenerate; i.e. has <3 vertices, we report a vertex of the polygon instead.)
pre: the polygon is given in CCW order
running time: \(O(n)\)
isTriangle :: Polygon p t r -> Bool Source #
Test if the polygon is a triangle
running time: \(O(1)\)
isStarShaped :: (MonadRandom m, Ord r, Fractional r) => SimplePolygon p r -> m (Maybe (Point 2 r)) Source #
Test if a Simple polygon is star-shaped. Returns a point in the kernel (i.e. from which the entire polygon is visible), if it exists.
\(O(n)\) expected time
isCounterClockwise :: (Eq r, Fractional r) => Polygon t p r -> Bool Source #
Test if the outer boundary of the polygon is in clockwise or counter clockwise order.
running time: \(O(n)\)
toCounterClockWiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #
Make sure that every edge has the polygon's interior on its left, by orienting the outer boundary into counter-clockwise order, and the inner borders (i.e. any holes, if they exist) into clockwise order.
running time: \(O(n)\)
toCounterClockWiseOrder' :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #
Orient the outer boundary into counter-clockwise order. Leaves any holes as they are.
toClockwiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #
Make sure that every edge has the polygon's interior on its right, by orienting the outer boundary into clockwise order, and the inner borders (i.e. any holes, if they exist) into counter-clockwise order.
running time: \(O(n)\) | Orient the outer boundary of the polygon to clockwise order
toClockwiseOrder' :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #
Orient the outer boundary into clockwise order. Leaves any holes as they are.
reverseOuterBoundary :: Polygon t p r -> Polygon t p r Source #
findDiagonal :: (Ord r, Fractional r) => Polygon t p r -> LineSegment 2 p r Source #
Find a diagonal of the polygon.
pre: the polygon is given in CCW order
running time: \(O(n)\)
withIncidentEdges :: Polygon t p r -> Polygon t (Two (LineSegment 2 p r)) r Source #
Pairs every vertex with its incident edges. The first one is its predecessor edge, the second one its successor edge (in terms of the ordering along the boundary).
>>>
mapM_ print . polygonVertices $ withIncidentEdges simplePoly
Point2 [0,0] :+ V2 LineSegment (Closed (Point2 [1,11] :+ ())) (Closed (Point2 [0,0] :+ ())) LineSegment (Closed (Point2 [0,0] :+ ())) (Closed (Point2 [10,0] :+ ())) Point2 [10,0] :+ V2 LineSegment (Closed (Point2 [0,0] :+ ())) (Closed (Point2 [10,0] :+ ())) LineSegment (Closed (Point2 [10,0] :+ ())) (Closed (Point2 [10,10] :+ ())) Point2 [10,10] :+ V2 LineSegment (Closed (Point2 [10,0] :+ ())) (Closed (Point2 [10,10] :+ ())) LineSegment (Closed (Point2 [10,10] :+ ())) (Closed (Point2 [5,15] :+ ())) Point2 [5,15] :+ V2 LineSegment (Closed (Point2 [10,10] :+ ())) (Closed (Point2 [5,15] :+ ())) LineSegment (Closed (Point2 [5,15] :+ ())) (Closed (Point2 [1,11] :+ ())) Point2 [1,11] :+ V2 LineSegment (Closed (Point2 [5,15] :+ ())) (Closed (Point2 [1,11] :+ ())) LineSegment (Closed (Point2 [1,11] :+ ())) (Closed (Point2 [0,0] :+ ()))
numberVertices :: Polygon t p r -> Polygon t (SP Int p) r Source #
assigns unique integer numbers to all vertices. Numbers start from 0, and are increasing along the outer boundary. The vertices of holes will be numbered last, in the same order.
>>>
numberVertices simplePoly
SimplePolygon (CSeq [Point2 [0,0] :+ SP 0 (),Point2 [10,0] :+ SP 1 (),Point2 [10,10] :+ SP 2 (),Point2 [5,15] :+ SP 3 (),Point2 [1,11] :+ SP 4 ()])
asSimplePolygon :: Polygon t p r -> SimplePolygon p r Source #
Convert a Polygon to a simple polygon by forgetting about any holes.