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

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Polygon

Contents

Synopsis

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.

Constructors

Simple 
Multi 

data Polygon t p r where Source #

Constructors

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

PointFunctor (Polygon t p) Source # 

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 #

IpeWriteText r => IpeWriteText (SimplePolygon () r) Source # 
HasDefaultIpeOut (SimplePolygon p r) Source # 
(Eq p, Eq r) => Eq (Polygon t p r) Source # 

Methods

(==) :: Polygon t p r -> Polygon t p r -> Bool #

(/=) :: Polygon t p r -> Polygon t p r -> Bool #

(Show p, Show r) => Show (Polygon t p r) Source # 

Methods

showsPrec :: Int -> Polygon t p r -> ShowS #

show :: Polygon t p r -> String #

showList :: [Polygon t p r] -> ShowS #

Num r => IsTransformable (Polygon t p r) Source # 

Methods

transformBy :: Transformation (Dimension (Polygon t p r)) (NumType (Polygon t p r)) -> Polygon t p r -> Polygon t p r Source #

IsBoxable (Polygon t p r) Source # 

Methods

boundingBox :: Polygon t p r -> Box (Dimension (Polygon t p r)) () (NumType (Polygon t p r)) Source #

type DefaultIpeOut (SimplePolygon p r) Source # 
type NumType (Polygon t p r) Source # 
type NumType (Polygon t p r) = r
type Dimension (Polygon t p r) Source # 
type Dimension (Polygon t p r) = 2

Functions on Polygons

outerBoundary :: forall t p r. Lens' (Polygon t p r) (CSeq (Point 2 r :+ p)) Source #

holes :: forall p r. Lens' (Polygon Multi p r) [Polygon Simple p r] Source #

outerVertex :: Int -> Lens' (Polygon t p r) (Point 2 r :+ p) Source #

Access the i^th vertex on the outer boundary

holeList :: Polygon t p r -> [Polygon Simple p r] Source #

Get all holes in a polygon

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!

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.

cmpExtreme :: (Num r, Ord r) => Vector 2 r -> (Point 2 r :+ p) -> (Point 2 r :+ q) -> Ordering Source #

Comparison that compares which point is larger in the direction given by the vector u.

extremesLinear :: (Ord r, Num r) => Vector 2 r -> Polygon t p r -> (Point 2 r :+ p, Point 2 r :+ p) Source #

Finds the extreme points, minimum and maximum, in a given direction

running time: \(O(n)\)