Did you know ... Search Documentation:
Pack gpc -- prolog/gpc.pl
PublicShow source

What is a polygon?

It is an aggregate of zero or more contours, each comprising zero or more vertices. Each vertex has two double-precision ordinates: x and y. Contours can be external, or hole.

To long, didn't read

Start with an empty polygon. Add contours. Call this the subject polygon. Do the same again with different contours. Call this the clipping polygon. Clip the subject polygon against the other. The result can be a difference, intersection, exclusive-or or union.

In Prolog terms (pardon the pun) it works like this. Use clause

gpc_empty_polygon(Polygon)

to unify Polygon with a new empty GPC polygon. Add an external contour using

gpc_polygon_add_contour(Polygon, external([vertex(0, 0), vertex(1, 1)]))

Ignore the exact vertices; it's just an example. Then add a hole using

gpc_polygon_add_contour(Polygon, hole([vertex(2, 2), vertex(3, 3)]))

Unify the polygon's contours non-deterministically using

gpc_polygon_contour(Polygon, Contour)

Intersect two polygons using

gpc_polygon_clip(int, Subject, Clip, Result)

Where the operation is one of: diff, int, xor, union.

Tristrips

You can also clip two polygons resulting in a triangle strip. Each strip comprises zero or more vertex lists, each representing a sub-strip of connected triangles. The interface lets you convert polygons to tristrips. You cannot directly create a tristrip.

Tristrips model in Prolog as blobs, just as polygons. You can convert from polygon to tristrip using gpc_polygon_to_tristrip/2, but polygons can clip with a tristrip result directly using

gpc_tristrip_clip(Op, Subject, Clip, Result)

where Result is a tristrip blob rather than a polygon blob. Get the number of tristrip sub-strips using

gpc_tristrip_num_strips(Tristrip, NumStrips)

and you can unify non-deterministically with the sub-strip vertex lists using

gpc_tristrip_vertices(Tristrip, Vertices)

Vertices is a list of vertex(X, Y) compounds describing a strip. Supplementary predicates give access to a tristrip's normalised triangles, their determinants as well as the tristrip's total area.

author
- Roy Ratcliffe <royratcliffe@me.com>
 gpc_version(-Version) is det
Version is the GPC version number, a colon-compound of major and minor version integers.
 gpc_empty_polygon(-Polygon) is det
Unifies Polygon with an empty polygon having no contours, no holes, and consequently no vertices.
 gpc_polygon_num_contours(+Polygon, -NumContours:integer) is det
NumContours unifies with the number of polygon contours, including holes.
 gpc_polygon_add_contour(+Polygon, +Contour:compound) is det
Adds a new Contour to Polygon. Each contour is a list of vertex(X, Y) compounds describing either an external contour or a hole.

External contours must wind clockwise.

 gpc_polygon(+Contours:list(compound), +Polygon) is det
Builds a Polygon from a given a list of Contours.
 gpc_polygon_contour(+Polygon, -Contour:compound) is nondet
Unifies one-by-one with contours in the polygon. Each contour is a compound whose functor indicates external or hole.

Fails if the polygon has no contours.

 gpc_polygon_vertex(+Polygon, ?Hole, -Vertex:compound) is nondet
Unifies with every Polygon Vertex matching Hole. Hole is one of:
  • external for exterior vertices,
  • hole for interior vertices, or
  • unbound for both exterior and interior.
 gpc_polygon_box(+Polygon, -Box:compound) is det
Aggregates the bounding Box of Polygon where Box becomes =box(MinX, MinY, MaxX, MaxY)=.

Makes no assumptions about vertex orientation. The minima is not necessarily the left-most or bottom-most. That depends on the coordinate system.

 gpc_polygon_clip(+Op:atom, +Subject, +Clip, -Result) is det
Clips the Subject contours against the Clip contours, unifying the resulting contours at Result polygon.
 gpc_read_polygon(Spec, Polygon, Options) is semidet
Reads Polygon from a file Spec. Replaces the foreign implementation.
 gpc_polygon_codes(+Polygon, -Codes) is det
gpc_polygon_codes(-Polygon, +Codes) is semidet
The clipper conventionally serialises polygons as a series of whitespace-delimited integer and floating-point numbers. The first number is the number of contours, an integer. This encoding appears in GPF (generic polygon) files.

There is one slight complication: hole serialisation is optional. Defaults to external contour. Applies a definite-clause grammar to the Polygon or the Codes, generating or parsing appropriately. The grammar is flexible enough to transform contours either with or without a hole flag, but always generates a serialisation with the hole flag indicating external contour or hole.

 gpc_polygon_to_tristrip(+Polygon, -Tristrip) is det
Converts Polygon to Tristrip.
 gpc_tristrip_clip(+Op:atom, +Subject, +Clip, -Result) is det
Clips Subject polygon against Clip polygon, resulting in a tristrip Result.
 gpc_tristrip_num_strips(+Tristrip, -NumStrips:nonneg) is det
Number of strips within Tristrip. This amounts to the same as
findall(Strip, gpc_tristrip_vertices(Strip), Strips),
length(Strips, NumStrips)

Except that it does not enumerate and collate the actual contiguous sub-strips.

 gpc_tristrip_vertices(+Tristrip, -Vertices:list(compound)) is nondet
Unifies with Vertices belonging to Tristrip, where vertices is a span of one or more vertex(X, Y) compounds representing a contiguous strip of triangles. The Tristrip blob comprises multiple discontiguous triangle strips.
 gpc_tristrip_triangle(+Tristrip, -Triangle:list(compound)) is nondet
Converts tristrip vertices to triangles each of three two-vectors.

Important to note the tristrip's vertex ordering. The first triple in each sub-strip winds 0-1-2 (i.e. first, second, third vertex) but the second winds 1-0-2, i.e. second, first, third vertex; and so on, alternating. The implementation normalises the vertices so that first-second-third ordering correctly unwinds the triangle, as if an independent standalone triangle.

Arguments:
Triangle- is a list of three vertex(X, Y) compounds describing a triangle within the tristrip.
 gpc_tristrip_det(+Tristrip, -Det:number) is nondet
Unifies with the determinant of each triangle in the tristrip.
 gpc_tristrip_area(+Tristrip, -Area:number) is semidet
Area of Tristrip. Accumulates the total area by summing the half-determinants of each triangle.

Fails for empty tristrips. Implies zero area.