Week 6: Notes

the cut

Normally Prolog generates all possible solutions to any query. In some situations, however, we may only want a single solution. The cut operator ! causes Prolog to commit to all choices that it has already made in the current query or predicate. After a cut, Prolog will not backtrack to look for more possible solutions. For example:

?- member(X, [2, 4, 6, 8, 10]), X #> 5, !.
X = 6.

?- append(L, M, [a, b, c]), !.
L = [],
M = [a, b, c].

Here are some more examples:

?- (X = 3; X = 4, !; X = 5).
X = 3 ;
X = 4.

?- (Z = 1; Z = 2), (X = 3; X = 4, !; X = 5).
Z = 1,
X = 3 ;
Z = 1,
X = 4.

Prolog will, however, continue to explore choices that appear to the right of the cut:

?- (X = 3; X = 4, !; X = 5), (Y = 10; Y = 20).
X = 3,
Y = 10 ;
X = 3,
Y = 20 ;
X = 4,
Y = 10 ;
X = 4,
Y = 20.

If a predicate is written using multiple rules, then the cut will affect it just as if it were written as a single rule using the ';' operator. In other words, after a cut no further rules will be considered. For example:

foo(X) :- X = 3.
foo(X) :- X = 4, !.
foo(X) :- X = 5.

?- foo(X).
X = 3 ;
X = 4.

?-

the cut and logical purity

Almost all the Prolog features and predicates that we have seen until now are part of the pure logical core of the language. For example, dif(), member(), append(), select(), maplist(), foldl(), and new-style arithmetic are all logically pure.

As we've noted before, any program written only using these pure logical features has some nice properties:

The cut can be useful in various situations, however it is not logically pure. This means that a program that uses the cut, or features derived from the cut, will probably not have the properties above.

Let's look at a couple of examples. Consider this predicate:

kind(N, small) :- N #< 10.
kind(N, medium) :- N #>= 10, N #< 100.
kind(N, large) :- N #>= 100.

We might attempt to simplify it using the cut as follows:

kind2(N, small) :- N #< 10, !.
kind2(N, medium) :- N #< 100, !.
kind2(_, large).

With this change, any query of the form kind2(N, K) will still produce a correct value K if N is already instantiated and K is not:

?- kind2(50, K).
K = medium.

?- kind2(200, K).
K = large.

However, if N is uninstantiated then we may now receive answers that are incorrect:

?- kind2(N, large).
true.

The preceding answer claims that all N are big, but that is not true. Similarly, if K is already instantiated then we may also receive incorrect answers:

?- kind2(5, medium).
true.

Furthermore, the results of our query may now depend on the order in which we ask questions:

?- N = 50, K = medium, kind2(N, K).
N = 50,
K = medium.

?- kind2(N, K), N = 50, K = medium.
false.

As another example, suppose that we use the cut to write a version of member(X, L) that will succeed only once, even if X is in the list L multiple times:

mem1(X, [X | _]) :- !.
mem1(X, [_ | L]) :- mem1(X, L).

In the forward direction, it works as intended:

?- mem1(3, [2, 3, 3, 5, 4, 3]).
true.

?-

However in the reverse direction it now returns results that are incomplete:

?- mem1(3, L).
L = [3|_].

?-

As a result, once again we may get different results if we reorder goals in a query:

?- L = [2, 3, 4], mem1(3, L).
L = [2, 3, 4].

?- mem1(3, L), L = [2, 3, 4].
false.

In summary, the cut works well in a forward direction, i.e. at a moment when all variables are already instantiated. So, for example, it's reasonable to use a cut at the top level of a program that is searching for solutions in a state space, at a moment when a first solution is known and you don't want to search for more solutions. However, in situations where code may need to run multidirectionally, the cut is potentially dangerous and requires you to think about your program in a more procedural way.

negation

We may use the cut to implement negation. For example, let's write a predicate not_mem(X, L) that is true if X is not a member of L:

not_mem(X, L) :- member(X, L), !, false; true.

This predicate works as follows. If X is a member of L, then the predicate is false, and the cut prevents it from considering the other branch. Otherwise, the other branch runs and the predicate is true:

?- not_mem(3, [4, 5, 6]).
true.

?- not_mem(3, [4, 3, 6]).
false.

We may generalize this idea by writing a higher-order predicate 'not':

not(P) :- call(P), !, false; true.

?- not(member(3, [4, 5, 6])).
true.

In fact this predicate is built into Prolog, and has the name \+:

?- \+ member(3, [4, 5, 6]).
true.

Because Prolog's negation is defined using the cut, it will really only work in a forward direction. If you apply negation to a term in which all variables are already instantiated, it will behave as you expect. If variables are not instantiated, you may receive results that are unsound or incomplete. For example, consider this query:

?- \+ member(X, [2, 3, 4]).
false

This result is claiming that there are no values X which are not members of the list [2, 3, 4]. But the claim is false, since certainly such X do exist:

?- X = 10, \+ member(X, [2, 3, 4]).
X = 10.

As another example, suppose that we have the following predicates about restaurants:

good_food(ferdinand).
good_food(beseda).

expensive(beseda).

cheap(R) :- \+ expensive(R).

I'm looking for a restaurant that has good food and is inexpensive. This query lets me find one:

?- good_food(R), cheap(R).
R = ferdinand 

However if I ask the questions in the other order, the query fails:

?- cheap(R), good_food(R).
false

if/then/else

We may also use the cut to implement an if/then/else operation. For example, here is a predicate max() which computes the maximum Z of two values X and Y:

max(X, Y, Z) :- X #>= Y, !, Z = X; Z = Y.

?- max(4, 10, Z).
Z = 10.

?- max(7, 3, Z).
Z = 7.

If the goal 'X #>= Y' succeeds, then Z = X and the cut prevents Prolog from considering the other choice. If 'X #>= Y' fails, then Z = Y.

Prolog includes an arrow operator '->' which is defined using the cut, and lets us write this if/then/else choice with an (arguably) nicer syntax:

max(X, Y, Z) :- X #>= Y -> Z = X; Z = Y.

Once again, because this operator is defined using the cut, it will really only work in a forward direction, and may give us unsound or incomplete results in a reverse direction. For example:

?- max(4, X, 10).
false

This result is claiming that there are no values X such that the maximum of 4 and X is 10. Of course, that is wrong.

graphs

There are various possible ways to represent a graph in Prolog. Consider this acylic directed graph:

We could represent the graph using a series of facts:

edge(a, b).
edge(a, e).
edge(b, c).
...

This is sometimes called a temporal representation, because a query such as edge(a, V) will return a series of solutions over time.

Alternatively, we could use an adjacency list representation:

graph1(G) :- G =
    [ a -> [b, e], b -> [c, f], c -> [],
      d -> [], e -> [d, f], f -> [c],
      g -> [d, h], h -> [f] ].

This is sometimes called a spatial representation, since the graph is represented using a data structure.

We can implement graph search algorithms on either sort of graph. Let's choose the adjacency-list representation. We can begin by writing a predicate that can tell whether an edge exists in a graph:

% True if G has an edge from V to W.
edge(G, V, W) :- member(V -> L, G), member(W, L).

depth-first search

Here is a predicate path() that can find a path between two vertices in a graph in adjacency-list representation.

% path(G, V, W, P): True if P is a path from V to W in graph G.

path(_, V, V, [V]).

path(G, V, W, [V | P]) :- edge(G, V, X), path(G, X, W, P).

This predicate is somewhat similar to the ancestor() predicate that we wrote in the first lecture. However, unlike that predicate it builds a path P from the start to the goal.

Let's use path() to find all paths from a to c in the graph above:

?- graph1(_G), path(_G, a, c, P).
P = [a, b, c] ;
P = [a, b, f, c] ;
P = [a, e, f, c]

The predicate will even work multidirectionally:

?- graph1(_G), path(_G, V, W, [a, e, f, c]).
V = a,
W = c

?- graph1(_G), path(_G, a, V, P).
V = a,
P = [a] ;
V = b,
P = [a, b] ;
V = c,
P = [a, b, c] ;
V = f,
P = [a, b, f]
...

Our undirected graph above was acyclic. Let's now add an edge from c to a to make the graph cyclic:

graph2(G) :- G =
    [ a -> [b, e], b -> [c, f], c -> [a],
      d -> [], e -> [d, f], f -> [c],
      g -> [d, h], h -> [f] ].

Let's try using path() to search this graph:

?- graph2(_G), path(_G, a, c, P).
P = [a, b, c] ;
P = [a, b, c, a, b, c] ;
P = [a, b, c, a, b, c, a, b, c]
...

?- path(_G, a, e, P)
<hang>

We see it fails to find a path from a to e. That's because the search walks around the cycle a-b-c in an infinite loop, so it will never consider the edge from a to e.

So how can we search in a graph (or state space) that may contain cycles? Let's look at three possible ways do that.

iterative deepening

Iterative deepening performs a series of depth-first searches, each of which has a maximum depth. The first depth-first search has depth limit 1, the second has limit 2, and so on. Iterative deepening will always find a shortest path to a goal. It will work fine even if graphs with cycles. Although it will explore paths around cycles, that will not cause it to go into an infinite loop since its search depth is always limited.

We can easily implement iterative deepening in Prolog using a simple trick, as follows:

% iter_deep(G, V, W, P): True if P is a path from V to W in G.
% Return the shortest path first.
iter_deep(G, V, W, P) :- length(P, _), path(G, V, W, P).

Howe does this work? The goal length(P, _) will generate uninstantiated paths of increasing lengths:

?- length(P, _).
P = [] ;
P = [_] ;
P = [_, _] ;
P = [_, _, _] ;
P = [_, _, _, _]
...

So iter_deep will make a series of calls to path, each of which looks for a path of a particular length.

Unlike path(), this predicate returns the shortest path from b to f as its first result:

?- graph2(_G), iter_deep(_G, b, f, P).
P = [b, f] ;
P = [b, c, a, e, f]
<hang>

Iterative deepening is sometimes a useful technique. However, this implementation will never terminate, since it will keep searching for longer and longer paths. Of course, we can use the cut if we want only a single solution:

% iter_deep(G, V, W, P): True if P is the shortest path from V to W in G.
iter_deep(G, V, W, P) :- length(P, _), path(G, V, W, P), !.

However, the predicate will still fail to terminate if there is no path V to W.

Another problem is that this predicate considers all possible paths of length (N - 1) before any path of length N. And unfortunately there may be exponentially many of these.

avoiding self-intersecting paths

As another possible approach, we can amend our path() predicate so that it avoids selecting any vertex that is already in the path that it has built so far. It might look like this:

not_mem(X, L) :- maplist(dif(X), L).

% extend(G, P, Goal, R): true if P can be extended to reach Goal, producing path R

extend(_, P, Goal, R) :- P = [Goal | _], reverse(P, R).

extend(G, [X | P], Goal, R) :- dif(X, Goal), edge(G, X, Y), not_mem(Y, [X | P]),
    extend(G, [Y, X | P], Goal, R).

% path(G, V, W, Path): True if Path is a path from V to W in graph G.

path2(G, V, W, Path) :- extend(G, [V], W, Path).

path2() can search successfully even in a cyclic graph:

?- graph2(_G), path2(_G, a, c, P).
P = [a, b, c] ;
P = [a, b, f, c] ;
P = [a, e, f, c]

?- graph2(_G), path2(_G, a, e, P).
P = [a, e]

This is a step forward, but path2() still has a couple of limitations. First, since it is a depth-first search it is not guaranteed to find the shortest path between two vertices:

?- graph2(_G), path2(_G, b, f, P).
P = [b, c, a, e, f]

Also, this predicate may be inefficient. Unlike our implementation of depth-first search in Introduction to Algorithms last year, this predicate does not use a visited set shared across the entire search. Instead, it only avoids self-intersecting paths. In some graphs this may be much less efficient than using a visited set, since there may be (exponentially) many paths that do not intersect themselves, and path2() may explore many of these.

breadth-first search

A breadth-first search with a visited set will visit each state only once, so it may be far more efficient than iterative deepening or a search that only avoids self-intersecting paths.

A breadth-first search needs a queue. For the moment, we will use a naive queue representation, i.e. a list, where we enqueue by appending to the list. We also need a visited set. For the moment, we will also use a naive visited set representation, i.e. a list.

When the breadth-first search reaches the goal, we would like to return a list of all states on the path from the start to the goal. For this reason, each element on the queue will not be a simple vertex V. Instead, it will be a list of vertices on a path from the start to V, in reverse order. Because this list is in reverse order, we can efficiently extend it by prepending any neighbor of V to it.

Here's one possible solution:

prepend_to(L, X, [X | L]).

% bfs(+Graph, +Queue, +Visited, +Goal, -Path)
% True if Path is a path of states leading from the start to Goal.

bfs(_, [[Goal | P1] | _], _, Goal, Path) :- reverse([Goal | P1], Path).

bfs(Graph, [[V | P1] | Q], Visited, Goal, Path) :-
    member(V -> Neighbors, Graph),
    subtract(Neighbors, Visited, Neighbors1), append(Neighbors1, Visited, Visited2),
    maplist(prepend_to([V | P1]), Neighbors1, Neighbors2), append(Q, Neighbors2, Q2),
    bfs(Graph, Q2, Visited2, Goal, Path).

% top-level entry point
bfs(Graph, Start, Goal, Path) :- bfs(Graph, [[Start]], [Start], Goal, Path).

Of course, we could improve this predicate by using more efficient data structures for the queue and visited set. For the queue, we could use the front/back data structure that we saw last week. For a visited set, SWI-Prolog includes libraries 'assoc' and 'rbtree' that implement efficient dictionaries using balanced binary trees. We could use one of these data structures, representing a set as a dictionary from keys to any fixed value.