Frontier Software

Cycles With Tabling

By adding arc(k, e). we alter the previous example in Transitive Closures to this:

tree_cycle.svg

Unless guarded against, this will cause tc(a, X). to never escape looping between k and e. Thanks to a relatively recent addition to SWI Prolog Tabled execution, all that’s needed to avoid this is adding one line of code prolog:- table tc/2. to that previously shown in TransitiveClosures.

:- table tc/2.

arc(a, b).
arc(a, c).
arc(a, d).
arc(b, e).
arc(b, f).
arc(c, g).
arc(c, h).
arc(c, i).
arc(d, j).
arc(e, k).
arc(f, l).
arc(f, m).
arc(h, n).
arc(i, o).
arc(i, p).
arc(j, q).
arc(j, r).
arc(j, s).
arc(k, e).
arc(m, t).

tc(X, Y) :-
    arc(X, Y).

tc(X, Z) :-
    arc(X, Y),
    tc(Y, Z).

Tabling changes the order of traversal returned by tc(a, X) to this:

X = h
X = e
X = q
X = j
X = l
X = f
X = o
X = c
X = i
X = r
X = b
X = t
X = g
X = n
X = s
X = d
X = m
X = k
X = p

Those familiar with transitive closures, but not Prolog, tend to wonder why we don’t just have our arc facts and one rule:

arc(X, Z) :-
  arc(X, Y),
  arc(Y, Z).

Tabling allows us to rewrite our code as follows to dispense with tc rules:

:- table arc/2.

arc(a, b).
arc(a, c).
arc(a, d).
arc(b, e).
arc(b, f).
arc(c, g).
arc(c, h).
arc(c, i).
arc(d, j).
arc(e, k).
arc(f, l).
arc(f, m).
arc(h, n).
arc(i, o).
arc(i, p).
arc(j, q).
arc(j, r).
arc(j, s).
arc(k, e).
arc(m, t).

arc(X, Z) :-
    arc(X, Y),
    arc(Y, Z).

Transitive closures with tabling are great assuming we aren’t dealing with dynamic data, as for instance in Puzzle Solving when the graph has to be built from a starting point with provided rules, so arcs can’t simply be looked up for PathFinding. In BreadthDepthFirst we’ll look at how to listify graphs and then traverse them breadth or depth first.