Previous Next Contents

7.2  First the Simple Cases

Let us set out first to define the data structure for an unlabelled graph. Essentially, the structure we are interested in is just a list of NodeName/Neighbors terms, where Neighbors is a list of node names. We refer to these terms as adjacency records. We choose as well to impose the additional condition that every node name appearing in a neighbors-list must have its own adjacency record somewhere in the graph structure.
graph(G):-
    forall_nodes(G,G).

forall_nodes([],_).
forall_nodes([_Nm/Nbrs|Rest],Graph):-
    for_all_neighbors(Nbrs,Graph),
    forall_nodes(Rest,Graph).

for_all_neighbors([],_).
for_all_neighbors([N1|Ns],Graph):-
    member(N1/_,Graph),
    for_all_neighbors(Ns,Graph).
Observe that for_all_nodes/2 will have the effect of verifying that every member of the graph is in the form of an adjacency record. Then for_all_neighbors/2 will make sure that every neighbor of the current node has an adjacency record.

The graph must appear twice as an argument. The first instance acts as a sort of agenda, which tells us which adjacency records remain to be checked. We do a recursion on this structure, so it shrinks as processing proceeds. The second argument position never changes. In effect the graph acts as a global variable which is carried around throughout the procedure, so that we can refer to it as needed.

We now consider a simple graph traversal predicate. Note that, for the first time, our data type definition is not a traversal predicate. It processes adjacency records in the order in which they are found in the graph data structure, and that order need have no relation whatsoever to the way in which graph nodes are connected to each other. It does visit every node in the graph, so in that sense it is a traversal, but the traversal visits nodes in an essentially random order.3

The traversal predicate we now examine is an example of depth-first search of a graph. We begin with the simplest case, a case where the graph is rooted (and so a fortiori connected as well) and acyclic. Note that a rooted acyclic graph can have only one root. Suppose it had two. Call them nodes i and j. Then, by definition of a root, j is reachable from i and likewise i is reachable from j. But then i is reachable from i, via j, and so there is a loop, which contradicts the assumption. We make the further simplifying assumption that the root is always the first record in the graph. The predicate df_traversal/2 takes a graph and returns a list of the nodes visited, in order.
df_traversal(Graph,[Root|Visited]):-
    Graph = [Root/Neighbors|_], % get the root's neighbors
    dft(Neighbors,Graph,Visited).

dft([],_,[]).
dft([N|RestNs],G,[N|Visited]):-
    member(N/Nbrs,G),
    dft(Nbrs,G,VisitedFromN),
    dft(RestNs,G,VisitedFromRest),
    append(VisitedFromN,VisitedFromRest,Visited).
Compare this with the equivalent code for a tree structure.
df_traversal(Tree,[Root|Visited]):-
    Tree = Root/Subtrees, % get the root's subtrees
    dft(Subtrees,Visited).

dft([],[]).
dft([N/Subs|RestNs],[N|Visited]):-
    dft(Subs,VisitedFromN),
    dft(RestNs,VisitedFromRest),
    append(VisitedFromN,VisitedFromRest,Visited).
The main difference is that with trees, when we pick a node it comes along with all of its subtrees. So the call to member/2 in dft/3 is not needed in dft/2, and as a consequence we do not need the extra argument.

This definition of depth first traversal works as advertised as long as the graph is rooted and acyclic. What do we do if we are given a graph which does not meet these conditions? Suppose first that we are given an unrooted graph. Then for any node x in the graph there is at least one node which cannot be reached from x. A fortiori, then, that node cannot be reached from x by a depth first traversal. The strategy to follow in this case is to start from some arbitrary node, visit all the nodes that are reachable from that node (taking them in depth first order); then pick some other arbitrary node from among those that we were not able to visit, and start again from there. We simply iterate this procedure until we have visited every node.

Now consider the problem of cyclic graphs. Assume we have a graph such as that in figure 7.3, on page X. The problem there is that, starting from a we might go on to node b, and then we might choose a again from b's adjacency record. Now the whole procedure repeats itself, and it can continue to do so as long as we like. Basically, cyclic graphs are bottomless, so doing a depth-first search is bound to get us in trouble! The strategy here is based on the following observation. Once we have visited node x, then, by the nature of a depth first search, we are certain to visit x's neighbors. So if at any point we encounter x again, we might as well just skip it. We know we've been that way before already and there is nothing new to find there. Loops are a special case of this situation. Given a finite graph, we cannot possibly get into an infinite traversal if we never visit any node twice.

It seems, then, that the strategies for solving both problems have an interesting symmetry. So it would appear that the same strategy would suffice for both cases. We consider first the problem of cycles.


Previous Next Contents