View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        R.A.O'Keefe, Vitor Santos Costa, Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  1984-2021, VU University Amsterdam
    7                              CWI, Amsterdam
    8                              SWI-Prolog Solutions .b.v
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(ugraphs,
   38          [ add_edges/3,                % +Graph, +Edges, -NewGraph
   39            add_vertices/3,             % +Graph, +Vertices, -NewGraph
   40            complement/2,               % +Graph, -NewGraph
   41            compose/3,                  % +LeftGraph, +RightGraph, -NewGraph
   42            del_edges/3,                % +Graph, +Edges, -NewGraph
   43            del_vertices/3,             % +Graph, +Vertices, -NewGraph
   44            edges/2,                    % +Graph, -Edges
   45            neighbors/3,                % +Vertex, +Graph, -Vertices
   46            neighbours/3,               % +Vertex, +Graph, -Vertices
   47            reachable/3,                % +Vertex, +Graph, -Vertices
   48            top_sort/2,                 % +Graph, -Sort
   49            top_sort/3,                 % +Graph, -Sort0, -Sort
   50            transitive_closure/2,       % +Graph, -Closure
   51            transpose_ugraph/2,         % +Graph, -NewGraph
   52            vertices/2,                 % +Graph, -Vertices
   53            vertices_edges_to_ugraph/3, % +Vertices, +Edges, -Graph
   54            ugraph_union/3,             % +Graph1, +Graph2, -Graph
   55            connect_ugraph/3            % +Graph1, -Start, -Graph
   56          ]).

Graph manipulation library

The S-representation of a graph is a list of (vertex-neighbours) pairs, where the pairs are in standard order (as produced by keysort) and the neighbours of each vertex are also in standard order (as produced by sort). This form is convenient for many calculations.

A new UGraph from raw data can be created using vertices_edges_to_ugraph/3.

Adapted to support some of the functionality of the SICStus ugraphs library by Vitor Santos Costa.

Ported from YAP 5.0.1 to SWI-Prolog by Jan Wielemaker.

author
- R.A.O'Keefe
- Vitor Santos Costa
- Jan Wielemaker
license
- BSD-2 or Artistic 2.0 */
   79:- autoload(library(lists),[append/3]).   80:- autoload(library(ordsets),
   81	    [ord_subtract/3,ord_union/3,ord_add_element/3,ord_union/4]).
 vertices(+Graph, -Vertices)
Unify Vertices with all vertices appearing in Graph. Example:
?- vertices([1-[3,5],2-[4],3-[],4-[5],5-[]], L).
L = [1, 2, 3, 4, 5]
   90vertices([], []) :- !.
   91vertices([Vertex-_|Graph], [Vertex|Vertices]) :-
   92    vertices(Graph, Vertices).
 vertices_edges_to_ugraph(+Vertices, +Edges, -UGraph) is det
Create a UGraph from Vertices and edges. Given a graph with a set of Vertices and a set of Edges, Graph must unify with the corresponding S-representation. Note that the vertices without edges will appear in Vertices but not in Edges. Moreover, it is sufficient for a vertice to appear in Edges.
?- vertices_edges_to_ugraph([],[1-3,2-4,4-5,1-5], L).
L = [1-[3,5], 2-[4], 3-[], 4-[5], 5-[]]

In this case all vertices are defined implicitly. The next example shows three unconnected vertices:

?- vertices_edges_to_ugraph([6,7,8],[1-3,2-4,4-5,1-5], L).
L = [1-[3,5], 2-[4], 3-[], 4-[5], 5-[], 6-[], 7-[], 8-[]]
  116vertices_edges_to_ugraph(Vertices, Edges, Graph) :-
  117    sort(Edges, EdgeSet),
  118    p_to_s_vertices(EdgeSet, IVertexBag),
  119    append(Vertices, IVertexBag, VertexBag),
  120    sort(VertexBag, VertexSet),
  121    p_to_s_group(VertexSet, EdgeSet, Graph).
 add_vertices(+Graph, +Vertices, -NewGraph)
Unify NewGraph with a new graph obtained by adding the list of Vertices to Graph. Example:
?- add_vertices([1-[3,5],2-[]], [0,1,2,9], NG).
NG = [0-[], 1-[3,5], 2-[], 9-[]]
  134add_vertices(Graph, Vertices, NewGraph) :-
  135    msort(Vertices, V1),
  136    add_vertices_to_s_graph(V1, Graph, NewGraph).
  137
  138add_vertices_to_s_graph(L, [], NL) :-
  139    !,
  140    add_empty_vertices(L, NL).
  141add_vertices_to_s_graph([], L, L) :- !.
  142add_vertices_to_s_graph([V1|VL], [V-Edges|G], NGL) :-
  143    compare(Res, V1, V),
  144    add_vertices_to_s_graph(Res, V1, VL, V, Edges, G, NGL).
  145
  146add_vertices_to_s_graph(=, _, VL, V, Edges, G, [V-Edges|NGL]) :-
  147    add_vertices_to_s_graph(VL, G, NGL).
  148add_vertices_to_s_graph(<, V1, VL, V, Edges, G, [V1-[]|NGL]) :-
  149    add_vertices_to_s_graph(VL, [V-Edges|G], NGL).
  150add_vertices_to_s_graph(>, V1, VL, V, Edges, G, [V-Edges|NGL]) :-
  151    add_vertices_to_s_graph([V1|VL], G, NGL).
  152
  153add_empty_vertices([], []).
  154add_empty_vertices([V|G], [V-[]|NG]) :-
  155    add_empty_vertices(G, NG).
 del_vertices(+Graph, +Vertices, -NewGraph) is det
Unify NewGraph with a new graph obtained by deleting the list of Vertices and all the edges that start from or go to a vertex in Vertices to the Graph. Example:
?- del_vertices([1-[3,5],2-[4],3-[],4-[5],5-[],6-[],7-[2,6],8-[]],
                [2,1],
                NL).
NL = [3-[],4-[5],5-[],6-[],7-[6],8-[]]
Compatibility
- Upto 5.6.48 the argument order was (+Vertices, +Graph, -NewGraph). Both YAP and SWI-Prolog have changed the argument order for compatibility with recent SICStus as well as consistency with del_edges/3.
  175del_vertices(Graph, Vertices, NewGraph) :-
  176    sort(Vertices, V1),             % JW: was msort
  177    (   V1 = []
  178    ->  Graph = NewGraph
  179    ;   del_vertices(Graph, V1, V1, NewGraph)
  180    ).
  181
  182del_vertices(G, [], V1, NG) :-
  183    !,
  184    del_remaining_edges_for_vertices(G, V1, NG).
  185del_vertices([], _, _, []).
  186del_vertices([V-Edges|G], [V0|Vs], V1, NG) :-
  187    compare(Res, V, V0),
  188    split_on_del_vertices(Res, V,Edges, [V0|Vs], NVs, V1, NG, NGr),
  189    del_vertices(G, NVs, V1, NGr).
  190
  191del_remaining_edges_for_vertices([], _, []).
  192del_remaining_edges_for_vertices([V0-Edges|G], V1, [V0-NEdges|NG]) :-
  193    ord_subtract(Edges, V1, NEdges),
  194    del_remaining_edges_for_vertices(G, V1, NG).
  195
  196split_on_del_vertices(<, V, Edges, Vs, Vs, V1, [V-NEdges|NG], NG) :-
  197    ord_subtract(Edges, V1, NEdges).
  198split_on_del_vertices(>, V, Edges, [_|Vs], Vs, V1, [V-NEdges|NG], NG) :-
  199    ord_subtract(Edges, V1, NEdges).
  200split_on_del_vertices(=, _, _, [_|Vs], Vs, _, NG, NG).
 add_edges(+Graph, +Edges, -NewGraph)
Unify NewGraph with a new graph obtained by adding the list of Edges to Graph. Example:
?- add_edges([1-[3,5],2-[4],3-[],4-[5],
              5-[],6-[],7-[],8-[]],
             [1-6,2-3,3-2,5-7,3-2,4-5],
             NL).
NL = [1-[3,5,6], 2-[3,4], 3-[2], 4-[5],
      5-[7], 6-[], 7-[], 8-[]]
  216add_edges(Graph, Edges, NewGraph) :-
  217    p_to_s_graph(Edges, G1),
  218    ugraph_union(Graph, G1, NewGraph).
 ugraph_union(+Graph1, +Graph2, -NewGraph)
NewGraph is the union of Graph1 and Graph2. Example:
?- ugraph_union([1-[2],2-[3]],[2-[4],3-[1,2,4]],L).
L = [1-[2], 2-[3,4], 3-[1,2,4]]
  229ugraph_union(Set1, [], Set1) :- !.
  230ugraph_union([], Set2, Set2) :- !.
  231ugraph_union([Head1-E1|Tail1], [Head2-E2|Tail2], Union) :-
  232    compare(Order, Head1, Head2),
  233    ugraph_union(Order, Head1-E1, Tail1, Head2-E2, Tail2, Union).
  234
  235ugraph_union(=, Head-E1, Tail1, _-E2, Tail2, [Head-Es|Union]) :-
  236    ord_union(E1, E2, Es),
  237    ugraph_union(Tail1, Tail2, Union).
  238ugraph_union(<, Head1, Tail1, Head2, Tail2, [Head1|Union]) :-
  239    ugraph_union(Tail1, [Head2|Tail2], Union).
  240ugraph_union(>, Head1, Tail1, Head2, Tail2, [Head2|Union]) :-
  241    ugraph_union([Head1|Tail1], Tail2, Union).
 del_edges(+Graph, +Edges, -NewGraph)
Unify NewGraph with a new graph obtained by removing the list of Edges from Graph. Notice that no vertices are deleted. Example:
?- del_edges([1-[3,5],2-[4],3-[],4-[5],5-[],6-[],7-[],8-[]],
             [1-6,2-3,3-2,5-7,3-2,4-5,1-3],
             NL).
NL = [1-[5],2-[4],3-[],4-[],5-[],6-[],7-[],8-[]]
  255del_edges(Graph, Edges, NewGraph) :-
  256    p_to_s_graph(Edges, G1),
  257    graph_subtract(Graph, G1, NewGraph).
 graph_subtract(+Set1, +Set2, ?Difference)
Is based on ord_subtract
  263graph_subtract(Set1, [], Set1) :- !.
  264graph_subtract([], _, []).
  265graph_subtract([Head1-E1|Tail1], [Head2-E2|Tail2], Difference) :-
  266    compare(Order, Head1, Head2),
  267    graph_subtract(Order, Head1-E1, Tail1, Head2-E2, Tail2, Difference).
  268
  269graph_subtract(=, H-E1,     Tail1, _-E2,     Tail2, [H-E|Difference]) :-
  270    ord_subtract(E1,E2,E),
  271    graph_subtract(Tail1, Tail2, Difference).
  272graph_subtract(<, Head1, Tail1, Head2, Tail2, [Head1|Difference]) :-
  273    graph_subtract(Tail1, [Head2|Tail2], Difference).
  274graph_subtract(>, Head1, Tail1, _,     Tail2, Difference) :-
  275    graph_subtract([Head1|Tail1], Tail2, Difference).
 edges(+Graph, -Edges)
Unify Edges with all edges appearing in Graph. Example:
?- edges([1-[3,5],2-[4],3-[],4-[5],5-[]], L).
L = [1-3, 1-5, 2-4, 4-5]
  284edges(Graph, Edges) :-
  285    s_to_p_graph(Graph, Edges).
  286
  287p_to_s_graph(P_Graph, S_Graph) :-
  288    sort(P_Graph, EdgeSet),
  289    p_to_s_vertices(EdgeSet, VertexBag),
  290    sort(VertexBag, VertexSet),
  291    p_to_s_group(VertexSet, EdgeSet, S_Graph).
  292
  293
  294p_to_s_vertices([], []).
  295p_to_s_vertices([A-Z|Edges], [A,Z|Vertices]) :-
  296    p_to_s_vertices(Edges, Vertices).
  297
  298
  299p_to_s_group([], _, []).
  300p_to_s_group([Vertex|Vertices], EdgeSet, [Vertex-Neibs|G]) :-
  301    p_to_s_group(EdgeSet, Vertex, Neibs, RestEdges),
  302    p_to_s_group(Vertices, RestEdges, G).
  303
  304
  305p_to_s_group([V1-X|Edges], V2, [X|Neibs], RestEdges) :- V1 == V2,
  306    !,
  307    p_to_s_group(Edges, V2, Neibs, RestEdges).
  308p_to_s_group(Edges, _, [], Edges).
  309
  310
  311
  312s_to_p_graph([], []) :- !.
  313s_to_p_graph([Vertex-Neibs|G], P_Graph) :-
  314    s_to_p_graph(Neibs, Vertex, P_Graph, Rest_P_Graph),
  315    s_to_p_graph(G, Rest_P_Graph).
  316
  317
  318s_to_p_graph([], _, P_Graph, P_Graph) :- !.
  319s_to_p_graph([Neib|Neibs], Vertex, [Vertex-Neib|P], Rest_P) :-
  320    s_to_p_graph(Neibs, Vertex, P, Rest_P).
 transitive_closure(+Graph, -Closure)
Generate the graph Closure as the transitive closure of Graph. Example:
?- transitive_closure([1-[2,3],2-[4,5],4-[6]],L).
L = [1-[2,3,4,5,6], 2-[4,5,6], 4-[6]]
  332transitive_closure(Graph, Closure) :-
  333    warshall(Graph, Graph, Closure).
  334
  335warshall([], Closure, Closure) :- !.
  336warshall([V-_|G], E, Closure) :-
  337    memberchk(V-Y, E),      %  Y := E(v)
  338    warshall(E, V, Y, NewE),
  339    warshall(G, NewE, Closure).
  340
  341
  342warshall([X-Neibs|G], V, Y, [X-NewNeibs|NewG]) :-
  343    memberchk(V, Neibs),
  344    !,
  345    ord_union(Neibs, Y, NewNeibs),
  346    warshall(G, V, Y, NewG).
  347warshall([X-Neibs|G], V, Y, [X-Neibs|NewG]) :-
  348    !,
  349    warshall(G, V, Y, NewG).
  350warshall([], _, _, []).
 transpose_ugraph(Graph, NewGraph) is det
Unify NewGraph with a new graph obtained from Graph by replacing all edges of the form V1-V2 by edges of the form V2-V1. The cost is O(|V|*log(|V|)). Notice that an undirected graph is its own transpose. Example:
?- transpose([1-[3,5],2-[4],3-[],4-[5],
              5-[],6-[],7-[],8-[]], NL).
NL = [1-[],2-[],3-[1],4-[2],5-[1,4],6-[],7-[],8-[]]
Compatibility
- This predicate used to be known as transpose/2. Following SICStus 4, we reserve transpose/2 for matrix transposition and renamed ugraph transposition to transpose_ugraph/2.
  370transpose_ugraph(Graph, NewGraph) :-
  371    edges(Graph, Edges),
  372    vertices(Graph, Vertices),
  373    flip_edges(Edges, TransposedEdges),
  374    vertices_edges_to_ugraph(Vertices, TransposedEdges, NewGraph).
  375
  376flip_edges([], []).
  377flip_edges([Key-Val|Pairs], [Val-Key|Flipped]) :-
  378    flip_edges(Pairs, Flipped).
 compose(+LeftGraph, +RightGraph, -NewGraph)
Compose NewGraph by connecting the drains of LeftGraph to the sources of RightGraph. Example:
?- compose([1-[2],2-[3]],[2-[4],3-[1,2,4]],L).
L = [1-[4], 2-[1,2,4], 3-[]]
  388compose(G1, G2, Composition) :-
  389    vertices(G1, V1),
  390    vertices(G2, V2),
  391    ord_union(V1, V2, V),
  392    compose(V, G1, G2, Composition).
  393
  394compose([], _, _, []) :- !.
  395compose([Vertex|Vertices], [Vertex-Neibs|G1], G2,
  396        [Vertex-Comp|Composition]) :-
  397    !,
  398    compose1(Neibs, G2, [], Comp),
  399    compose(Vertices, G1, G2, Composition).
  400compose([Vertex|Vertices], G1, G2, [Vertex-[]|Composition]) :-
  401    compose(Vertices, G1, G2, Composition).
  402
  403
  404compose1([V1|Vs1], [V2-N2|G2], SoFar, Comp) :-
  405    compare(Rel, V1, V2),
  406    !,
  407    compose1(Rel, V1, Vs1, V2, N2, G2, SoFar, Comp).
  408compose1(_, _, Comp, Comp).
  409
  410
  411compose1(<, _, Vs1, V2, N2, G2, SoFar, Comp) :-
  412    !,
  413    compose1(Vs1, [V2-N2|G2], SoFar, Comp).
  414compose1(>, V1, Vs1, _, _, G2, SoFar, Comp) :-
  415    !,
  416    compose1([V1|Vs1], G2, SoFar, Comp).
  417compose1(=, V1, Vs1, V1, N2, G2, SoFar, Comp) :-
  418    ord_union(N2, SoFar, Next),
  419    compose1(Vs1, G2, Next, Comp).
 top_sort(+Graph, -Sorted) is semidet
 top_sort(+Graph, -Sorted, ?Tail) is semidet
Sorted is a topological sorted list of nodes in Graph. A toplogical sort is possible if the graph is connected and acyclic. In the example we show how topological sorting works for a linear graph:
?- top_sort([1-[2], 2-[3], 3-[]], L).
L = [1, 2, 3]

The predicate top_sort/3 is a difference list version of top_sort/2.

  437top_sort(Graph, Sorted) :-
  438    vertices_and_zeros(Graph, Vertices, Counts0),
  439    count_edges(Graph, Vertices, Counts0, Counts1),
  440    select_zeros(Counts1, Vertices, Zeros),
  441    top_sort(Zeros, Sorted, Graph, Vertices, Counts1).
  442
  443top_sort(Graph, Sorted0, Sorted) :-
  444    vertices_and_zeros(Graph, Vertices, Counts0),
  445    count_edges(Graph, Vertices, Counts0, Counts1),
  446    select_zeros(Counts1, Vertices, Zeros),
  447    top_sort(Zeros, Sorted, Sorted0, Graph, Vertices, Counts1).
  448
  449
  450vertices_and_zeros([], [], []) :- !.
  451vertices_and_zeros([Vertex-_|Graph], [Vertex|Vertices], [0|Zeros]) :-
  452    vertices_and_zeros(Graph, Vertices, Zeros).
  453
  454
  455count_edges([], _, Counts, Counts) :- !.
  456count_edges([_-Neibs|Graph], Vertices, Counts0, Counts2) :-
  457    incr_list(Neibs, Vertices, Counts0, Counts1),
  458    count_edges(Graph, Vertices, Counts1, Counts2).
  459
  460
  461incr_list([], _, Counts, Counts) :- !.
  462incr_list([V1|Neibs], [V2|Vertices], [M|Counts0], [N|Counts1]) :-
  463    V1 == V2,
  464    !,
  465    N is M+1,
  466    incr_list(Neibs, Vertices, Counts0, Counts1).
  467incr_list(Neibs, [_|Vertices], [N|Counts0], [N|Counts1]) :-
  468    incr_list(Neibs, Vertices, Counts0, Counts1).
  469
  470
  471select_zeros([], [], []) :- !.
  472select_zeros([0|Counts], [Vertex|Vertices], [Vertex|Zeros]) :-
  473    !,
  474    select_zeros(Counts, Vertices, Zeros).
  475select_zeros([_|Counts], [_|Vertices], Zeros) :-
  476    select_zeros(Counts, Vertices, Zeros).
  477
  478
  479
  480top_sort([], [], Graph, _, Counts) :-
  481    !,
  482    vertices_and_zeros(Graph, _, Counts).
  483top_sort([Zero|Zeros], [Zero|Sorted], Graph, Vertices, Counts1) :-
  484    graph_memberchk(Zero-Neibs, Graph),
  485    decr_list(Neibs, Vertices, Counts1, Counts2, Zeros, NewZeros),
  486    top_sort(NewZeros, Sorted, Graph, Vertices, Counts2).
  487
  488top_sort([], Sorted0, Sorted0, Graph, _, Counts) :-
  489    !,
  490    vertices_and_zeros(Graph, _, Counts).
  491top_sort([Zero|Zeros], [Zero|Sorted], Sorted0, Graph, Vertices, Counts1) :-
  492    graph_memberchk(Zero-Neibs, Graph),
  493    decr_list(Neibs, Vertices, Counts1, Counts2, Zeros, NewZeros),
  494    top_sort(NewZeros, Sorted, Sorted0, Graph, Vertices, Counts2).
  495
  496graph_memberchk(Element1-Edges, [Element2-Edges2|_]) :-
  497    Element1 == Element2,
  498    !,
  499    Edges = Edges2.
  500graph_memberchk(Element, [_|Rest]) :-
  501    graph_memberchk(Element, Rest).
  502
  503
  504decr_list([], _, Counts, Counts, Zeros, Zeros) :- !.
  505decr_list([V1|Neibs], [V2|Vertices], [1|Counts1], [0|Counts2], Zi, Zo) :-
  506    V1 == V2,
  507    !,
  508    decr_list(Neibs, Vertices, Counts1, Counts2, [V2|Zi], Zo).
  509decr_list([V1|Neibs], [V2|Vertices], [N|Counts1], [M|Counts2], Zi, Zo) :-
  510    V1 == V2,
  511    !,
  512    M is N-1,
  513    decr_list(Neibs, Vertices, Counts1, Counts2, Zi, Zo).
  514decr_list(Neibs, [_|Vertices], [N|Counts1], [N|Counts2], Zi, Zo) :-
  515    decr_list(Neibs, Vertices, Counts1, Counts2, Zi, Zo).
 neighbors(+Vertex, +Graph, -Neigbours) is det
 neighbours(+Vertex, +Graph, -Neigbours) is det
Neigbours is a sorted list of the neighbours of Vertex in Graph. Example:
?- neighbours(4,[1-[3,5],2-[4],3-[],
                 4-[1,2,7,5],5-[],6-[],7-[],8-[]], NL).
NL = [1,2,7,5]
  530neighbors(Vertex, Graph, Neig) :-
  531    neighbours(Vertex, Graph, Neig).
  532
  533neighbours(V,[V0-Neig|_],Neig) :-
  534    V == V0,
  535    !.
  536neighbours(V,[_|G],Neig) :-
  537    neighbours(V,G,Neig).
 connect_ugraph(+UGraphIn, -Start, -UGraphOut) is det
Adds Start as an additional vertex that is connected to all vertices in UGraphIn. This can be used to create an topological sort for a not connected graph. Start is before any vertex in UGraphIn in the standard order of terms. No vertex in UGraphIn can be a variable.

Can be used to order a not-connected graph as follows:

top_sort_unconnected(Graph, Vertices) :-
    (   top_sort(Graph, Vertices)
    ->  true
    ;   connect_ugraph(Graph, Start, Connected),
        top_sort(Connected, Ordered0),
        Ordered0 = [Start|Vertices]
    ).
  559connect_ugraph([], 0, []) :- !.
  560connect_ugraph(Graph, Start, [Start-Vertices|Graph]) :-
  561    vertices(Graph, Vertices),
  562    Vertices = [First|_],
  563    before(First, Start).
 before(+Term, -Before) is det
Unify Before to a term that comes before Term in the standard order of terms.
Errors
- instantiation_error if Term is unbound.
  572before(X, _) :-
  573    var(X),
  574    !,
  575    instantiation_error(X).
  576before(Number, Start) :-
  577    number(Number),
  578    !,
  579    Start is Number - 1.
  580before(_, 0).
 complement(+UGraphIn, -UGraphOut)
UGraphOut is a ugraph with an edge between all vertices that are not connected in UGraphIn and all edges from UGraphIn removed. Example:
?- complement([1-[3,5],2-[4],3-[],
               4-[1,2,7,5],5-[],6-[],7-[],8-[]], NL).
NL = [1-[2,4,6,7,8],2-[1,3,5,6,7,8],3-[1,2,4,5,6,7,8],
      4-[3,5,6,8],5-[1,2,3,4,6,7,8],6-[1,2,3,4,5,7,8],
      7-[1,2,3,4,5,6,8],8-[1,2,3,4,5,6,7]]
To be done
- Simple two-step algorithm. You could be smarter, I suppose.
  599complement(G, NG) :-
  600    vertices(G,Vs),
  601    complement(G,Vs,NG).
  602
  603complement([], _, []).
  604complement([V-Ns|G], Vs, [V-INs|NG]) :-
  605    ord_add_element(Ns,V,Ns1),
  606    ord_subtract(Vs,Ns1,INs),
  607    complement(G, Vs, NG).
 reachable(+Vertex, +UGraph, -Vertices)
True when Vertices is an ordered set of vertices reachable in UGraph, including Vertex. Example:
?- reachable(1,[1-[3,5],2-[4],3-[],4-[5],5-[]],V).
V = [1, 3, 5]
  617reachable(N, G, Rs) :-
  618    reachable([N], G, [N], Rs).
  619
  620reachable([], _, Rs, Rs).
  621reachable([N|Ns], G, Rs0, RsF) :-
  622    neighbours(N, G, Nei),
  623    ord_union(Rs0, Nei, Rs1, D),
  624    append(Ns, D, Nsi),
  625    reachable(Nsi, G, Rs1, RsF)