CHAPTER 6    Repetition and Recursion

 

Much of the usefulness of computers comes from the fact that they are good at doing the same thing over and over again. Prolog can express repetition both in its procedures and in its data structures. The idea of a repetitive data structure may sound strange, but Prolog allows you to create data structures whose ultimate size is not known at the time you create them. In this chapter, we discuss repetitive processes first (as loops and recursive procedures), then cover recursive data structures.

Repetitive Processes

Pascal, BASIC, or C programmers who start using Visual Prolog are often dismayed to find that the language has no FOR, WHILE, or REPEAT statements. There is no direct way to express iteration. Prolog allows only two kinds of repetition--backtracking, in which it searches for multiple solutions in a single query, and recursion, in which a procedure calls itself.

As it turns out, this lack doesn't restrict the power of the Prolog language. In fact, Visual Prolog recognizes a special case of recursion--called tail recursion --and compiles it into an iterative loop in machine language. This means that although the program logic is expressed recursively, the compiled code is as efficient as it would be in Pascal or BASIC.

In this section, we explore the art of writing repetitive processes in Prolog. As you'll see, recursion is--in most cases--clearer, more logical, and less error-prone than the loops that conventional languages use. Before delving into recursion, however, take another look at backtracking.

1. Backtracking Revisited

When a procedure backtracks, it looks for another solution to a goal that has already been satisfied. It does this by retreating to the most recent subgoal that has an untried alternative, using that alternative, then moving forward again. You can exploit backtracking as a way to perform repetitive processes.

Example

Program ch06e01.pro demonstrates how to use backtracking to perform repetitive processes--it prints all solutions to a query.

/* Program ch06e01.pro */

The predicate country simply lists the names of various countries, so that a goal such as

    country(X)

has multiple solutions. The predicate print_countries then prints out all of these solutions. It is defined as follows:

    print_countries :-
        country(X), write(X), nl, fail.
    print_countries.

The first clause says:

"To print countries, find a solution to country(X), then write X and start a new line, then fail."

In this case, "fail" means:

"assume that a solution to the original goal has not been reached, so back up and look for an alternative."

The built-in predicate fail always fails, but you could equally well force backtracking by using any other goal that would always fail, such as 5=2+2 or country(shangri_la).

The first time through, X is bound to england, which is printed. Then, when it hits fail, the computer backs up. There are no alternative ways to satisfy nl or write(X), so the computer looks for a different solution to country(X).

The last time country(X) was executed, it bound a value to the previously free variable X. So, before retrying this step, the computer unbinds X (frees it). Then it can look for an alternative solution for country(X) and bind X to a different value. If it succeeds, processing goes forward again and the name of another country is printed.

Eventually, the first clause runs out of alternatives. The only hope then is to try another clause for the same predicate. Sure enough, execution falls through to the second clause, which succeeds without doing anything further. In this way the goal print_countries terminates with success. Its complete output is

    england
    france
    germany
    denmark
    yes

If the second clause were not there, the print_countries goal would terminate with failure, and the final message would be no. Apart from that, the output would be the same.

Exercise

Modify ch06e01.pro so that

country has two arguments, name and population, and

only those countries with populations greater than 10 million (1e+7) are printed

Pre- and Post-Actions

Typically, a program that retrieves all the solutions to a goal will also want to do something beforehand and afterward. For instance, your program could

Print Some delightful places to live are....

Print all solutions to country(X).

Close by printing And maybe others.

Note that print_countries, as defined in the preceding example, already includes clauses that print all solutions to country(X) and close by (potentially) printing a final message.

The first clause for print_countries corresponds to step 2 and prints all the solutions; its second clause corresponds to step 3 and simply terminates the goal successfully (because the first clause always fails).

You could change the second clause in ch06e01.pro to

    print_countries :- write("And maybe others."), nl.

which would implement step 3 as specified.

What about step 1? There's no reason why print_countries should have only two clauses. It can have three, like this:

    print_countries :-
        write("Some delightful places to live are"),
        nl,
        fail.

    print_countries :-
        country(X),
        write(X),
        nl,
        fail.

    print_countries :-
        write("And maybe others."), nl.

The fail in the first clause is important--it ensures that, after executing the first clause, the computer backs up and tries the second clause. It's also important that the predicates write and nl do not generate alternatives; strictly speaking, the first clause tries all possible solutions before failing.

This three-clause structure is more of a trick than an established programming technique. A more fastidious programmer might try to do things this way:

    print_countries_with_captions :-
        write("Some delightful places to live are"),
        nl,
        print_countries,
        write("And maybe others."),
        nl.

    print_countries :-
        country(X),
        write(X),
        nl,
        fail.

There's nothing essentially wrong here, but this hypothetical fastidious programmer has made a mistake.

Exercise

Don't look ahead--figure out what's wrong with this program, and fix it!

You're right--the problem is that, as written in the latest example, print_countries will always fail, and print_countries_with_captions will never get to execute any of the subgoals that follow it. As a result, And maybe others. will never be printed.

To fix this, all you need to do is restore the original second clause for print_countries.

    print_countries.

to its original position. If you want the goal print_countries_with_captions to succeed, it must have at least one clause that does not contain fail.

2. Implementing Backtracking with Loops

Backtracking is a good way to get all the alternative solutions to a goal. But even if your goal doesn't have multiple solutions, you can still use backtracking to introduce repetition. Simply define the two-clause predicate

    repeat.
    repeat :- repeat.

This tricks Prolog's control structure into thinking it has an infinite number of different solutions. (Never mind the bollox how--after reading about tail recursion, you'll see how this works.) The purpose of repeat is to allow backtracking ad infinitum.

/* Program ch06e02.pro */

Program 2 shows how repeat works. The rule typewriter :- ... describes a procedure that accepts characters from the keyboard and prints them on the screen until the user presses the Enter (Return) key.

typewriter works as follows:

Execute repeat (which does nothing).

Then read a character into the variable C.

Then write C.

Then check if C is a carriage return.

If so, you're finished. If not, backtrack and look for alternatives. Neither write nor readchar generates alternative solutions, so backtrack all the way to repeat, which always has alternative solutions.

Now processing can go forward again, reading another character, printing it, and checking whether it's a carriage return.

Note, by the way, that C looses its binding when you backtrack past readchar(C), which bound it. This kind of unbinding is vital when you use backtracking to obtain alternative solutions to a goal, but it makes it hard to use backtracking for any other purpose. The reason is that, although a backtracking process can repeat operations any number of times, it can't "remember" anything from one repetition to the next. All variables loose their values when execution backtracks over the steps that established those values. There is no simple way for a repeat loop to keep a counter, a total, or any other record of its progress.

Exercises

Modify 2 so that, if the user types lower-case letters, they will be displayed as upper-case.

If you'd like to play with file I/O now, look up the appropriate built-in predicates and write a program that uses a repeat loop to copy a file character-by-character. (Refer to chapter 12.)

3. Recursive Procedures

The other way to express repetition is through recursion. A recursive procedure is one that calls itself. Recursive procedures have no trouble keeping records of their progress because counters, totals, and intermediate results can be passed from each iteration to the next as arguments.

The logic of recursion is easy to follow if you forget, for the moment, how computers work. (Prolog is so different from machine language that ignorance of computers is often an asset to the Prolog programmer.) Forget for the moment that the computer is trekking through memory addresses one by one, and imagine a machine that can follow recipes like this one:

    To find the factorial of a number N:
        If N is 1, the factorial is 1.
        Otherwise, find the factorial of N-1, then multiply it by N.

This recipe says: To find the factorial of 3, you must find the factorial of 2, and, to find the factorial of 2, you must find the factorial of 1. Fortunately, you can find the factorial of 1 without referring to any other factorials, so the repetition doesn't go on forever. When you have the factorial of 1, you multiply it by 2 to get the factorial of 2, then multiply that by 3 to get the factorial of 3, and you're done.

In Visual Prolog:

    factorial(1, 1) :- !.

    factorial(X, FactX) :-
        Y = X-1,
        factorial(Y, FactY),
        FactX = X*FactY.

A complete program is as follows:

/* Program ch06e03.pro */

What the Computer is Really Doing

But wait a minute, you say. How does the computer execute factorial while it's in the middle of executing factorial? If you call factorial with X=3, factorial will then call itself with X=2. Will X then have two values, or will the second value just wipe out the first, or what?

The answer is that the computer creates a new copy of factorial so that factorial can call itself as if it were a completely separate procedure. The executable code doesn't have to be duplicated, of course, but the arguments and internal variables do.

This information is stored in an area called a stack frame, which is created every time a rule is called. When the rule terminates, the stack is reset (unless it was a non-deterministic return) and execution continues in the stack frame for the parent.

Advantages of Recursion

Recursion has three main advantages:

It can express algorithms that can't conveniently be expressed any other way.

It is logically simpler than iteration.

It is used extensively in list processing.

Recursion is the natural way to describe any problem that contains within itself another problem of the same kind. Examples include tree search (a tree is made up of smaller trees) and recursive sorting (to sort a list, partition it, sort the parts, and then put them together).

Logically, recursive algorithms have the structure of an inductive mathematical proof. The preceding recursive factorial algorithm, in Program 3, describes an infinite number of different computations by means of just two clauses. This makes it easy to see that the clauses are correct. Further, the correctness of each clause can be judged independently of the other.

4. Tail Recursion Optimisation

Recursion has one big drawback: It eats memory. Whenever one procedure calls another, the calling procedure's state of execution must be saved so that it (the calling procedure) can resume where it left off after the called procedure has finished. This means that, if a procedure calls itself 100 times, 100 different states of execution must be stored at once. (The saved state of execution is known as a stack frame.) The maximum stack size on 16bit platforms, such as the IBM PC running DOS, is 64K, which will accommodate, at most, 3000 or 4000 stack frames. On 32bit platforms, the stack may theoretically grow to several GigaBytes; here, other system limitations will set in before the stack overflows. Anyway, what can be done to avoid using so much stack space?

It turns out that there's a special case in which a procedure can call itself without storing its state of execution. What if the calling procedure isn't going to resume after the called procedure finishes?

Suppose the calling procedure calls a procedure as its very last step. When the called procedure finishes, the calling procedure won't have anything else to do. This means the calling procedure doesn't need to save its state of execution, because that information isn't needed any more. As soon as the called procedure finishes, control can go directly to wherever it would have gone when the calling procedure finished.

For example, suppose that procedure A calls procedure B, and B calls procedure C as its very last step. When B calls C, B isn't going to do anything more. So, instead of storing the current state of execution for C under B, you can replace B's old stored state (which isn't needed any more) with C's current state, making appropriate changes in the stored information. When C finishes, it thinks it was called by A directly.

Now suppose that, instead of calling C, procedure B calls itself as its very last step. The recipe says that, when B calls B, the stack frame for the calling B should be replaced by a stack frame for the called B. This is a particularly simple operation; only the arguments need to be set to new values, and then processing jumps back to the beginning of the procedure. So, from a procedural point of view, what happens is very similar to updating the control variables in a loop.

This is called tail recursion optimization, or last-call optimization. Note that for technical reasons, recursive functions (predicates returning a value, described in chapter 11) cannot be tail recursive.

Making Tail Recursion Work

What does it mean to say that one procedure calls another "as its very last step?" In Prolog, this means that

The call is the very last subgoal of the clause.

There are no backtrack points earlier in the clause.

Here's an example that satisfies both conditions:

    count(N) :-
        
write(N), nl,
        NewN = N+1,
        count(NewN).

This procedure is tail recursive; it calls itself without allocating a new stack frame, so it never runs out of memory. As program 4 shows, if you give it the goal

    count(0)

count will print integers starting with 0 and never ending. Eventually, rounding errors will make it print inaccurate numbers, but it will never stop.

/* Program ch06e04.pro */

Exercise

Without looking ahead, modify 4 so that it is no longer tail recursive. How many iterations can it execute before running out of memory? Try it and see. (On 32bit platforms, this will take a considerable length of time, and the program will most likely not run out of stack space; it, or the system, will run out of memory in general. On 16bit platforms, the number of possible iterations is directly related to the stack size.

How Not to Do Tail Recursion

Now that you've seen how to do tail recursion right, program 5 shows you three ways to do it wrong.

If the recursive call isn't the very last step, the procedure isn't tail recursive. For example:

    badcount1(X) :-
        write('¡¬r',X),
        NewX = X+1,
        badcount1(NewX),
        nl.

Every time badcount1 calls itself, a stack frame has to be saved so that control can return to the calling procedure, which has yet to execute its final nl. So only a few thousand recursive calls can take place before the program runs out of memory.

Another way to lose tail recursion is to leave an alternative untried at the time the recursive call is made. Then a stack frame must be saved so that, if the recursive call fails, the calling procedure can go back and try the alternative. For example:

    badcount2(X) :-
        write('¡¬r',X),
        NewX = X+1,
        badcount2(NewX).
        badcount2(X) :-
        X < 0,

    write("X is negative.").

Here, the first clause of badcount2 calls itself before the second clause has been tried. Again, the program runs out of memory after a certain number of calls.

The untried alternative doesn't need to be a separate clause for the recursive procedure itself. It can equally well be an alternative in some other clause that it calls. For example:

    badcount3(X) :-
        write('¡¬r',X),
        NewX = X+1,
        check(NewX),
        
badcount3(NewX).
   
check(Z) :- Z >= 0.
   check(Z) :- Z < 0.

Suppose X is positive, as it normally is. Then, when badcount3 calls itself, the first clause of check has succeeded, but the second clause of check has not yet been tried. So badcount3 has to preserve a copy of its stack frame in order to go back and try the other clause of check if the recursive call fails.

/* Program ch06e05.pro */

Note that badcount2 and badcount3 are worse than badcount1 because they generate backtrack points.

Cuts to the Rescue

By now, you may think it's impossible to guarantee that a procedure is tail recursive. After all, it's easy enough to put the recursive call in the last subgoal of the last clause, but how do you guarantee there are no alternatives in any of the other procedures that it calls?

Fortunately, you don't have to. The cut (!) allows you to discard whatever alternatives may exist. You'll need to use the check_determ compiler directive to guide you through setting the cuts. (Compiler directives are described in the chapter 17.)

You can fix up badcount3 as follows (changing its name in the process):

    cutcount3(X) :-
        write('¡¬r',X),
        NewX = X+1,
        check(NewX),
        !,
        cutcount3(NewX). 

leaving check as it was.

The cut means "burn your bridges behind you" or, more precisely, "once you reach this point, disregard alternative clauses for this predicate and alternative solutions to earlier subgoals within this clause." That's precisely what you need. Because alternatives are ruled out, no stack frame is needed and the recursive call can go inexorably ahead.

A cut is equally effective in badcount2, by negating and moving the test from the second clause to the first:

    cutcount2(X) :-
        X >= 0, !,
        write('¡¬r',X),
        NewX = X+1,
        cutcount2(NewX).

    cutcount2(X) :-
        write("X is negative.").

A cut is really all about making up ones mind. You set a cut whenever you can look at non-deterministic code, and say "Yes! Go ahead!" -- whenever it's obvious that alternatives are of no interest. In the original version of the above example, which tries to illustrate a situation where you have to decide something about X (the test X < 0 in the second clause), the second clause had to remain an option as the code in the first clause didn't test X. By moving the test to the first clause and negating it, a decision can be reached already there and a cut set in accordance: "Now I know I don't want to write that X is negative.".

The same applies to cutcount3. The predicate check illustrates a situation where you want to do some additional processing of X, based on its sign. However, the code for check is, in this case for illustration, non-deterministic, and the cut after the call to it is all about you having made up your mind. After the call to check, you can say "Yes! Go ahead!". However, the above is slightly artificial -- it would probably be more correct for check to be deterministic:

                    check(Z) :- Z >= 0, !, ... % processing using Z
check(Z) :- Z < 0, ... %processing using Z

And, since the test in the second clause of check is the perfect negation of the test in the first, check can be further rewritten as:

                    check(Z) :- Z >= 0, !, % processing using Z
check(Z) :- ... % processing using Z

When a cut is executed, the computer assumes there are no untried alternatives and does not create a stack frame. Program 6 contains modified versions of badcount2 and badcount3:

/* Program ch06e06.pro */

Unfortunately, cuts won't help with badcount1, whose need for stack frames has nothing to do with untried alternatives. The only way to improve badcount1 would be to rearrange the computation so that the recursive call comes at the end of the clause.

5. Using Arguments as Loop Variables

Now that you've mastered tail recursion, what can you do about loop variables and counters? To answer that question, we'll do a bit of Pascal-to-Prolog translation, assuming that you're familiar with Pascal. Generally, the results of direct translations between two languages, whether natural or programming, are poor. The following isn't too bad and serves as a reasonable illustration of strictly imperative programming in Prolog, but you should never write Prolog programs by blind translation from another language. Prolog is a very powerful and expressive language, and properly written Prolog programs will display a programming style and problem focus quite different from what programs in other languages do.

In the "Recursion" section, we developed a recursive procedure to compute factorials; in this section we'll develop an iterative one. In Pascal, this would be:

    P := 1;
    for I := 1 to N do P := P*I;
    FactN := P;

If you're unfamiliar with Pascal, the :- is the assignment, read as "becomes". There are four variables here. N is the number whose factorial will be calculated; FactN is the result of the calculation; I is the loop variable, counting from 1 to N; and P is the variable in which the product accumulates. A more efficient Pascal programmer might combine FactN and P, but in Prolog it pays to be fastidiously tidy.

The first step in translating this into Prolog is to replace for with a simpler loop statement, making what happens to I in each step more explicit. Here is the algorithm recast as a while loop:

    P := 1;                                  /* Initialize P and I */
    I := 1;
    while I <= N do                                   /* Loop test */
        begin
           
P := P*I;                              /* Update P and I */
            I := I+1
        end;
    FactN := P;
                                   /* Return result */

shows the Prolog translation constructed from this Pascal while loop.

/* Program ch06e07.pro */

Let's look at this in greater detail.

The factorial clause has only N and FactN as arguments; they are its input and output, from the viewpoint of someone who is using it to find a factorial. A second clause, factorial_aux(N, FactN, I, P), actually performs the recursion; its four arguments are the four variables that need to be passed along from each step to the next. So factorial simply invokes factorial_aux, passing to it N and FactN, along with the initial values for I and P, like so:

factorial(N, FactN) :-
   
factorial_aux(N, FactN, 1, 1).

That's how I and P get initialized.

How can factorial "pass along" FactN? It doesn't even have a value yet! The answer is that, conceptually, all Visual Prolog's doing here is unifying a variable called FactN in one clause with a variable called FactN in another clause. The same thing will happen whenever factorial_aux passes FactN to itself as an argument in a recursive call. Eventually, the last FactN will get a value, and, when this happens, all the other FactN's, having been unified with it, will get the same value. We said "conceptually" above, because in reality there is only one FactN. Visual Prolog can determine from the source code that FactN is never really used before the second clause for factorial_aux, and just shuffles the same FactN around all the time.

Now for factorial_aux. Ordinarily, this predicate will check that I is less than or equal to N--the condition for continuing the loop--and then call itself recursively with new values for I and P. Here another peculiarity of Prolog asserts itself. In Prolog there is no assignment statement such as

    P = P + 1

which is found in most other programming languages. You can't change the value of a Prolog variable. In Prolog, the above is as absurd as in algebra, and will fail. Instead, you have to create a new variable and say something like

    NewP = P + 1

So here's the first clause:

    factorial_aux(N, FactN, I, P) :-
        I <= N, !,
        NewP = P*I,
        NewI = I+1,
        factorial_aux(N, FactN, NewI, NewP).

As in cutcount2, the cut enables last-call optimization to take effect, even though the clause isn't the last in the predicate.

Eventually I will exceed N. When it does, processing should unify the current value of P with FactN and stop the recursion. This is done in the second clause, which will be reached when the test I <= N in the first clause fails:

    factorial_aux(N, FactN, I, P) :-
        I > N,
        FactN = P.

But there is no need for FactN = P to be a separate step; the unification can be performed in the argument list. Putting the same variable name in the positions occupied by FactN and P requires the arguments in these positions to be matched with each other. Moreover, the test I > N is redundant since the opposite has been tested for in the first clause. This gives the final clause:

    factorial_aux(_, FactN, _, FactN).

Exercises

The following is a more elegant version of factorial.

/* Program ch06e08.pro */

Load and run this program. Carefully look at the code in the second clause of factorial/4. It takes advantage of the fact that the first time it's called the counter variable I always has the value 1. This allows the multiplication step to be carried out with the incremented counter variable NewI rather than I, saving one recursion/iteration. This is reflected in the first clause.

Write a tail recursive program that behaves like 2 but doesn't use backtracking.

Write a tail recursive program that prints a table of powers of 2, like this:

N

2^N

--

-----

1

2

2

4

3

8

4

16

...

...

10

1024

    Make it stop at 10 as shown here.

Write a tail recursive program that accepts a number as input and can end in either of two ways. It will start multiplying the number by itself over and over until it either reaches 81 or reaches a number greater than 100. If it reaches 81, it will print yes; if it exceeds 100, it will print no.