
 ugraphs.pl -- Graph manipulation library
ugraphs.pl -- Graph manipulation libraryThe 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.
 vertices(+Graph, -Vertices)
 vertices(+Graph, -Vertices)?- vertices([1-[3,5],2-[4],3-[],4-[5],5-[]], L). L = [1, 2, 3, 4, 5]
 vertices_edges_to_ugraph(+Vertices:list, +Edges:pairs, -UGraph) is det
 vertices_edges_to_ugraph(+Vertices:list, +Edges:pairs, -UGraph) is detVertice-[]. The set
of vertices in UGraph is the union of Vertices and all vertices that
appear in the Edges pairs.
?- 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([1,2,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-[]]
 add_vertices(+Graph, +Vertices, -NewGraph)
 add_vertices(+Graph, +Vertices, -NewGraph)?- add_vertices([1-[3,5],2-[]], [0,1,2,9], NG). NG = [0-[], 1-[3,5], 2-[], 9-[]]
 del_vertices(+Graph, +Vertices, -NewGraph) is det
 del_vertices(+Graph, +Vertices, -NewGraph) is det
?- 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-[]]
 add_edges(+Graph, +Edges, -NewGraph)
 add_edges(+Graph, +Edges, -NewGraph)
?- 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-[]]
 ugraph_union(+Graph1, +Graph2, -NewGraph)
 ugraph_union(+Graph1, +Graph2, -NewGraph)?- ugraph_union([1-[2],2-[3]],[2-[4],3-[1,2,4]],L). L = [1-[2], 2-[3,4], 3-[1,2,4]]
 del_edges(+Graph, +Edges, -NewGraph)
 del_edges(+Graph, +Edges, -NewGraph)
?- 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-[]]
 edges(+Graph, -Edges)
 edges(+Graph, -Edges)?- edges([1-[3,5],2-[4],3-[],4-[5],5-[]], L). L = [1-3, 1-5, 2-4, 4-5]
 transitive_closure(+Graph, -Closure)
 transitive_closure(+Graph, -Closure)?- transitive_closure([1-[2,3],2-[4,5],4-[6]],L). L = [1-[2,3,4,5,6], 2-[4,5,6], 4-[6]]
 transpose_ugraph(Graph, NewGraph) is det
 transpose_ugraph(Graph, NewGraph) is det
?- 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-[]]
 compose(+LeftGraph, +RightGraph, -NewGraph)
 compose(+LeftGraph, +RightGraph, -NewGraph)?- compose([1-[2],2-[3]],[2-[4],3-[1,2,4]],L). L = [1-[4], 2-[1,2,4], 3-[]]
 ugraph_layers(Graph, -Layers) is semidet
 ugraph_layers(Graph, -Layers) is semidet top_sort(+Graph, -Sorted) is semidet
 top_sort(+Graph, -Sorted) is semidetThese predicates fail if Graph is cyclic. If Graph is not connected, the sub-graphs are individually sorted, where the root of each subgraph is in the first layer, the nodes connected to the roots in the second, etc.
?- top_sort([1-[2], 2-[3], 3-[]], L). L = [1, 2, 3]
 neighbors(+Vertex, +Graph, -Neigbours) is det
 neighbors(+Vertex, +Graph, -Neigbours) is det neighbours(+Vertex, +Graph, -Neigbours) is det
 neighbours(+Vertex, +Graph, -Neigbours) is det
?- neighbours(4,[1-[3,5],2-[4],3-[],
                 4-[1,2,7,5],5-[],6-[],7-[],8-[]], NL).
NL = [1,2,7,5]
 connect_ugraph(+UGraphIn, -Start, -UGraphOut) is det
 connect_ugraph(+UGraphIn, -Start, -UGraphOut) is detCan 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]
    ).
 complement(+UGraphIn, -UGraphOut)
 complement(+UGraphIn, -UGraphOut)
?- 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]]
 reachable(+Vertex, +UGraph, -Vertices)
 reachable(+Vertex, +UGraph, -Vertices)?- reachable(1,[1-[3,5],2-[4],3-[],4-[5],5-[]],V). V = [1, 3, 5]
The following predicates are exported, but not or incorrectly documented.
 top_sort(Arg1, Arg2)
 top_sort(Arg1, Arg2) neighbours(Arg1, Arg2, Arg3)
 neighbours(Arg1, Arg2, Arg3)