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

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Polygon.Convex

Description

Convex Polygons

Synopsis

Documentation

newtype ConvexPolygon p r Source #

Data Type representing a convex polygon

Constructors

ConvexPolygon 
Instances
PointFunctor (ConvexPolygon p) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

(Eq p, Eq r) => Eq (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

Methods

(==) :: ConvexPolygon p r -> ConvexPolygon p r -> Bool #

(/=) :: ConvexPolygon p r -> ConvexPolygon p r -> Bool #

(Show p, Show r) => Show (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

(NFData p, NFData r) => NFData (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

Methods

rnf :: ConvexPolygon p r -> () #

Fractional r => IsTransformable (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

IsBoxable (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

type NumType (ConvexPolygon p r) Source # 
Instance details

Defined in Data.Geometry.Polygon.Convex

type NumType (ConvexPolygon p r) = r
type Dimension (ConvexPolygon p r) Source #

Polygons are per definition 2 dimensional

Instance details

Defined in Data.Geometry.Polygon.Convex

type Dimension (ConvexPolygon p r) = 2

simplePolygon :: forall p r p r. Iso (ConvexPolygon p r) (ConvexPolygon p r) (SimplePolygon p r) (SimplePolygon p r) Source #

merge :: (Num r, Ord r) => ConvexPolygon p r -> ConvexPolygon p r -> (ConvexPolygon p r, LineSegment 2 p r, LineSegment 2 p r) Source #

Rotating Right - rotate clockwise

Merging two convex hulls, based on the paper:

Two Algorithms for Constructing a Delaunay Triangulation Lee and Schachter International Journal of Computer and Information Sciences, Vol 9, No. 3, 1980

: (combined hull, lower tangent that was added, upper tangent thtat was added)

lowerTangent :: (Num r, Ord r) => ConvexPolygon p r -> ConvexPolygon p r -> LineSegment 2 p r Source #

Compute the lower tangent of the two polgyons

pre: - polygons lp and rp have at least 1 vertex - lp and rp are disjoint, and there is a vertical line separating the two polygons. - The vertices of the polygons are given in clockwise order

Running time: O(n+m), where n and m are the sizes of the two polygons respectively

lowerTangent' :: (Ord r, Num r, Foldable1 f) => f (Point 2 r :+ p) -> f (Point 2 r :+ p) -> Two ((Point 2 r :+ p) :+ [Point 2 r :+ p]) Source #

Compute the lower tangent of the two convex chains lp and rp

pre: - the chains lp and rp have at least 1 vertex - lp and rp are disjoint, and there is a vertical line having lp on the left and rp on the right. - The vertices in the left-chain are given in clockwise order, (right to left) - The vertices in the right chain are given in counterclockwise order (left-to-right)

The result returned is the two endpoints l and r of the tangents, and the remainders lc and rc of the chains (i.e.) such that the lower hull of both chains is: (reverse lc) ++ [l,h] ++ rc

Running time: \(O(n+m)\), where n and m are the sizes of the two chains respectively

upperTangent :: (Num r, Ord r) => ConvexPolygon p r -> ConvexPolygon p r -> LineSegment 2 p r Source #

Compute the upper tangent of the two polgyons

pre: - polygons lp and rp have at least 1 vertex - lp and rp are disjoint, and there is a vertical line separating the two polygons. - The vertices of the polygons are given in clockwise order

Running time: O(n+m), where n and m are the sizes of the two polygons respectively

upperTangent' :: (Ord r, Num r, Foldable1 f) => f (Point 2 r :+ p) -> f (Point 2 r :+ p) -> Two ((Point 2 r :+ p) :+ [Point 2 r :+ p]) Source #

Compute the upper tangent of the two convex chains lp and rp

pre: - the chains lp and rp have at least 1 vertex - lp and rp are disjoint, and there is a vertical line having lp on the left and rp on the right. - The vertices in the left-chain are given in clockwise order, (right to left) - The vertices in the right chain are given in counterclockwise order (left-to-right)

The result returned is the two endpoints l and r of the tangents, and the remainders lc and rc of the chains (i.e.) such that the upper hull of both chains is: (reverse lc) ++ [l,h] ++ rc

Running time: \(O(n+m)\), where n and m are the sizes of the two chains respectively

extremes :: (Num r, Ord r) => Vector 2 r -> ConvexPolygon p r -> (Point 2 r :+ p, Point 2 r :+ p) Source #

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

pre: The input polygon is strictly convex.

running time: \(O(\log n)\)

maxInDirection :: (Num r, Ord r) => Vector 2 r -> ConvexPolygon p r -> Point 2 r :+ p Source #

Finds the extreme maximum point in the given direction. Based on http://geomalgorithms.com/a14-_extreme_pts.html

pre: The input polygon is strictly convex.

running time: \(O(\log^2 n)\)

leftTangent :: (Ord r, Num r) => ConvexPolygon p r -> Point 2 r -> Point 2 r :+ p Source #

rightTangent :: (Ord r, Num r) => ConvexPolygon p r -> Point 2 r -> Point 2 r :+ p Source #

minkowskiSum :: (Ord r, Num r) => ConvexPolygon p r -> ConvexPolygon q r -> ConvexPolygon (p, q) r Source #

Computes the Minkowski sum of the two input polygons with $n$ and $m$ vertices respectively.

pre: input polygons are in CCW order.

running time: \(O(n+m)\).

bottomMost :: Ord r => CSeq (Point 2 r :+ p) -> CSeq (Point 2 r :+ p) Source #

Rotate to the bottommost point (and leftmost in case of ties)