Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data PolygonType
- data Polygon t p r where
- type SimplePolygon = Polygon Simple
- type MultiPolygon = Polygon Multi
- outerBoundary :: forall t p r. Lens' (Polygon t p r) (CSeq (Point 2 r :+ p))
- holes :: forall p r. Lens' (Polygon Multi p r) [Polygon Simple p r]
- outerVertex :: Int -> Lens' (Polygon t p r) (Point 2 r :+ p)
- outerBoundaryEdge :: Int -> Polygon t p r -> LineSegment 2 p r
- holeList :: Polygon t p r -> [Polygon Simple p r]
- polygonVertices :: Polygon t p r -> NonEmpty (Point 2 r :+ p)
- fromPoints :: [Point 2 r :+ p] -> SimplePolygon p r
- outerBoundaryEdges :: Polygon t p r -> CSeq (LineSegment 2 p r)
- toEdges :: CSeq (Point 2 r :+ p) -> CSeq (LineSegment 2 p r)
- onBoundary :: (Fractional r, Ord r) => Point 2 r -> Polygon t p r -> Bool
- 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
- area :: Fractional r => Polygon t p r -> r
- signedArea :: Fractional r => SimplePolygon p r -> r
- centroid :: Fractional r => SimplePolygon p r -> Point 2 r
- isCounterClockwise :: (Eq r, Fractional r) => Polygon t p r -> Bool
- toClockwiseOrder :: (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
- asSimplePolygon :: Polygon t p r -> SimplePolygon p r
- cmpExtreme :: (Num r, Ord r) => Vector 2 r -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering
- extremesLinear :: (Ord r, Num r) => Vector 2 r -> Polygon t p r -> (Point 2 r :+ p, Point 2 r :+ p)
Polygons
>>>
:{
let simplePoly :: SimplePolygon () Rational simplePoly = SimplePolygon . C.fromList . map ext $ [ point2 0 0 , point2 10 0 , point2 10 10 , point2 5 15 , point2 1 11 ] :}
data PolygonType Source #
We distinguish between simple polygons (without holes) and Polygons with holes.
data Polygon t 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 |
PointFunctor (Polygon t p) Source # | |
IpeWriteText r => IpeWriteText (SimplePolygon () r) Source # | |
HasDefaultIpeOut (SimplePolygon p r) Source # | |
(Eq p, Eq r) => Eq (Polygon t p r) Source # | |
(Show p, Show r) => Show (Polygon t p r) Source # | |
Num r => IsTransformable (Polygon t p r) Source # | |
IsBoxable (Polygon t p r) Source # | |
type DefaultIpeOut (SimplePolygon p r) Source # | |
type NumType (Polygon t p r) Source # | |
type Dimension (Polygon t p r) Source # | |
type SimplePolygon = Polygon Simple Source #
type MultiPolygon = Polygon Multi Source #
Functions on Polygons
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 #
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!
fromPoints :: [Point 2 r :+ p] -> SimplePolygon p r Source #
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.
toEdges :: CSeq (Point 2 r :+ p) -> CSeq (LineSegment 2 p r) Source #
Given the vertices of the polygon. Produce a list of edges. The edges are half-open.
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
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.
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.
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(1)\)
toClockwiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #
Orient the outer boundary to clockwise order
toCounterClockWiseOrder :: (Eq r, Fractional r) => Polygon t p r -> Polygon t p r Source #
Orient the outer boundary to counter clockwise order
asSimplePolygon :: Polygon t p r -> SimplePolygon p r Source #
Convert a Polygon to a simple polygon by forgetting about any holes.