% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(ugraphs): Graph manipulation library} \label{sec:ugraphs} \begin{tags} \mtag{author}- R.A.O'Keefe \\- Vitor Santos Costa \\- Jan Wielemaker \tag{license} BSD-2 or Artistic 2.0 \end{tags} 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 \predref{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.\vspace{0.7cm} \begin{description} \predicate{vertices}{2}{+Graph, -Vertices} Unify \arg{Vertices} with all vertices appearing in \arg{Graph}. Example: \begin{code} ?- vertices([1-[3,5],2-[4],3-[],4-[5],5-[]], L). L = [1, 2, 3, 4, 5] \end{code} \predicate[det]{vertices_edges_to_ugraph}{3}{+Vertices, +Edges, -UGraph} Create a \arg{UGraph} from \arg{Vertices} and edges. Given a graph with a set of \arg{Vertices} and a set of \arg{Edges}, Graph must unify with the corresponding S-representation. Note that the vertices without edges will appear in \arg{Vertices} but not in \arg{Edges}. Moreover, it is sufficient for a vertice to appear in \arg{Edges}. \begin{code} ?- vertices_edges_to_ugraph([],[1-3,2-4,4-5,1-5], L). L = [1-[3,5], 2-[4], 3-[], 4-[5], 5-[]] \end{code} In this case all vertices are defined implicitly. The next example shows three unconnected vertices: \begin{code} ?- 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-[]] \end{code} \predicate{add_vertices}{3}{+Graph, +Vertices, -NewGraph} Unify \arg{NewGraph} with a new graph obtained by adding the list of \arg{Vertices} to \arg{Graph}. Example: \begin{code} ?- add_vertices([1-[3,5],2-[]], [0,1,2,9], NG). NG = [0-[], 1-[3,5], 2-[], 9-[]] \end{code} \predicate[det]{del_vertices}{3}{+Graph, +Vertices, -NewGraph} Unify \arg{NewGraph} with a new graph obtained by deleting the list of \arg{Vertices} and all the edges that start from or go to a vertex in \arg{Vertices} to the \arg{Graph}. Example: \begin{code} ?- 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-[]] \end{code} \begin{tags} \tag{Compatibility} Upto 5.6.48 the argument order was (+\arg{Vertices}, +\arg{Graph}, -\arg{NewGraph}). Both YAP and SWI-Prolog have changed the argument order for compatibility with recent SICStus as well as consistency with \predref{del_edges}{3}. \end{tags} \predicate{add_edges}{3}{+Graph, +Edges, -NewGraph} Unify \arg{NewGraph} with a new graph obtained by adding the list of \arg{Edges} to \arg{Graph}. Example: \begin{code} ?- 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-[]] \end{code} \predicate{ugraph_union}{3}{+Graph1, +Graph2, -NewGraph} \arg{NewGraph} is the union of \arg{Graph1} and \arg{Graph2}. Example: \begin{code} ?- ugraph_union([1-[2],2-[3]],[2-[4],3-[1,2,4]],L). L = [1-[2], 2-[3,4], 3-[1,2,4]] \end{code} \predicate{del_edges}{3}{+Graph, +Edges, -NewGraph} Unify \arg{NewGraph} with a new graph obtained by removing the list of \arg{Edges} from \arg{Graph}. Notice that no vertices are deleted. Example: \begin{code} ?- 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-[]] \end{code} \predicate{edges}{2}{+Graph, -Edges} Unify \arg{Edges} with all edges appearing in \arg{Graph}. Example: \begin{code} ?- edges([1-[3,5],2-[4],3-[],4-[5],5-[]], L). L = [1-3, 1-5, 2-4, 4-5] \end{code} \predicate{transitive_closure}{2}{+Graph, -Closure} Generate the graph \arg{Closure} as the transitive closure of \arg{Graph}. Example: \begin{code} ?- transitive_closure([1-[2,3],2-[4,5],4-[6]],L). L = [1-[2,3,4,5,6], 2-[4,5,6], 4-[6]] \end{code} \predicate[det]{transpose_ugraph}{2}{Graph, NewGraph} Unify \arg{NewGraph} with a new graph obtained from \arg{Graph} by replacing all edges of the form V1-V2 by edges of the form V2-V1. The cost is O(\Sbar{}V\Sbar{}*log(\Sbar{}V\Sbar{})). Notice that an undirected graph is its own transpose. Example: \begin{code} ?- 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-[]] \end{code} \begin{tags} \tag{Compatibility} This predicate used to be known as \predref{transpose}{2}. Following SICStus 4, we reserve \predref{transpose}{2} for matrix transposition and renamed ugraph transposition to \predref{transpose_ugraph}{2}. \end{tags} \predicate{compose}{3}{+LeftGraph, +RightGraph, -NewGraph} Compose \arg{NewGraph} by connecting the \textit{drains} of \arg{LeftGraph} to the \textit{sources} of \arg{RightGraph}. Example: \begin{code} ?- compose([1-[2],2-[3]],[2-[4],3-[1,2,4]],L). L = [1-[4], 2-[1,2,4], 3-[]] \end{code} \predicate[semidet]{ugraph_layers}{2}{Graph, -Layers} \nodescription \predicate[semidet]{top_sort}{2}{+Graph, -Sorted} Sort vertices topologically. \arg{Layers} is a list of lists of vertices where there are no edges from a layer to an earlier layer. The predicate \predref{top_sort}{2} flattens the layers using \predref{append}{2}. These predicates fail if \arg{Graph} is cyclic. If \arg{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. \begin{code} ?- top_sort([1-[2], 2-[3], 3-[]], L). L = [1, 2, 3] \end{code} \begin{tags} \mtag{Compatibility}- The original version of this library provided \predref{top_sort}{3} as a \textit{difference list} version of \predref{top_sort}{2}. We removed this because the argument order was non-standard. Fixing causes hard to debug compatibility issues while we expect \predref{top_sort}{3} was rarely used. A backward compatible \predref{top_sort}{3} can be defined as \begin{code} top_sort(Graph, Tail, Sorted) :- top_sort(Graph, Sorted0), append(Sorted0, Tail, Sorted). \end{code} The original version returned all vertices in a \textit{layer} in reverse order. The current one returns them in standard order of terms, i.e., each layer is an \textit{ordered set}. \\- \predref{ugraph_layers}{2} is a SWI-Prolog specific addition to this library. \end{tags} \predicate[det]{neighbors}{3}{+Vertex, +Graph, -Neigbours} \nodescription \predicate[det]{neighbours}{3}{+Vertex, +Graph, -Neigbours} \arg{Neigbours} is a sorted list of the neighbours of \arg{Vertex} in \arg{Graph}. Example: \begin{code} ?- neighbours(4,[1-[3,5],2-[4],3-[], 4-[1,2,7,5],5-[],6-[],7-[],8-[]], NL). NL = [1,2,7,5] \end{code} \predicate[det]{connect_ugraph}{3}{+UGraphIn, -Start, -UGraphOut} Adds \arg{Start} as an additional vertex that is connected to all vertices in \arg{UGraphIn}. This can be used to create an topological sort for a not connected graph. \arg{Start} is before any vertex in \arg{UGraphIn} in the standard order of terms. No vertex in \arg{UGraphIn} can be a variable. Can be used to order a not-connected graph as follows: \begin{code} top_sort_unconnected(Graph, Vertices) :- ( top_sort(Graph, Vertices) -> true ; connect_ugraph(Graph, Start, Connected), top_sort(Connected, Ordered0), Ordered0 = [Start|Vertices] ). \end{code} \predicate{complement}{2}{+UGraphIn, -UGraphOut} \arg{UGraphOut} is a ugraph with an edge between all vertices that are \textit{not} connected in \arg{UGraphIn} and all edges from \arg{UGraphIn} removed. Example: \begin{code} ?- 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]] \end{code} \begin{tags} \tag{To be done} Simple two-step algorithm. You could be smarter, I suppose. \end{tags} \predicate{reachable}{3}{+Vertex, +UGraph, -Vertices} True when \arg{Vertices} is an ordered set of vertices reachable in \arg{UGraph}, including \arg{Vertex}. Example: \begin{code} ?- reachable(1,[1-[3,5],2-[4],3-[],4-[5],5-[]],V). V = [1, 3, 5] \end{code} \end{description}