1:- module(
2 wkt_generate,
3 [
4 wkt_generate//1 5 ]
6).
12:- use_module(library(error)). 13
14:- use_module(library(abnf)). 15:- use_module(library(dcg)). 16
17
18
20
21circularstring_text(_, _, 'CircularString'([])) --> !,
22 "Empty".
23circularstring_text(Z, LRS, 'CircularString'(Coords)) -->
24 "(",
25 '+&!'(coord(Z, LRS), ",", Coords),
26 ")".
27
28circularstring_text_representation(Z, LRS, CircularString) -->
29 "CircularString",
30 z_m(Z, LRS),
31 circularstring_text(Z, LRS, CircularString).
32
33
34
35collection_text_representation(Z, LRS, MultiPoint) -->
36 multipoint_text_representation(Z, LRS, MultiPoint), !.
37collection_text_representation(Z, LRS, MultiCurve) -->
38 multicurve_text_representation(Z, LRS, MultiCurve), !.
39collection_text_representation(Z, LRS, MultiSurface) -->
40 multisurface_text_representation(Z, LRS, MultiSurface), !.
41collection_text_representation(Z, LRS, GeometryCollection) -->
42 geometrycollection_text_representation(Z, LRS, GeometryCollection).
43
44
45
47
48compoundcurve_text(_, _, 'CompoundCurve'([])) --> !,
49 "Empty".
50compoundcurve_text(Z, LRS, 'CompoundCurve'(Curves)) -->
51 "(",
52 '+&!'(single_curve_text(Z, LRS), ",", Curves),
53 ")".
54
55compoundcurve_text_representation(Z, LRS, CompoundCurve) -->
56 "CompoundCurve",
57 z_m(Z, LRS),
58 compoundcurve_text(Z, LRS, CompoundCurve).
59
60
61
62curve_text(Z, LRS, LineString) -->
63 linestring_text_body(Z, LRS, LineString), !.
64curve_text(Z, LRS, CircularString) -->
65 circularstring_text_representation(Z, LRS, CircularString), !.
66curve_text(Z, LRS, CompoundCurve) -->
67 compoundcurve_text_representation(Z, LRS, CompoundCurve).
68
69curve_text_representation(Z, LRS, LineString) -->
70 linestring_text_representation(Z, LRS, LineString), !.
71curve_text_representation(Z, LRS, CircularString) -->
72 circularstring_text_representation(Z, LRS, CircularString), !.
73curve_text_representation(Z, LRS, CompoundCurve) -->
74 compoundcurve_text_representation(Z, LRS, CompoundCurve).
75
76
77
79
80curvepolygon_text(_, _, 'CurvePolygon'([])) --> !,
81 "Empty".
82curvepolygon_text(Z, LRS, 'CurvePolygon'(Rings)) -->
83 "(",
84 '+&!'(ring_text(Z, LRS), ",", Rings),
85 ")".
86
87curvepolygon_text_body(Z, LRS, CurvePolygon) -->
88 curvepolygon_text(Z, LRS, CurvePolygon).
89
90curvepolygon_text_representation(Z, LRS, CurvePolygon) -->
91 "CurvePolygon",
92 z_m(Z, LRS),
93 curvepolygon_text_body(Z, LRS, CurvePolygon), !.
94curvepolygon_text_representation(Z, LRS, Polygon) -->
95 polygon_text_representation(Z, LRS, Polygon), !.
96curvepolygon_text_representation(Z, LRS, Triangle) -->
97 triangle_text_representation(Z, LRS, Triangle).
98
99
100
102
103geometrycollection_text(_, _, 'GeometryCollection'([])) --> !,
104 "Empty".
105geometrycollection_text(Z, LRS, 'GeometryCollection'(Shapes)) -->
106 "(",
107 '+&!'(wkt_representation(Z, LRS), ",", Shapes),
108 ")".
109
110geometrycollection_text_representation(Z, LRS, GeometryCollection) -->
111 "GeometryCollection",
112 z_m(Z, LRS),
113 geometrycollection_text(Z, LRS, GeometryCollection).
114
115
116
118
119linestring_text(_, _, 'LineString'([])) --> !,
120 "Empty".
121linestring_text(Z, LRS, 'LineString'(Coords)) -->
122 "(",
123 '+&!'(coord(Z, LRS), ",", Coords),
124 ")".
125
126linestring_text_body(Z, LRS, LineString) -->
127 linestring_text(Z, LRS, LineString).
128
129linestring_text_representation(Z, LRS, LineString) -->
130 "LineString",
131 z_m(Z, LRS),
132 linestring_text_body(Z, LRS, LineString).
133
134
135
137
138multicurve_text(_, _, 'MultiCurve'([])) --> !,
139 "Empty".
140multicurve_text(Z, LRS, 'MultiCurve'(Curves)) -->
141 "(",
142 '+&!'(curve_text(Z, LRS), ",", Curves),
143 ")".
144
145multicurve_text_representation(Z, LRS, MultiCurve) -->
146 "MultiCurve",
147 z_m(Z, LRS),
148 multicurve_text(Z, LRS, MultiCurve), !.
149multicurve_text_representation(Z, LRS, MultiLineString) -->
150 multilinestring_text_representation(Z, LRS, MultiLineString).
151
152
153
155
156multilinestring_text(_, _, 'MultiLineString'([])) --> !,
157 "Empty".
158multilinestring_text(Z, LRS, 'MultiLineString'(LineStrings)) -->
159 "(",
160 '+&!'(linestring_text_body(Z, LRS), ",", LineStrings),
161 ")".
162
163multilinestring_text_representation(Z, LRS, MultiLineString) -->
164 "MultiLineString",
165 z_m(Z, LRS),
166 multilinestring_text(Z, LRS, MultiLineString).
167
168
169
171
172multipoint_text(_, _, 'MultiPoint'([])) --> !,
173 "Empty".
174multipoint_text(Z, LRS, 'MultiPoint'(Coords)) -->
175 "(",
176 '+&!'(coord(Z, LRS), ",", Coords),
177 ")".
178
179multipoint_text_representation(Z, LRS, MultiPoint) -->
180 "MultiPoint",
181 z_m(Z, LRS),
182 multipoint_text(Z, LRS, MultiPoint).
183
184
185
187
188multipolygon_text(_, _, 'MultiPolygon'([])) --> !,
189 "Empty".
190multipolygon_text(Z, LRS, 'MultiPolygon'(Polygons)) -->
191 "(",
192 '+&!'(polygon_text_body(Z, LRS), ",", Polygons),
193 ")".
194
195multipolygon_text_representation(Z, LRS, MultiPolygon) -->
196 "MultiPolygon",
197 z_m(Z, LRS),
198 multipolygon_text(Z, LRS, MultiPolygon).
199
200
201
203
204multisurface_text(_, _, 'MultiSurface'([])) --> !,
205 "Empty".
206multisurface_text(Z, LRS, 'MultiSurface'(Surfaces)) -->
207 "(",
208 '+&!'(surface_text(Z, LRS), ",", Surfaces),
209 ")".
210
211multisurface_text_representation(Z, LRS, MultiSurface) -->
212 "MultiSurface",
213 z_m(Z, LRS),
214 multisurface_text(Z, LRS, MultiSurface), !.
215multisurface_text_representation(Z, LRS, MultiPolygon) -->
216 multipolygon_text_representation(Z, LRS, MultiPolygon), !.
217multisurface_text_representation(Z, LRS, PolyhedralSurface) -->
218 polyhedralsurface_text_representation(Z, LRS, PolyhedralSurface), !.
219multisurface_text_representation(Z, LRS, Tin) -->
220 tin_text_representation(Z, LRS, Tin).
221
222
223
225
228point_text(Z, LRS, Coord) -->
229 "(",
230 coord(Z, LRS, Coord),
231 ")".
232
233point_text_representation(Z, LRS, 'Point'(Coord)) -->
234 "Point",
235 z_m(Z, LRS),
236 point_text(Z, LRS, Coord).
237
238
239
241
242polygon_text(_, _, 'Polygon'([])) --> !,
243 "Empty".
244polygon_text(Z, LRS, 'Polygon'(LineStrings)) -->
245 "(",
246 '+&!'(linestring_text(Z, LRS), ",", LineStrings),
247 ")".
248
249polygon_text_body(Z, LRS, Polygon) -->
250 polygon_text(Z, LRS, Polygon).
251
252polygon_text_representation(Z, LRS, Polygon) -->
253 "Polygon",
254 z_m(Z, LRS),
255 polygon_text_body(Z, LRS, Polygon).
256
257
258
260
261polyhedralsurface_text(_, _, 'PolyhedralSurface'([])) --> !,
262 "Empty".
263polyhedralsurface_text(Z, LRS, 'PolyhedralSurface'(Polygons)) -->
264 "(",
265 '+&!'(polygon_text_body(Z, LRS), ",", Polygons),
266 ")".
267
268polyhedralsurface_text_representation(Z, LRS, PolyhedralSurface) -->
269 "PolyhedralSurface",
270 z_m(Z, LRS),
271 polyhedralsurface_text(Z, LRS, PolyhedralSurface).
272
273
274
275ring_text(Z, LRS, LineString) -->
276 linestring_text_body(Z, LRS, LineString), !.
277ring_text(Z, LRS, CircularString) -->
278 circularstring_text_representation(Z, LRS, CircularString), !.
279ring_text(Z, LRS, CompoundCurve) -->
280 compoundcurve_text_representation(Z, LRS, CompoundCurve).
281
282
283
284single_curve_text(Z, LRS, LineString) -->
285 linestring_text_body(Z, LRS, LineString), !.
286single_curve_text(Z, LRS, CircularString) -->
287 circularstring_text_representation(Z, LRS, CircularString).
288
289
290
292
293surface_text(Z, LRS, CurvePolygon) -->
294 "CurvePolygon",
295 curvepolygon_text_body(Z, LRS, CurvePolygon), !.
296surface_text(Z, LRS, Polygon) -->
297 polygon_text_body(Z, LRS, Polygon).
298
299surface_text_representation(Z, LRS, CurvePolygon) -->
300 curvepolygon_text_representation(Z, LRS, CurvePolygon).
301
302
303
305
306tin_text(_, _, 'TIN'([])) --> !,
307 "Empty".
308tin_text(Z, LRS, 'TIN'([Triangles])) -->
309 "(",
310 '+&!'(triangle_text_body(Z, LRS), ",", Triangles),
311 ")".
312
313tin_text_representation(Z, LRS, Tin) -->
314 "TIN",
315 z_m(Z, LRS),
316 tin_text(Z, LRS, Tin).
317
318
319
321
322triangle_text(_, _, 'Triangle'([])) --> !,
323 "Empty".
324triangle_text(Z, LRS, 'Triangle'([LineString])) -->
325 "(",
326 linestring_text(Z, LRS, LineString),
327 ")".
328
329triangle_text_body(Z, LRS, Triangle) -->
330 triangle_text(Z, LRS, Triangle).
331
332triangle_text_representation(Z, LRS, Triangle) -->
333 "Triangle",
334 z_m(Z, LRS),
335 triangle_text_body(Z, LRS, Triangle).
341wkt_generate(shape(Z,LRS,Crs,Shape)) -->
342 crs(Crs),
343 wkt_representation(Z, LRS, Shape).
344
345crs('http://www.opengis.net/def/crs/EPSG/0/4326') --> !, "".
346crs('http://www.opengis.net/def/crs/OGC/1.3/CRS84') --> !, "".
347crs(Crs) --> "<", atom(Crs), "> ".
348
349wkt_representation(Z, LRS, Point) -->
350 point_text_representation(Z, LRS, Point), !.
351wkt_representation(Z, LRS, Curve) -->
352 curve_text_representation(Z, LRS, Curve), !.
353wkt_representation(Z, LRS, Surface) -->
354 surface_text_representation(Z, LRS, Surface), !.
355wkt_representation(Z, LRS, Collection) -->
356 collection_text_representation(Z, LRS, Collection).
357
358
359
360
361
366coord(false, false, coord(X,Y)) --> !,
367 'X'(X),
368 " ",
369 'Y'(Y).
370coord(false, true, coord(X,Y,LRS)) --> !,
371 coord(false, false, coord(X,Y)),
372 " ",
373 m(LRS).
374coord(true, false, coord(X,Y,Z)) --> !,
375 coord(false, false, coord(X,Y)),
376 " ",
377 'Z'(Z).
378coord(true, true, coord(X,Y,Z,LRS)) -->
379 coord(true, false, coord(X,Y,Z)),
380 " ",
381 m(LRS).
387m(N) -->
388 number(N).
394'X'(N) -->
395 {must_be(number, N)},
396 number(N).
402'Y'(N) -->
403 {must_be(number, N)},
404 number(N).
410'Z'(N) -->
411 {must_be(number, N)},
412 number(N).
418z_m(false, false) --> !, "".
419z_m(false, true) --> !, " M ".
420z_m(true, false) --> !, " Z ".
421z_m(true, true) --> " ZM "
Well-Known Text (WKT) generator support
*/