1:- module(
    2  wkt_parse,
    3  [
    4    wkt_parse//1 % -Shape:compound
    5  ]
    6).

Well-Known Text (WKT) parser support

shape(Z:boolean, LRS:boolean, Crs:iri, Shape:compound)

*/

   16:- use_module(library(abnf)).   17:- use_module(library(dcg)).
 wkt_parse(-Shape:compound)// is det
   23wkt_parse(shape(Z,LRS,Crs,Shape)) -->
   24  (   "<",
   25      ...(Codes),
   26      ">"
   27  ->  blank,
   28      blanks, !,
   29      {atom_codes(Crs, Codes)}
   30  ;   {Crs = 'http://www.opengis.net/def/crs/OGC/1.3/CRS84'}
   31  ),
   32  wkt_representation(Z, LRS, Shape).
   33
   34
   35
   36
   37
   38% GRAMMAR %
   39
   40% CircularString
   41
   42circularstring_text(Z, LRS, 'CircularString'(Coords)) -->
   43  (   "("
   44  ->  '+&!'(coord(Z, LRS), ",", Coords),
   45      must_see_code(0'))
   46  ;   empty(Coords)
   47  ).
   48
   49circularstring_text_representation(Z, LRS, CircularString) -->
   50  keyword(`circularstring`),
   51  z_m(Z, LRS),
   52  circularstring_text(Z, LRS, CircularString).
   53
   54
   55
   56collection_text_representation(Z, LRS, MultiPoint) -->
   57  multipoint_text_representation(Z, LRS, MultiPoint), !.
   58collection_text_representation(Z, LRS, MultiCurve) -->
   59  multicurve_text_representation(Z, LRS, MultiCurve), !.
   60collection_text_representation(Z, LRS, MultiSurface) -->
   61  multisurface_text_representation(Z, LRS, MultiSurface), !.
   62collection_text_representation(Z, LRS, GeometryCollection) -->
   63  geometrycollection_text_representation(Z, LRS, GeometryCollection).
   64
   65
   66
   67% CompoundCurve
   68
   69compoundcurve_text(Z, LRS, 'CompoundCurve'(Curves)) -->
   70  (   "("
   71  ->  '+&!'(single_curve_text(Z, LRS), ",", Curves),
   72      must_see_code(0'))
   73  ;   empty(Curves)
   74  ).
   75
   76compoundcurve_text_representation(Z, LRS, CompoundCurve) -->
   77  keyword(`compoundcurve`),
   78  z_m(Z, LRS),
   79  compoundcurve_text(Z, LRS, CompoundCurve).
   80
   81
   82
   83curve_text(Z, LRS, LineString) -->
   84  linestring_text_body(Z, LRS, LineString), !.
   85curve_text(Z, LRS, CircularString) -->
   86  circularstring_text_representation(Z, LRS, CircularString), !.
   87curve_text(Z, LRS, CompoundCurve) -->
   88  compoundcurve_text_representation(Z, LRS, CompoundCurve).
   89
   90
   91curve_text_representation(Z, LRS, LineString) -->
   92  linestring_text_representation(Z, LRS, LineString), !.
   93curve_text_representation(Z, LRS, CircularString) -->
   94  circularstring_text_representation(Z, LRS, CircularString), !.
   95curve_text_representation(Z, LRS, CompoundCurve) -->
   96  compoundcurve_text_representation(Z, LRS, CompoundCurve).
   97
   98
   99
  100% CurvePolygon
  101
  102curvepolygon_text(Z, LRS, 'CurvePolygon'(Rings)) -->
  103  (   "("
  104  ->  '+&!'(ring_text(Z, LRS), ",", Rings),
  105      must_see_code(0'))
  106  ;   empty(Rings)
  107  ).
  108
  109curvepolygon_text_body(Z, LRS, CurvePolygon) -->
  110  curvepolygon_text(Z, LRS, CurvePolygon).
  111
  112curvepolygon_text_representation(Z, LRS, CurvePolygon) -->
  113  keyword(`curvepolygon`),
  114  z_m(Z, LRS),
  115  curvepolygon_text_body(Z, LRS, CurvePolygon), !.
  116curvepolygon_text_representation(Z, LRS, Polygon) -->
  117  polygon_text_representation(Z, LRS, Polygon), !.
  118curvepolygon_text_representation(Z, LRS, Triangle) -->
  119  triangle_text_representation(Z, LRS, Triangle).
  120
  121
  122
  123% GeometryCollection
  124
  125geometrycollection_text(Z, LRS, 'GeometryCollection'(Shapes)) -->
  126  (   "("
  127  ->  '+&!'(wkt_representation(Z, LRS), ",", Shapes),
  128      must_see_code(0'))
  129  ;   empty(Shapes)
  130  ).
  131
  132geometrycollection_text_representation(Z, LRS, GeometryCollection) -->
  133  keyword(`geometrycollection`),
  134  z_m(Z, LRS),
  135  geometrycollection_text(Z, LRS, GeometryCollection).
  136
  137
  138
  139% LineString
  140
  141linestring_text(Z, LRS, 'LineString'(Coords)) -->
  142  (   "("
  143  ->  '+&!'(coord(Z, LRS), ",", Coords),
  144      must_see_code(0'))
  145  ;   empty(Coords)
  146  ).
  147
  148linestring_text_body(Z, LRS, LineString) -->
  149  linestring_text(Z, LRS, LineString).
  150
  151linestring_text_representation(Z, LRS, LineString) -->
  152  keyword(`linestring`),
  153  z_m(Z, LRS),
  154  linestring_text_body(Z, LRS, LineString).
  155
  156
  157
  158% MultiCurve
  159
  160multicurve_text(Z, LRS, 'MultiCurve'(Curves)) -->
  161  (   "("
  162  ->  '+&!'(curve_text(Z, LRS), ",", Curves),
  163      must_see_code(0'))
  164  ;   empty(Curves)
  165  ).
  166
  167multicurve_text_representation(Z, LRS, MultiCurve) -->
  168  keyword(`multicurve`),
  169  z_m(Z, LRS),
  170  multicurve_text(Z, LRS, MultiCurve), !.
  171multicurve_text_representation(Z, LRS, MultiLineString) -->
  172  multilinestring_text_representation(Z, LRS, MultiLineString).
  173
  174
  175
  176% MultiLineString
  177
  178multilinestring_text(Z, LRS, 'MultiLineString'(LineStrings)) -->
  179  (   "("
  180  ->  '+&!'(linestring_text_body(Z, LRS), ",", LineStrings),
  181      must_see_code(0'))
  182  ;   empty(LineStrings)
  183  ).
  184
  185multilinestring_text_representation(Z, LRS, MultiLineString) -->
  186  keyword(`multilinestring`),
  187  z_m(Z, LRS),
  188  multilinestring_text(Z, LRS, MultiLineString).
  189
  190
  191
  192% MultiPoint
  193
  194multipoint_text(Z, LRS, 'MultiPoint'(Coords)) -->
  195  (   "("
  196  ->  '+&!'(point_text(Z, LRS), ",", Coords),
  197      must_see_code(0'))
  198  ;   empty(Coords)
  199  ).
  200
  201multipoint_text_representation(Z, LRS, MultiPoint) -->
  202  keyword(`multipoint`),
  203  z_m(Z, LRS),
  204  multipoint_text(Z, LRS, MultiPoint).
  205
  206
  207
  208% MultiPolygon
  209
  210multipolygon_text(Z, LRS, 'MultiPolygon'(Polygons)) -->
  211  (   "("
  212  ->  '+&!'(polygon_text_body(Z, LRS), ",", Polygons),
  213      must_see_code(0'))
  214  ;   empty(Polygons)
  215  ).
  216
  217multipolygon_text_representation(Z, LRS, MultiPolygon) -->
  218  keyword(`multipolygon`),
  219  z_m(Z, LRS),
  220  multipolygon_text(Z, LRS, MultiPolygon).
  221
  222
  223
  224% MultiSurface
  225
  226multisurface_text(Z, LRS, 'MultiSurface'(Surfaces)) -->
  227  (   "("
  228  ->  '+&!'(surface_text(Z, LRS), ",", Surfaces),
  229      must_see_code(0'))
  230  ;   empty(Surfaces)
  231  ).
  232
  233multisurface_text_representation(Z, LRS, MultiSurface) -->
  234  keyword(`multisurface`),
  235  z_m(Z, LRS),
  236  multisurface_text(Z, LRS, MultiSurface), !.
  237multisurface_text_representation(Z, LRS, MultiPolygon) -->
  238  multipolygon_text_representation(Z, LRS, MultiPolygon), !.
  239multisurface_text_representation(Z, LRS, PolyhedralSurface) -->
  240  polyhedralsurface_text_representation(Z, LRS, PolyhedralSurface), !.
  241multisurface_text_representation(Z, LRS, Tin) -->
  242  tin_text_representation(Z, LRS, Tin).
  243
  244
  245
  246% Point
  247
  248point_text(Z, LRS, Coord) -->
  249  "(",
  250  coord(Z, LRS, Coord),
  251  must_see_code(0')).
  252
  253point_text_representation(Z, LRS, 'Point'(Coord)) -->
  254  keyword(`point`),
  255  z_m(Z, LRS),
  256  point_text(Z, LRS, Coord).
  257
  258
  259
  260% Polygon
  261
  262polygon_text(Z, LRS, 'Polygon'(LineStrings)) -->
  263  (   "("
  264  ->  '+&!'(linestring_text(Z, LRS), ",", LineStrings),
  265      must_see_code(0'))
  266  ;   empty(LineStrings)
  267  ).
  268
  269polygon_text_body(Z, LRS, Polygon) -->
  270  polygon_text(Z, LRS, Polygon).
  271
  272polygon_text_representation(Z, LRS, Polygon) -->
  273  keyword(`polygon`),
  274  z_m(Z, LRS),
  275  polygon_text_body(Z, LRS, Polygon).
  276
  277
  278
  279% PolyhedralSurface
  280
  281polyhedralsurface_text(Z, LRS, 'PolyhedralSurface'(Polygons)) -->
  282  (   "("
  283  ->  '+&!'(polygon_text_body(Z, LRS), ",", Polygons),
  284      must_see_code(0'))
  285  ;   empty(Polygons)
  286  ).
  287
  288polyhedralsurface_text_representation(Z, LRS, PolyhedralSurface) -->
  289  keyword(`polyhedralsurface`),
  290  z_m(Z, LRS),
  291  polyhedralsurface_text(Z, LRS, PolyhedralSurface).
  292
  293
  294
  295ring_text(Z, LRS, LineString) -->
  296  linestring_text_body(Z, LRS, LineString), !.
  297ring_text(Z, LRS, CircularString) -->
  298  circularstring_text_representation(Z, LRS, CircularString), !.
  299ring_text(Z, LRS, CompoundCurve) -->
  300  compoundcurve_text_representation(Z, LRS, CompoundCurve).
  301
  302
  303
  304single_curve_text(Z, LRS, LineString) -->
  305  linestring_text_body(Z, LRS, LineString), !.
  306single_curve_text(Z, LRS, CircularString) -->
  307  circularstring_text_representation(Z, LRS, CircularString).
  308
  309
  310
  311surface_text(Z, LRS, CurvePolygon) -->
  312  keyword(`curvepolygon`),
  313  curvepolygon_text_body(Z, LRS, CurvePolygon), !.
  314surface_text(Z, LRS, Polygon) -->
  315  polygon_text_body(Z, LRS, Polygon).
  316
  317surface_text_representation(Z, LRS, CurvePolygon) -->
  318  curvepolygon_text_representation(Z, LRS, CurvePolygon).
  319
  320
  321
  322% TIN
  323
  324tin_text(Z, LRS, 'TIN'(Triangles)) -->
  325  (   "("
  326  ->  '+&!'(triangle_text_body(Z, LRS), ",", Triangles),
  327      must_see_code(0'))
  328  ;   empty(Triangles)
  329  ).
  330
  331tin_text_representation(Z, LRS, Tin) -->
  332  keyword(`tin`),
  333  z_m(Z, LRS),
  334  tin_text(Z, LRS, Tin).
  335
  336
  337
  338% Triangle
  339
  340triangle_text(Z, LRS, 'Triangle'(LineStrings)) -->
  341  (   "("
  342  ->  linestring_text(Z, LRS, LineString),
  343      {LineStrings = [LineString]},
  344      must_see_code(0'))
  345  ;   empty(LineStrings)
  346  ).
  347
  348triangle_text_body(Z, LRS, Triangle) -->
  349  triangle_text(Z, LRS, Triangle).
  350
  351triangle_text_representation(Z, LRS, Triangle) -->
  352  keyword(`triangle`),
  353  z_m(Z, LRS),
  354  triangle_text_body(Z, LRS, Triangle).
  355
  356
  357
  358wkt_representation(Z, LRS, Point) -->
  359  point_text_representation(Z, LRS, Point), !.
  360wkt_representation(Z, LRS, Curve) -->
  361  curve_text_representation(Z, LRS, Curve), !.
  362wkt_representation(Z, LRS, Surface) -->
  363  surface_text_representation(Z, LRS, Surface), !.
  364wkt_representation(Z, LRS, Collection) -->
  365  collection_text_representation(Z, LRS, Collection).
  366
  367
  368
  369
  370
  371% HELPERS %
 coord(+Z:boolean, +LRS:boolean, -Coord:compound)// is det
  375coord(true, true, coord(X,Y,Z,LRS)) --> !,
  376  coord(true, false, coord(X,Y,Z)),
  377  must_see_code(0' ),
  378  blanks,
  379  m(LRS).
  380coord(true, false, coord(X,Y,Z)) --> !,
  381  coord(false, false, coord(X,Y)),
  382  must_see_code(0' ),
  383  blanks,
  384  'Z'(Z).
  385coord(false, true, coord(X,Y,LRS)) --> !,
  386  coord(false, false, coord(X,Y)),
  387  must_see_code(0' ),
  388  blanks,
  389  m(LRS).
  390coord(false, false, coord(X,Y)) -->
  391  'X'(X),
  392  must_see_code(0' ),
  393  blanks,
  394  'Y'(Y).
 empty(-Shapes:list:compound)//
  400empty([]) -->
  401  keyword(`empty`).
 keyword(+Cs)//
  407keyword([H|T]) -->
  408  alpha(C),
  409  {code_type(H, to_lower(C))},
  410  keyword(T).
  411keyword([]) -->
  412  (alpha(_) -> !, {fail} ; ""),
  413  blanks.
 m(-N)//
  419m(N) -->
  420  number(N).
 must_see_code(-Code)//
  426must_see_code(C) -->
  427  must_see_code(C, blanks).
 X(-N)//
  433'X'(N) -->
  434  number(N).
 Y(-N)//
  440'Y'(N) -->
  441  number(N).
 Z(-N)//
  447'Z'(N) -->
  448  number(N).
 z_m(-Z:boolean, -LRS:boolean)// is det
  454z_m(Z, LRS) -->
  455  ("Z" -> blanks, {Z = true} ; {Z = false}),
  456  ("M" -> blanks, {LRS = true} ; {LRS = false})