Frontier Software

Iterative Deepening

By Robert Laing

A snag we hit in puzzle solving is the graph isn’t handily prestored in a database for route finding using transitive closures with infinite loop protection thanks to cycles with tabling. We have to turn to what’s sometimes called generative recursion to dynamically build our graph as we explore it. For this, we’ll return to the techniques introduced in BreadthDepthFirst.

We’ll be using iterative deepening depth-first search which gets depth first to mimic breadth first by doing it repeatedly, lengthening its depth-limit one step at a time. The reason is unbounded depth first instead of finding the shortest route, finds the leftmost route. Breadth first does find the shortest route, but even the cheap RAM available on modern computers is often insufficient for it to complete this task.

As in route finding, we want a rule route(Start, End, Path). We can’t simply call a transitive closure in examples such as buttons and lights and wolf, goat, cabbage because initially all we have is the starting node and rules to expand a node. To build a simple skeleton template to expand on later, we’ll be using arc(Parent, Child) and a slightly modified version of the getchildren rule used in BreadthDepthFirst. The difference is that to trace a path from start to goal, we need to remember the pairs. I’m keeping to the tradition of using an unlabeled graph and working with nodes, but for most practical purposes, we actually want a string of labels as we’ll get to in puzzle solving`.

We also need to remember the depth of each arc.

getchildren(Depth, Parent, Children) :-
    findall(arc(Depth, Parent, Child), arc(Parent, Child), Unsorted),
    sort(Unsorted, Children).

Iterative deepening allows us to memoize child nodes generated in past iterations, and we only need to append new nodes to the frontier list when we reach an unexplored level. The basic template used in BottomUpRecursion gets a third rule to simply shunt nodes from the frontier to the visited list when we are not at the Limit depth.

depthfirst(_, [], RGraph, Graph) :-
    reverse(RGraph, Graph).

depthfirst(Limit, [arc(Depth, Parent, Child)|Frontier], Visited, Acc) :-
    \+succ(Depth, Limit),
    depthfirst(Limit, Frontier, [arc(Depth, Parent, Child)|Visited], Acc).

depthfirst(Limit, [arc(Depth, Parent, Child)|Frontier], Visited, Acc) :-
    succ(Depth, Limit),
    getchildren(Limit, Child, GrandChildren),
    append(GrandChildren, Frontier, NewFrontier),
    depthfirst(Limit, NewFrontier, [arc(Depth, Parent, Child)|Visited], Acc).

Next we have the recursive iterative deepening rule which keeps increasing the depth limit and feeding the visited list of the previous call as the frontier list of the current call until the end goal is found. This is a first attempt which runs into problems with cycles and unreachable goals (eg route(a, x, Path)) would hang the computer.

iterative_deepening(Limit, End, Graph, Graph) :-
    memberchk(arc(Limit, _, End), Graph).

iterative_deepening(Depth, End, GraphIn, Acc) :-
    \+memberchk(arc(Depth, _, End), GraphIn),
    succ(Depth, Limit),
    depthfirst(Limit, GraphIn, [], GraphOut),
    iterative_deepening(Limit, End, GraphOut, Acc).

route(Start, End, Path) will need to use the list of arcs produced by iterative_deepening to create a list of nodes from start to end. As explained in PuzzleSolving, for nearly all practical purposes we want a list of the labels between the nodes (the historical meaning of the jargon term string), not a list of the nodes themselves. But lets stick to this computer science textbook tradition for now.

getpath(Start, Graph, [Node|Path], [Start, Node|Path]) :-
    member(arc(1, Start, Node), Graph).

getpath(Start, Graph, [Child|Path], Acc) :-
    member(arc(_, Parent, Child), Graph),
    getpath(Start, Graph, [Parent, Child|Path], Acc).

route(Start, End, Path) :-
    getchildren(1, Start, GraphIn),
    iterative_deepening(1, End, GraphIn, GraphOut),
    getpath(Start, GraphOut, [End], Path).

Testing the above on this example with route(a, t, Path) we’ll get the desired answers of Path = [a, b, f, m, t] and Path = [a, c, h, n, t].

tree_tnocycles.svg

Similarly, route(a, s, Path) (a worst case scenario at the bottom right) promptly gives us Path = [a, d, j, s].

Snags with the code so far is there’s not protection from {{{{route(a, x, Path)}}} hanging the computer. This can be fixed by adding a statement to iterative_deepening:

iterative_deepening(Limit, End, Graph, Graph) :-
    memberchk(arc(Limit, _, End), Graph).

iterative_deepening(Depth, End, GraphIn, Acc) :-
    \+memberchk(arc(Depth, _, End), GraphIn),
    succ(Depth, Limit),
    depthfirst(Limit, GraphIn, [], GraphOut),
    GraphOut \== GraphIn,
    iterative_deepening(Limit, End, GraphOut, Acc).

Adding the guard GraphOut \== GraphIn halts the recursion when depthfirst isn’t finding anything new.

The full code for the above example looks like this. An advantage of iterative deepening is that besides memoizing old search results, we can prune known ‘‘cul-de-sacs’’ out of the graph which we’ll get to next in PrunedIterativeDeepening.

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(m, f).
%arc(m, m).
arc(m, t).
arc(n, t).

getchildren(Depth, Parent, Children) :-
    findall(arc(Depth, Parent, Child), arc(Parent, Child), Unsorted),
    sort(Unsorted, Children).

depthfirst(_, [], RGraph, Graph) :-
    reverse(RGraph, Graph).

depthfirst(Limit, [arc(Depth, Parent, Child)|Frontier], Visited, Acc) :-
    \+succ(Depth, Limit),
    depthfirst(Limit, Frontier, [arc(Depth, Parent, Child)|Visited], Acc).

depthfirst(Limit, [arc(Depth, Parent, Child)|Frontier], Visited, Acc) :-
    succ(Depth, Limit),
    getchildren(Limit, Child, GrandChildren),
    append(GrandChildren, Frontier, NewFrontier),
    depthfirst(Limit, NewFrontier, [arc(Depth, Parent, Child)|Visited], Acc).

% iterative_deepening(_, _, [], []).

iterative_deepening(Limit, End, Graph, Graph) :-
    memberchk(arc(Limit, _, End), Graph).

iterative_deepening(Depth, End, GraphIn, Acc) :-
    \+memberchk(arc(Depth, _, End), GraphIn),
    succ(Depth, Limit),
    depthfirst(Limit, GraphIn, [], GraphOut),
    GraphOut \== GraphIn,
    iterative_deepening(Limit, End, GraphOut, Acc).

getpath(Start, Graph, [Node|Path], [Start, Node|Path]) :-
    member(arc(1, Start, Node), Graph).

getpath(Start, Graph, [Child|Path], Acc) :-
    member(arc(_, Parent, Child), Graph),
    getpath(Start, Graph, [Parent, Child|Path], Acc).

route(Start, End, Path) :-
    getchildren(1, Start, GraphIn),
    iterative_deepening(1, End, GraphIn, GraphOut),
    getpath(Start, GraphOut, [End], Path).