1:- module(gpc, 2 [ gpc_version/1, 3 gpc_empty_polygon/1, 4 gpc_polygon_num_contours/2, 5 gpc_polygon_add_contour/2, 6 gpc_polygon/2, 7 gpc_polygon_contour/2, 8 gpc_polygon_vertex/3, 9 gpc_polygon_box/2, 10 gpc_polygon_clip/4, 11 gpc_read_polygon/3, 12 gpc_polygon_codes/2, 13 gpc_polygon_to_tristrip/2, 14 gpc_tristrip_clip/4, 15 gpc_tristrip_num_strips/2, 16 gpc_tristrip_vertices/2, 17 gpc_tristrip_triangle/2, 18 gpc_tristrip_det/2, 19 gpc_tristrip_area/2 20 ]). 21 22:- predicate_options(gpc_read_polygon/3, 3, 23 [ pass_to(readutil:read_file_to_codes/3, 3) 24 ]). 25 26:- use_foreign_library(foreign(gpc)). 27 28:- use_module(library(dcg/basics)).
vertex(X,
Y)
compounds describing either an external contour or a hole.
External contours must wind clockwise.
125gpc_polygon(Contours, Polygon) :-
126 gpc_empty_polygon(Polygon),
127 forall(member(Contour, Contours), gpc_polygon_add_contour(Polygon, Contour)).
external
or hole
.
Fails if the polygon has no contours.
external
for exterior vertices,hole
for interior vertices, or
144gpc_polygon_vertex(Polygon, Hole, Vertex) :-
145 gpc_polygon_contour(Polygon, Contour),
146 Contour =.. [Hole, Vertices],
147 member(Vertex, Vertices).
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.
158gpc_polygon_box(Polygon, Box) :-
159 aggregate_all(box(min(X), min(Y), max(X), max(Y)),
160 gpc_polygon_vertex(Polygon, external, vertex(X, Y)), Box).
171gpc_read_polygon(Spec, Polygon, Options) :-
172 read_file_to_codes(Spec, Codes, Options),
173 gpc_polygon_codes(Polygon, Codes).
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.
190gpc_polygon_codes(Polygon, Codes) :- 191 var(Polygon), 192 !, 193 phrase(gpf(Contours), Codes), 194 gpc_polygon(Contours, Polygon). 195gpc_polygon_codes(Polygon, Codes) :- 196 findall(Contour, gpc_polygon_contour(Polygon, Contour), Contours), 197 phrase(gpf(Contours), Codes). 198 199gpf(Contours) --> 200 { var(Contours) 201 }, 202 !, 203 blanks, 204 integer(NumContours), 205 contours(Contours), 206 blanks, 207 { length(Contours, NumContours) 208 }. 209gpf(Contours) --> 210 { length(Contours, NumContours) 211 }, 212 integer(NumContours), 213 nl, 214 contours(Contours). 215 216contours([Contour|Contours]) --> 217 contour(Contour), 218 !, 219 contours(Contours). 220contours([]) --> 221 []. 222 223contour(Contour) --> 224 { var(Contour) 225 }, 226 !, 227 blanks, 228 integer(NumVertices), 229 external_or_hole(NumVertices, Contour). 230contour(external(Vertices)) --> 231 !, 232 { length(Vertices, NumVertices) 233 }, 234 integer(NumVertices), 235 nl, 236 integer(0), 237 nl, 238 vertices(NumVertices, Vertices). 239contour(hole(Vertices)) --> 240 { length(Vertices, NumVertices) 241 }, 242 integer(NumVertices), 243 nl, 244 integer(1), 245 nl, 246 vertices(NumVertices, Vertices). 247 248external_or_hole(NumVertices, external(Vertices)) --> 249 blanks, 250 integer(0), 251 blank, 252 !, 253 vertices(NumVertices, Vertices). 254external_or_hole(NumVertices, hole(Vertices)) --> 255 blanks, 256 integer(1), 257 blank, 258 !, 259 vertices(NumVertices, Vertices), 260 { length(Vertices, NumVertices) 261 }. 262external_or_hole(NumVertices, external(Vertices)) --> 263 vertices(NumVertices, Vertices), 264 { length(Vertices, NumVertices) 265 }. 266 267vertices(0, []) --> 268 !, 269 []. 270vertices(NumVertices0, [Vertex|Vertices]) --> 271 vertex(Vertex), 272 { NumVertices is NumVertices0 - 1 273 }, 274 vertices(NumVertices, Vertices). 275 276vertex(Vertex) --> 277 { var(Vertex) 278 }, 279 !, 280 blanks, 281 number(X), 282 blanks, 283 number(Y), 284 { Vertex = vertex(X, Y) 285 }. 286vertex(vertex(X, Y)) --> 287 number(X), 288 " ", 289 number(Y), 290 nl. 291 292nl --> 293 "\r\n", 294 !. 295nl --> 296 "\n".
findall(Strip, gpc_tristrip_vertices(Strip), Strips), length(Strips, NumStrips)
Except that it does not enumerate and collate the actual contiguous sub-strips.
vertex(X, Y)
compounds representing a contiguous
strip of triangles. The Tristrip blob comprises multiple
discontiguous triangle strips.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.
338gpc_tristrip_triangle(Tristrip, Triangle) :- 339 gpc_tristrip_vertices(Tristrip, Vertices), 340 vertices_triangles(Vertices, Triangles), 341 member(Triangle, Triangles). 342 343vertices_triangles([V0, V1, V2], [[V0, V1, V2]]). 344vertices_triangles([V0, V1, V2|T0], [[V0, V1, V2]|T]) :- 345 vertices_triangles_([V1, V2|T0], T). 346 347vertices_triangles_([V0, V1, V2], [[V1, V0, V2]]). 348vertices_triangles_([V0, V1, V2|T0], [[V1, V0, V2]|T]) :- 349 vertices_triangles([V1, V2|T0], T).
355gpc_tristrip_det(Tristrip, Det) :-
356 gpc_tristrip_triangle(Tristrip,
357 [ vertex(X0, Y0),
358 vertex(X1, Y1),
359 vertex(X2, Y2)
360 ]),
361 A is X1 - X0,
362 B is Y1 - Y0,
363 C is X2 - X0,
364 D is Y2 - Y0,
365 Det is A * D - B * C.
Fails for empty tristrips. Implies zero area.
374gpc_tristrip_area(Tristrip, Area) :-
375 aggregate(sum(Det), gpc_tristrip_det(Tristrip, Det), Sum),
376 Area is Sum / 2
Generic Polygon Clipper
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
to unify Polygon with a new empty GPC polygon. Add an external contour using
Ignore the exact vertices; it's just an example. Then add a hole using
Unify the polygon's contours non-deterministically using
Intersect two polygons using
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
where Result is a tristrip blob rather than a polygon blob. Get the number of tristrip sub-strips using
and you can unify non-deterministically with the sub-strip vertex lists using
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.*/