1-- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2--
3--
4-- PostGIS - Spatial Types for PostgreSQL
5-- http://postgis.net
6--
7-- Copyright (C) 2010, 2021 Sandro Santilli <strk@kbt.io>
8-- Copyright (C) 2005 Refractions Research Inc.
9--
10-- This is free software; you can redistribute and/or modify it under
11-- the terms of the GNU General Public Licence. See the COPYING file.
12--
13-- Author: Sandro Santilli <strk@kbt.io>
14--
15-- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
16
17--
18-- Type returned by ValidateTopology
19--
20CREATE TYPE topology.ValidateTopology_ReturnType AS (
21  error varchar,
22  id1 integer,
23  id2 integer
24);
25
26--{
27-- Return the exterior ring of a topology face
28--
29--
30CREATE OR REPLACE FUNCTION topology._ValidateTopologyGetFaceShellMaximalEdgeRing(atopology varchar, aface int)
31RETURNS GEOMETRY AS
32$BODY$
33DECLARE
34  sql TEXT;
35  outsidePoint GEOMETRY;
36  shell GEOMETRY;
37BEGIN
38
39  sql := format(
40    $$
41      SELECT
42        ST_Translate(
43          ST_StartPoint( ST_BoundingDiagonal(mbr) ),
44          -1,
45          -1
46        )
47      FROM %1$I.face
48      WHERE face_id = $1
49    $$,
50    atopology
51  );
52  EXECUTE sql USING aface INTO outsidePoint;
53
54  sql := format(
55    $$
56      WITH
57      outside_point AS (
58        SELECT ST_Translate(
59          ST_StartPoint( ST_BoundingDiagonal(mbr) ),
60          -1,
61          -1
62        )
63        FROM %1$I.face
64        WHERE face_id = $1
65      ),
66      leftmost_edge AS (
67        SELECT
68          CASE WHEN left_face = $1
69          THEN
70            edge_id
71          ELSE
72            -edge_id
73          END ring_id
74        FROM %1$I.edge
75        WHERE left_face = $1 or right_face = $1
76        ORDER BY
77#if POSTGIS_PGSQL_VERSION < 95
78          ST_Distance(geom, $2)
79#else
80          geom <-> $2
81#endif
82        LIMIT 1
83      ),
84      edgering AS (
85        SELECT *
86        FROM
87          GetRingEdges(
88            %1$L,
89            (SELECT ring_id FROM leftmost_edge)
90          )
91      )
92      SELECT
93        ST_MakeLine(
94          CASE WHEN r.edge > 0 THEN
95            e.geom
96          ELSE
97            ST_Reverse(e.geom)
98          END
99          ORDER BY r.sequence
100        ) outerRing
101      FROM edgering r, %1$I.edge e
102      WHERE e.edge_id = abs(r.edge)
103    $$,
104    atopology
105  );
106
107  --RAISE DEBUG 'SQL: %', sql;
108
109  EXECUTE sql USING aface, outsidePoint
110  INTO shell;
111
112  -- TODO: check if the ring is not closed
113
114  shell := ST_MakePolygon(shell);
115
116  RETURN shell;
117END;
118$BODY$ LANGUAGE 'plpgsql' STABLE; --}
119
120-- Assumes search_path has topology schema first
121--{
122CREATE OR REPLACE FUNCTION topology._ValidateTopologyGetRingEdges(starting_edge int)
123RETURNS int[]
124AS
125$BODY$
126DECLARE
127  ret int[];
128BEGIN
129  WITH RECURSIVE edgering AS (
130    SELECT
131      starting_edge as signed_edge_id,
132      edge_id,
133      next_left_edge,
134      next_right_edge
135    FROM edge_data
136    WHERE edge_id = abs(starting_edge)
137      UNION
138    SELECT
139      CASE WHEN p.signed_edge_id < 0 THEN
140        p.next_right_edge
141      ELSE
142        p.next_left_edge
143      END,
144      e.edge_id,
145      e.next_left_edge,
146      e.next_right_edge
147    FROM edge_data e, edgering p
148    WHERE e.edge_id =
149      CASE WHEN p.signed_edge_id < 0 THEN
150        abs(p.next_right_edge)
151      ELSE
152        abs(p.next_left_edge)
153      END
154  )
155  SELECT array_agg(signed_edge_id)
156  FROM edgering
157  INTO ret;
158
159  RETURN ret;
160END;
161$BODY$ LANGUAGE 'plpgsql';
162--}
163
164CREATE OR REPLACE FUNCTION topology._CheckEdgeLinking(curedge_edge_id INT, prevedge_edge_id INT, prevedge_next_left_edge INT, prevedge_next_right_edge INT)
165RETURNS topology.ValidateTopology_ReturnType
166AS
167$BODY$
168DECLARE
169  retrec topology.ValidateTopology_ReturnType;
170BEGIN
171  IF prevedge_edge_id > 0
172  THEN -- previous was outgoing, this one should be next-right
173    IF prevedge_next_right_edge != curedge_edge_id THEN
174#ifdef POSTGIS_TOPOLOGY_DEBUG
175      RAISE DEBUG 'Edge % should be next-right of edge %, is % instead',
176        curedge_edge_id,
177        abs(prevedge_edge_id),
178        prevedge_next_right_edge
179      ;
180#endif /* POSTGIS_TOPOLOGY_DEBUG */
181      retrec.error = 'invalid next_right_edge';
182      retrec.id1 = abs(prevedge_edge_id);
183      retrec.id2 = curedge_edge_id; -- we put the expected one here, for convenience
184      RETURN retrec;
185    END IF;
186  ELSE -- previous was incoming, this one should be next-left
187    IF prevedge_next_left_edge != curedge_edge_id THEN
188#ifdef POSTGIS_TOPOLOGY_DEBUG
189      RAISE DEBUG 'Edge % should be next-left of edge %, is % instead',
190        curedge_edge_id,
191        abs(prevedge_edge_id),
192        prevedge_next_left_edge
193      ;
194#endif /* POSTGIS_TOPOLOGY_DEBUG */
195      retrec.error = 'invalid next_left_edge';
196      retrec.id1 = abs(prevedge_edge_id);
197      retrec.id2 = curedge_edge_id; -- we put the expected one here, for convenience
198      RETURN retrec;
199    END IF;
200  END IF;
201
202  RETURN retrec;
203END;
204$BODY$
205LANGUAGE 'plpgsql' IMMUTABLE STRICT;
206
207--
208-- Check that the edges incident to topology nodes
209-- (as advertised by their start_node/end_node)
210-- correctly link to the next incident node on each
211-- side (CW and CCW)
212--
213-- NOTE: if start_node/end_node values are incorrect the behavior
214--       of this function is undefined
215--
216-- NOTE: assumes search_path was set before calling this function
217--
218CREATE OR REPLACE FUNCTION topology._ValidateTopologyEdgeLinking(bbox geometry DEFAULT NULL)
219RETURNS SETOF topology.ValidateTopology_ReturnType
220AS --{
221$BODY$
222DECLARE
223  retrec topology.ValidateTopology_ReturnType;
224  rec RECORD;
225  last_node_id int;
226  last_node_first_edge RECORD;
227  last_node_prev_edge RECORD;
228BEGIN
229  RAISE NOTICE 'Checking edge linking';
230  -- NOTE: this check relies on correct start_node and end_node
231  --       for edges, if those are not correct the results
232  --       of this check do not make much sense.
233  FOR rec IN --{
234      WITH
235      nodes AS (
236        SELECT node_id
237        FROM node
238        WHERE containing_face IS NULL
239        AND (
240          bbox IS NULL
241          OR geom && bbox
242        )
243      ),
244      incident_edges AS (
245        SELECT
246          n.node_id,
247          e.edge_id,
248          e.start_node,
249          e.end_node,
250          e.next_left_edge,
251          e.next_right_edge,
252          ST_RemoveRepeatedPoints(e.geom) as edge_geom
253        FROM edge_data e, nodes n
254        WHERE e.start_node = n.node_id
255        or e.end_node = n.node_id
256      ),
257      edge_star AS (
258        SELECT
259          node_id,
260          edge_id,
261          next_left_edge,
262          next_right_edge,
263          ST_Azimuth(ST_StartPoint(edge_geom), ST_PointN(edge_geom, 2)) as az
264        FROM incident_edges
265        WHERE start_node = node_id
266          UNION ALL
267        SELECT
268          node_id,
269          -edge_id,
270          next_left_edge,
271          next_right_edge,
272          ST_Azimuth(ST_EndPoint(edge_geom), ST_PointN(edge_geom, ST_NumPoints(edge_geom)-1))
273        FROM incident_edges
274        WHERE end_node = node_id
275      ),
276      sequenced_edge_star AS (
277        SELECT
278          row_number() over (partition by node_id order by az, edge_id) seq,
279          *
280        FROM edge_star
281      )
282      SELECT * FROM sequenced_edge_star
283      ORDER BY node_id, seq
284  LOOP --}{
285    IF last_node_id IS NULL OR last_node_id != rec.node_id
286    THEN --{
287      IF last_node_id IS NOT NULL
288      THEN
289        -- Check that last edge (CW from prev one) is correctly linked
290        retrec := topology._CheckEdgeLinking(
291          last_node_first_edge.edge_id,
292          last_node_prev_edge.edge_id,
293          last_node_prev_edge.next_left_edge,
294          last_node_prev_edge.next_right_edge
295        );
296        IF retrec IS NOT NULL
297        THEN
298          RETURN NEXT retrec;
299        END IF;
300#ifdef POSTGIS_TOPOLOGY_DEBUG
301        RAISE DEBUG 'Finished analisys of edge star around node %', last_node_id;
302#endif /* POSTGIS_TOPOLOGY_DEBUG */
303      END IF;
304#ifdef POSTGIS_TOPOLOGY_DEBUG
305      RAISE DEBUG 'Analyzing edge star around node %', rec.node_id;
306#endif /* POSTGIS_TOPOLOGY_DEBUG */
307      last_node_id = rec.node_id;
308      last_node_first_edge = rec;
309    ELSE --}{
310      -- Check that this edge (CW from last one) is correctly linked
311      retrec := topology._CheckEdgeLinking(
312        rec.edge_id,
313        last_node_prev_edge.edge_id,
314        last_node_prev_edge.next_left_edge,
315        last_node_prev_edge.next_right_edge
316      );
317      IF retrec IS NOT NULL
318      THEN
319        RETURN NEXT retrec;
320      END IF;
321    END IF; --}
322    last_node_prev_edge = rec;
323  END LOOP; --}
324  IF last_node_id IS NOT NULL THEN --{
325#ifdef POSTGIS_TOPOLOGY_DEBUG
326    RAISE DEBUG 'Out of loop: last_node_id: %', last_node_id;
327    RAISE DEBUG 'Out of loop: last_node_first_edge edge_id:% next_left_edge:%', last_node_first_edge.edge_id, last_node_first_edge.next_left_edge;
328    RAISE DEBUG 'Out of loop: last_node_prev_edge edge_id:% next_left_edge:%', last_node_prev_edge.edge_id, last_node_prev_edge.next_left_edge;
329    RAISE DEBUG 'Out of loop: last_node_first_edge: %', last_node_first_edge;
330#endif /* POSTGIS_TOPOLOGY_DEBUG */
331    -- Check that last edge (CW from prev one) is correctly linked
332    retrec := topology._CheckEdgeLinking(
333      last_node_first_edge.edge_id,
334      last_node_prev_edge.edge_id,
335      last_node_prev_edge.next_left_edge,
336      last_node_prev_edge.next_right_edge
337      );
338    IF retrec IS NOT NULL
339    THEN
340      RETURN NEXT retrec;
341    END IF;
342#ifdef POSTGIS_TOPOLOGY_DEBUG
343    RAISE DEBUG 'Finished analisys of edge star around node % (out of loop)', last_node_id;
344#endif /* POSTGIS_TOPOLOGY_DEBUG */
345  END IF; --}
346
347
348END;
349$BODY$ --}
350LANGUAGE 'plpgsql' VOLATILE;
351
352--
353-- Check that the edges forming all rings
354-- (as advertised by their next_right_edge/next_left_edge)
355-- consistently advertise the same face on the walking side
356-- (CW or CCW)
357--
358-- NOTE: if next_right_edge/next_left_edge values are incorrect
359--       the behavior of this function is undefined, use
360--       _ValidateTopologyEdgeLinking to verify that
361--
362-- NOTE: assumes search_path was set before calling this function
363--
364-- Creates a pg_temp.hole_check table
365-- Creates a pg_temp.shell_check table
366--
367CREATE OR REPLACE FUNCTION topology._ValidateTopologyRings(bbox geometry DEFAULT NULL)
368RETURNS SETOF topology.ValidateTopology_ReturnType
369AS --{
370$BODY$
371DECLARE
372  retrec topology.ValidateTopology_ReturnType;
373  rec RECORD;
374  ring_poly GEOMETRY;
375  is_shell BOOLEAN;
376  found_rings INT := 0;
377  found_shells INT := 0;
378  found_holes INT := 0;
379BEGIN
380
381  CREATE TEMP TABLE shell_check (
382    face_id int PRIMARY KEY,
383    ring_geom geometry
384  );
385
386  CREATE TEMP TABLE hole_check (
387    ring_id int,
388    hole_mbr geometry, -- point
389    hole_point geometry, -- point
390    in_shell int
391  );
392
393  RAISE NOTICE 'Building edge rings';
394
395  -- Find all rings that can be formed on both sides
396  -- of selected edges
397  FOR rec IN
398    WITH --{
399    considered_edges AS (
400      SELECT e.* FROM edge_data e, node n
401      WHERE
402        ( e.start_node = n.node_id OR e.end_node = n.node_id )
403        AND
404        ( bbox IS NULL OR n.geom && bbox )
405    ),
406    forward_rings AS (
407      SELECT topology._ValidateTopologyGetRingEdges(e.edge_id) edges
408      FROM considered_edges e
409    ),
410    forward_rings_with_id AS (
411      SELECT
412        (select min(e) FROM unnest(edges) e) ring_id,
413        *
414      FROM forward_rings
415    ),
416    distinct_forward_rings AS (
417      SELECT
418        DISTINCT ON (ring_id)
419        *
420      FROM forward_rings_with_id
421    ),
422    backward_rings AS (
423      SELECT topology._ValidateTopologyGetRingEdges(-e.edge_id) edges
424      FROM considered_edges e
425      WHERE -edge_id NOT IN (
426        SELECT x FROM (
427          SELECT unnest(edges) x
428          FROM distinct_forward_rings
429        ) foo
430      )
431    ),
432    backward_rings_with_id AS (
433      SELECT
434        (select min(e) FROM unnest(edges) e) ring_id,
435        *
436      FROM backward_rings
437    ),
438    distinct_backward_rings AS (
439      SELECT
440        DISTINCT ON (ring_id)
441        *
442      FROM backward_rings_with_id
443    ),
444    all_rings AS (
445      SELECT * FROM distinct_forward_rings
446      UNION
447      SELECT * FROM distinct_backward_rings
448    ),
449    all_rings_with_ring_ordinal_edge AS (
450      SELECT
451        r.ring_id,
452        e.seq,
453        e.edge signed_edge_id
454      FROM all_rings r
455      LEFT JOIN LATERAL unnest(r.edges) WITH ORDINALITY AS e(edge, seq)
456      ON TRUE
457    ),
458    all_rings_with_ring_geom AS (
459      SELECT
460        r.ring_id,
461        ST_MakeLine(
462          CASE WHEN signed_edge_id > 0 THEN
463            e.geom
464          ELSE
465            ST_Reverse(e.geom)
466          END
467           -- TODO: how to make sure rows are ordered ?
468          ORDER BY seq
469        ) geom,
470        array_agg(
471          DISTINCT
472          CASE WHEN signed_edge_id > 0 THEN
473            e.left_face
474          ELSE
475            e.right_face
476          END
477        ) side_faces
478      FROM
479        all_rings_with_ring_ordinal_edge r,
480        edge_data e
481      WHERE e.edge_id = abs(r.signed_edge_id)
482      GROUP BY ring_id
483    ) --}{
484    SELECT ring_id, geom as ring_geom, side_faces
485    FROM all_rings_with_ring_geom
486  LOOP --}{
487
488    found_rings := found_rings + 1;
489
490#ifdef POSTGIS_TOPOLOGY_DEBUG
491    RAISE DEBUG 'Ring % - faces:[%]',
492      rec.ring_id,
493      array_to_string(rec.side_faces, ',')
494    ;
495#endif /* POSTGIS_TOPOLOGY_DEBUG */
496
497    -- Check that there's a single face advertised
498    IF array_upper(rec.side_faces,1) != 1
499    THEN --{
500
501#ifdef POSTGIS_TOPOLOGY_DEBUG
502      RAISE DEBUG 'Side faces found on ring %: %', rec.ring_id,
503       rec.side_faces;
504#endif /* POSTGIS_TOPOLOGY_DEBUG */
505      retrec.error = 'mixed face labeling in ring';
506      retrec.id1 = rec.ring_id;
507      retrec.id2 = NULL;
508      RETURN NEXT retrec;
509      CONTINUE;
510
511    END IF; --}
512
513    --RAISE DEBUG 'Ring geom: %', ST_AsTexT(rec.ring_geom);
514    IF NOT ST_Equals(
515      ST_StartPoint(rec.ring_geom),
516      ST_EndPoint(rec.ring_geom)
517    )
518    THEN --{
519      -- This should have been reported before,
520      -- on the edge linking check
521      retrec.error = 'non-closed ring';
522      retrec.id1 = rec.ring_id;
523      retrec.id2 = NULL;
524      RETURN NEXT retrec;
525      CONTINUE;
526    END IF; --}
527
528    -- Ring is valid, save it.
529    is_shell := false;
530    IF ST_NPoints(rec.ring_geom) > 3 THEN
531      ring_poly := ST_MakePolygon(rec.ring_geom);
532      IF ST_IsPolygonCCW(ring_poly) THEN
533        is_shell := true;
534      END IF;
535    END IF;
536
537    IF is_shell THEN --{ It's a shell (CCW)
538      -- Check that a single face is ever used
539      --       for each distinct CCW ring (shell)
540      BEGIN
541        INSERT INTO shell_check VALUES (
542          rec.side_faces[1],
543          ring_poly
544        );
545        found_shells := found_shells + 1;
546      EXCEPTION WHEN unique_violation THEN
547        retrec.error = 'face has multiple shells';
548        retrec.id1 = rec.side_faces[1];
549        retrec.id2 = rec.ring_id;
550        RETURN NEXT retrec;
551      END;
552    ELSE -- }{ It's an hole (CW)
553    -- NOTE: multiple CW rings (holes) can exist for a given face
554      INSERT INTO hole_check VALUES (
555        rec.ring_id,
556        ST_Envelope(rec.ring_geom),
557        ST_PointN(rec.ring_geom, 1),
558        -- NOTE: we don't incurr in the risk
559        --       of a ring touching the shell
560        --       because in those cases the
561        --       intruding "hole" will not really
562        --       be considered an hole as its ring
563        --       will not be CW
564        rec.side_faces[1]
565      );
566      found_holes := found_holes + 1;
567    END IF; --} hole
568
569  END LOOP; --}
570
571  RAISE NOTICE 'Found % rings, % valid shells, % valid holes',
572    found_rings, found_shells, found_holes
573  ;
574
575#ifdef POSTGIS_TOPOLOGY_DEBUG
576  FOR rec IN
577    SELECT * FROM hole_check
578  LOOP
579    RAISE DEBUG 'Hole % in_shell % point % mbr %',
580      rec.ring_id, rec.in_shell, ST_AsText(rec.hole_point), ST_AsText(rec.hole_mbr);
581  END LOOP;
582#endif /* POSTGIS_TOPOLOGY_DEBUG */
583
584END;
585$BODY$ --}
586LANGUAGE 'plpgsql' VOLATILE;
587
588--{
589--  ValidateTopology(toponame, [bbox])
590--
591--  Return a Set of ValidateTopology_ReturnType containing
592--  informations on all topology inconsistencies
593--
594-- Availability: 1.0.0
595-- Changed: 3.2.0 - add bbox optional parameter
596--
597CREATE OR REPLACE FUNCTION topology.ValidateTopology(toponame varchar, bbox geometry DEFAULT NULL)
598  RETURNS setof topology.ValidateTopology_ReturnType
599AS
600$$
601DECLARE
602  retrec topology.ValidateTopology_ReturnType;
603  rec RECORD;
604  rec2 RECORD;
605  affected_rows integer;
606  invalid_edges integer[];
607  invalid_faces integer[];
608  has_invalid_edge_linking BOOLEAN := false;
609  has_invalid_rings BOOLEAN := false;
610  search_path_backup text;
611  containing_face integer;
612BEGIN
613
614  IF NOT EXISTS (
615    SELECT oid
616    FROM pg_catalog.pg_namespace
617    WHERE nspname = toponame
618  )
619  THEN
620    RAISE EXCEPTION 'Topology schema % does not exist', toponame;
621  END IF;
622
623  IF NOT EXISTS (
624    SELECT id
625    FROM topology.topology
626    WHERE name = toponame
627  )
628  THEN
629    RAISE WARNING 'Topology % is not registered in topology.topology', toponame;
630  END IF;
631
632  EXECUTE 'SHOW search_path' INTO search_path_backup;
633  EXECUTE 'SET search_PATH TO ' || quote_ident(toponame) || ','
634                                || search_path_backup;
635
636  IF bbox IS NOT NULL THEN
637    RAISE NOTICE 'Limiting topology checking to bbox %', ST_AsEWKT(ST_Envelope(bbox));
638  END IF;
639
640
641  -- Check for coincident nodes
642  RAISE NOTICE 'Checking for coincident nodes';
643  FOR rec IN
644    SELECT a.node_id as id1, b.node_id as id2
645    FROM
646      node a,
647      node b
648    WHERE a.node_id < b.node_id
649    AND ST_DWithin(a.geom, b.geom, 0) -- NOTE: see #1625 and #1789
650    AND (
651      bbox IS NULL
652      OR (
653        a.geom && bbox
654        AND
655        b.geom && bbox
656      )
657    )
658  LOOP
659    retrec.error = 'coincident nodes';
660    retrec.id1 = rec.id1;
661    retrec.id2 = rec.id2;
662    RETURN NEXT retrec;
663  END LOOP;
664
665  -- Check for edge crossed nodes
666  -- TODO: do this in the single edge loop
667  RAISE NOTICE 'Checking for edges crossing nodes';
668  FOR rec IN
669    SELECT n.node_id as nid, e.edge_id as eid
670    FROM
671      node n,
672      edge e
673    WHERE e.start_node != n.node_id
674    AND e.end_node != n.node_id
675    AND ST_Within(n.geom, e.geom)
676    AND (
677      bbox IS NULL
678      OR (
679        n.geom && bbox
680        AND
681        e.geom && bbox
682      )
683    )
684  LOOP
685    retrec.error = 'edge crosses node';
686    retrec.id1 = rec.eid; -- edge_id
687    retrec.id2 = rec.nid; -- node_id
688    RETURN NEXT retrec;
689  END LOOP;
690
691  -- Scan all edges
692  RAISE NOTICE 'Checking for invalid or not-simple edges';
693  FOR rec IN
694    SELECT e.geom, e.edge_id as id1, e.left_face, e.right_face
695    FROM edge e
696    WHERE (
697      bbox IS NULL
698      OR e.geom && bbox
699    )
700    ORDER BY edge_id
701  LOOP --{
702
703    -- Any invalid edge becomes a cancer for higher level complexes
704    IF NOT ST_IsValid(rec.geom) THEN
705
706      retrec.error = 'invalid edge';
707      retrec.id1 = rec.id1;
708      retrec.id2 = NULL;
709      RETURN NEXT retrec;
710      invalid_edges := array_append(invalid_edges, rec.id1);
711
712      IF invalid_faces IS NULL OR NOT rec.left_face = ANY ( invalid_faces )
713      THEN
714        invalid_faces := array_append(invalid_faces, rec.left_face);
715      END IF;
716
717      IF rec.right_face != rec.left_face AND ( invalid_faces IS NULL OR
718            NOT rec.right_face = ANY ( invalid_faces ) )
719      THEN
720        invalid_faces := array_append(invalid_faces, rec.right_face);
721      END IF;
722
723      CONTINUE;
724
725    END IF;
726
727    -- Check edge being simple (ie: not self-intersecting)
728    IF NOT ST_IsSimple(rec.geom) THEN
729      retrec.error = 'edge not simple';
730      retrec.id1 = rec.id1;
731      retrec.id2 = NULL;
732      RETURN NEXT retrec;
733    END IF;
734
735  END LOOP; --}
736
737  -- Check for edge crossing
738  RAISE NOTICE 'Checking for crossing edges';
739  FOR rec IN
740    SELECT
741      e1.edge_id as id1,
742      e2.edge_id as id2,
743      e1.geom as g1,
744      e2.geom as g2,
745      ST_Relate(e1.geom, e2.geom) as im
746    FROM
747      edge e1,
748      edge e2
749    WHERE
750      e1.edge_id < e2.edge_id
751      AND e1.geom && e2.geom
752      AND (
753        invalid_edges IS NULL OR (
754          NOT e1.edge_id = ANY (invalid_edges)
755          AND
756          NOT e2.edge_id = ANY (invalid_edges)
757        )
758      )
759      AND (
760        bbox IS NULL
761        OR (
762          e1.geom && bbox
763          AND
764          e2.geom && bbox
765        )
766      )
767  LOOP --{
768
769    IF ST_RelateMatch(rec.im, 'FF1F**1*2') THEN
770      CONTINUE; -- no interior intersection
771
772    --
773    -- Closed lines have no boundary, so endpoint
774    -- intersection would be considered interior
775    -- See http://trac.osgeo.org/postgis/ticket/770
776    -- See also full explanation in topology.AddEdge
777    --
778
779    ELSIF ST_RelateMatch(rec.im, 'FF10F01F2') THEN
780      -- first line (g1) is open, second (g2) is closed
781      -- first boundary has puntual intersection with second interior
782      --
783      -- compute intersection, check it equals second endpoint
784      IF ST_Equals(ST_Intersection(rec.g2, rec.g1),
785                   ST_StartPoint(rec.g2))
786      THEN
787        CONTINUE;
788      END IF;
789
790    ELSIF ST_RelateMatch(rec.im, 'F01FFF102') THEN
791      -- second line (g2) is open, first (g1) is closed
792      -- second boundary has puntual intersection with first interior
793      --
794      -- compute intersection, check it equals first endpoint
795      IF ST_Equals(ST_Intersection(rec.g2, rec.g1),
796                   ST_StartPoint(rec.g1))
797      THEN
798        CONTINUE;
799      END IF;
800
801    ELSIF ST_RelateMatch(rec.im, '0F1FFF1F2') THEN
802      -- both lines are closed (boundary intersects nothing)
803      -- they have puntual intersection between interiors
804      --
805      -- compute intersection, check it's a single point
806      -- and equals first StartPoint _and_ second StartPoint
807      IF ST_Equals(ST_Intersection(rec.g1, rec.g2),
808                   ST_StartPoint(rec.g1)) AND
809         ST_Equals(ST_StartPoint(rec.g1), ST_StartPoint(rec.g2))
810      THEN
811        CONTINUE;
812      END IF;
813
814    END IF;
815
816    retrec.error = 'edge crosses edge';
817    retrec.id1 = rec.id1;
818    retrec.id2 = rec.id2;
819    RETURN NEXT retrec;
820  END LOOP; --}
821
822  -- Check for edge start_node geometry mis-match
823  -- TODO: move this in the first edge table scan
824  RAISE NOTICE 'Checking for edges start_node mismatch';
825  FOR rec IN
826    SELECT e.edge_id as id1, n.node_id as id2
827    FROM
828      edge e,
829      node n
830    WHERE e.start_node = n.node_id
831    AND NOT ST_Equals(ST_StartPoint(e.geom), n.geom)
832    AND (
833      bbox IS NULL
834      OR e.geom && bbox
835    )
836  LOOP --{
837    retrec.error = 'edge start node geometry mis-match';
838    retrec.id1 = rec.id1;
839    retrec.id2 = rec.id2;
840    RETURN NEXT retrec;
841  END LOOP; --}
842
843  -- Check for edge end_node geometry mis-match
844  -- TODO: move this in the first edge table scan
845  RAISE NOTICE 'Checking for edges end_node mismatch';
846  FOR rec IN
847    SELECT e.edge_id as id1, n.node_id as id2
848    FROM
849      edge e,
850      node n
851    WHERE e.end_node = n.node_id
852    AND NOT ST_Equals(ST_EndPoint(e.geom), n.geom)
853    AND (
854      bbox IS NULL
855      OR e.geom && bbox
856    )
857  LOOP --{
858    retrec.error = 'edge end node geometry mis-match';
859    retrec.id1 = rec.id1;
860    retrec.id2 = rec.id2;
861    RETURN NEXT retrec;
862  END LOOP; --}
863
864  -- Check for faces w/out edges
865  RAISE NOTICE 'Checking for faces without edges';
866  FOR rec IN
867    SELECT face_id as id1
868    FROM face
869    WHERE face_id > 0
870    AND (
871      bbox IS NULL
872      OR mbr && bbox
873    )
874    EXCEPT (
875      SELECT left_face FROM edge
876      UNION
877      SELECT right_face FROM edge
878    )
879  LOOP --{
880    retrec.error = 'face without edges';
881    retrec.id1 = rec.id1;
882    retrec.id2 = NULL;
883    RETURN NEXT retrec;
884  END LOOP; --}
885
886  -- Validate edge linking
887  -- NOTE: relies on correct start_node/end_node on edges
888  FOR rec IN SELECT * FROM topology._ValidateTopologyEdgeLinking(bbox)
889  LOOP
890    RETURN next rec;
891    has_invalid_edge_linking := true;
892  END LOOP;
893
894  IF has_invalid_edge_linking THEN
895    DROP TABLE IF EXISTS pg_temp.hole_check;
896    DROP TABLE IF EXISTS pg_temp.shell_check;
897    RETURN; -- does not make sense to continue
898  END IF;
899
900  --- Validate edge rings
901  FOR rec IN SELECT * FROM topology._ValidateTopologyRings(bbox)
902  LOOP
903    RETURN next rec;
904    has_invalid_rings := true;
905  END LOOP;
906
907  IF has_invalid_rings THEN
908    DROP TABLE IF EXISTS pg_temp.hole_check;
909    DROP TABLE IF EXISTS pg_temp.shell_check;
910    RETURN; -- does not make sense to continue
911  END IF;
912
913  -- Now create a temporary table to construct all face geometries
914  -- for checking their consistency
915
916  RAISE NOTICE 'Constructing geometry of all faces';
917  -- TODO: only construct exterior ring
918
919  CREATE TEMP TABLE face_check ON COMMIT DROP AS
920  SELECT
921    sc.face_id,
922    sc.ring_geom AS shell,
923    f.mbr
924  FROM
925    pg_temp.shell_check sc, face f
926  WHERE
927    f.face_id = sc.face_id
928  ;
929
930  DROP TABLE pg_temp.shell_check;
931
932
933  IF bbox IS NOT NULL
934  THEN --{
935    INSERT INTO pg_temp.face_check
936    SELECT face_id,
937      topology._ValidateTopologyGetFaceShellMaximalEdgeRing(toponame, face_id),
938      mbr
939    FROM face
940    WHERE mbr && bbox
941    AND (
942      CASE WHEN invalid_faces IS NOT NULL THEN
943        NOT face_id = ANY(invalid_faces)
944      ELSE
945        TRUE
946      END
947    )
948    AND face_id NOT IN (
949      SELECT face_id FROM pg_temp.face_check
950    )
951    ;
952  END IF; --}
953
954  -- Build a gist index on geom
955  CREATE INDEX ON face_check USING gist (shell);
956
957  -- Build a btree index on id
958  CREATE INDEX ON face_check (face_id);
959
960  -- Scan the table looking for NULL geometries
961  -- or geometries with wrong MBR consistency
962  RAISE NOTICE 'Checking faces';
963  affected_rows := 0;
964  FOR rec IN
965    SELECT * FROM face_check
966  LOOP --{
967
968    affected_rows := affected_rows + 1;
969
970    IF rec.shell IS NULL OR ST_IsEmpty(rec.shell)
971    THEN
972      -- Face missing !
973      retrec.error := 'face has no rings';
974      retrec.id1 := rec.face_id;
975      retrec.id2 := NULL;
976      RETURN NEXT retrec;
977    END IF;
978
979    IF NOT ST_Equals(rec.mbr, ST_Envelope(rec.shell))
980    THEN
981#ifdef POSTGIS_TOPOLOGY_DEBUG
982      RAISE DEBUG 'MBR expected:% obtained:%', ST_AsEWKT(ST_Envelope(rec.shell)), ST_AsEWKT(ST_Envelope(rec.mbr));
983#endif /* POSTGIS_TOPOLOGY_DEBUG */
984      -- Inconsistent MBR!
985      retrec.error := 'face has wrong mbr';
986      retrec.id1 := rec.face_id;
987      retrec.id2 := NULL;
988      RETURN NEXT retrec;
989    END IF;
990
991  END LOOP; --}
992
993  RAISE NOTICE 'Checked % faces', affected_rows;
994
995  -- Check edges are covered by their left-right faces (#4830)
996  RAISE NOTICE 'Checking for holes coverage';
997  affected_rows := 0;
998  FOR rec IN
999    SELECT * FROM hole_check
1000  LOOP --{
1001    SELECT f.face_id
1002    FROM face_check f
1003    WHERE rec.hole_mbr @ f.shell
1004    AND _ST_Contains(f.shell, rec.hole_point)
1005    ORDER BY ST_Area(f.shell) ASC
1006    LIMIT 1
1007    INTO rec2;
1008
1009    IF ( NOT FOUND AND rec.in_shell != 0 )
1010       OR ( rec2.face_id != rec.in_shell )
1011    THEN
1012        retrec.error := 'hole not in advertised face';
1013        retrec.id1 := rec.ring_id;
1014        retrec.id2 := NULL;
1015        RETURN NEXT retrec;
1016    END IF;
1017    affected_rows := affected_rows + 1;
1018
1019  END LOOP; --}
1020
1021  RAISE NOTICE 'Finished checking for coverage of % holes', affected_rows;
1022
1023  -- Check nodes have correct containing_face (#3233)
1024  -- NOTE: relies on correct edge linking
1025  RAISE NOTICE 'Checking for node containing_face correctness';
1026  FOR rec IN
1027    SELECT
1028      n.node_id,
1029      n.geom geom,
1030      n.containing_face,
1031      e.edge_id
1032    FROM node n
1033    LEFT JOIN edge e ON (
1034      e.start_node = n.node_id OR
1035      e.end_node = n.node_id
1036    )
1037    WHERE
1038     ( bbox IS NULL OR n.geom && bbox )
1039  LOOP --{
1040
1041    IF rec.edge_id IS NOT NULL
1042    THEN --{
1043      -- Node is not isolated, make sure it
1044      -- advertises itself as such
1045      IF rec.containing_face IS NOT NULL
1046      THEN --{
1047        -- node is not really isolated
1048        retrec.error := 'not-isolated node has not-null containing_face';
1049        retrec.id1 := rec.node_id;
1050        retrec.id2 := NULL;
1051        RETURN NEXT retrec;
1052      END IF; --}
1053    ELSE -- }{
1054      -- Node is isolated, make sure it
1055      -- advertises itself as such
1056      IF rec.containing_face IS NULL
1057      THEN --{
1058        -- isolated node advertises itself as non-isolated
1059        retrec.error := 'isolated node has null containing_face';
1060        retrec.id1 := rec.node_id;
1061        retrec.id2 := NULL;
1062        RETURN NEXT retrec;
1063      ELSE -- }{
1064        -- node is isolated and advertising a containing_face
1065        -- now let's check it's really in contained by it
1066        BEGIN
1067          containing_face := topology.GetFaceContainingPoint(toponame, rec.geom);
1068        EXCEPTION WHEN OTHERS THEN
1069          RAISE NOTICE 'Got % (%)', SQLSTATE, SQLERRM;
1070          retrec.error := format('got exception trying to find face containing node: %s', SQLERRM);
1071          retrec.id1 := rec.node_id;
1072          retrec.id2 := NULL;
1073          RETURN NEXT retrec;
1074        END;
1075        IF containing_face != rec.containing_face THEN
1076          retrec.error := 'isolated node has wrong containing_face';
1077          retrec.id1 := rec.node_id;
1078          retrec.id2 := NULL; -- TODO: write expected containing_face here ?
1079          RETURN NEXT retrec;
1080        END IF;
1081      END IF; --}
1082    END IF; --}
1083
1084  END LOOP; --}
1085
1086
1087  DROP TABLE pg_temp.hole_check;
1088  DROP TABLE pg_temp.face_check;
1089
1090  EXECUTE 'SET search_PATH TO ' || search_path_backup;
1091
1092  RETURN;
1093END
1094$$
1095LANGUAGE 'plpgsql' VOLATILE; -- NOTE: we need VOLATILE to use SHOW
1096--} ValidateTopology(toponame, bbox)
1097
1098