Module 5 , Part 2
Termination criteria
 
- Terminate when the list is empty

 

 
The pattern for this is:
     % 1 terminating condition
     rule([]) :-
          some_processing([]).
     % 2 recursive
     rule([Head|Tail]) :-
          some_processing(Head),
          rule(Tail).
Now, this is only a pattern: the procedures we'll see in this section will all have this pattern as part of them, although there may be additions.
is_list/1

is_list/1 is one of the simplest of this family of procedures. The idea is that we can tell if an argument is a list if we can reduce it to an empty list:
     % 1 terminating condition
     is_list([]) :-
          write('This is a list'),
          nl.
     % 2 recursive
     is_list([_|Tail]) :-
          % we don't have any processing here - which is why we can
          % use an anonymous variable (instead of Head) in the argument
          is_list(Tail).
Try the following goals:
     | ?- is_list([]).
     | ?- is_list([a,b,c]).
     | ?- is_list([X,Y,Z]).

 
count_elems/2

The obvious difference between the previous example and count_elems/2 is that the latter has two arguments. For those who have used other programming languages which include functions, this can be confusing. Prolog procedures aren't returned with a value setable by the programmer, as are functions. Values to be passed back have to be included in the argument list. count_elems/2 is a simple example of this. count_elems/2 has the straightforward purpose of counting the number of elements in a list. The procedure is slightly different from the basic pattern:
     % 1 terminating condition
     count_elems([], Total) :-
          Total = 0.                      % processing
     % 2 recursive
     count_elems([Head|Tail], Count) :-
          count_elems(Tail, Sum),         % recursive
          Count is Sum + 1.               % processing
The main difference is that the order of the recursive and processing sub-goals in the recursive rule have been swapped. If we draw a tree to represent the processing of some goal, eg: count_elems([alpha, beta, gamma], Cnt).

the most obvious difference is that it is a reflection of the typical tree shown earlier. This is simply because of the switch of the recursive and processing sub-goals in the second rule.
 

app/3

A common process in list processing is the need to run two lists together to make one list. This is usually known as appending or concatenating lists. So we might have the lists:
     [alpha, beta, gamma]
and
     [chi, psi, omega]
and require the final list:
     [alpha, beta, gamma, chi, psi, omega]
Unfortunately it isn't possible to get this solution simply with the query:
     | ?- List1 = [alpha, beta, gamma], List2 = [chi, psi, omega], 
          [List1|List2] = List3.
(If you don't know what the List3 will be instantiated to, then you should try the query for yourself.)

Instead, we have to write a procedure that will add one list to another, element-by-element. We'll start the process by considering the terminating condition. The assumption implicit in this is that if the first of the original lists is empty, then the result list must be the same as the second original list:

     % 1 terminating condition
     app([], List2, List3) :-
          List2 = List3.
More experienced Prolog programmers always attempt to do as much work as possible in the argument list, rather than writing extra sub-goals. In this example, we can unify List2 and List3 in the argument list simply by calling them the same name. So we can rewrite this rule as a fact:
     % 1 terminating condition
     app([], List, List).
Before looking at the recursive clause, we'll look at the kinds of queries that this will unify with. Here is a sample:
     | ?- app([], [chi, psi, omega], [chi, psi, omega]).

     yes
     | ?- app([], [chi, psi, omega], List3).

     List3 = [chi,psi,omega] ? ;

     no
     | ?- app(Var, [chi, psi, omega], List3).
     
     Var = [] 
     List3 = [chi,psi,omega] ? ;

     no
     | ?- app([], [], Result).

     Result = [] ? ;

     no
     | ?- app(Var, [], Result).

     Var = [] 
     Result = [] ? ;

     no
The first three are predictable. In the case of the third, the first argument of the query is an uninstantiated variable which is unified with [] in the program. The last two are more interesting. It would seem obvious that, if there is a need to write a definition of what is to be done is the first argument is an empty list, then there should be a definition of what is to be done if the second argument is an empty list. (I suppose we ought to also write a definition that would cope when both the first and second arguments are empty lists.) In practice, we don't need to do this as our definition will cover situations where the second list is either empty or not empty.

This brings us to the recursive rule. We have just seen that we can deal with the second argument if it is empty or non-empty. This suggests that the recursive rule should work on the first argument, which we haven't yet dealt with. All we can really say about the first argument is that we want each element of it stuck onto the second argument. We've seen that we can't just "stick" the two lists together, so we are reduced to attaching the first list to the second, one element at a time.

An initial definition that fits into our basic pattern is:

     % 2 recursive
     app([Hd1|Tl1], List2, [Hd3|Tl3]) :-
          Hd1 = Hd3              % this makes the head of the first list
                                 % unify with the head of the third list
          app(Tl1, List2, Tl3).
We can read this as: appending a list is true if it is true that we can unify the head of the first list with the head of the third list and that we can append the tail of the first list, the second list and the tail of the third list.

As with the definition of the terminating condition, we can rewrite this rule more succinctly, simply by renaming the variables used to stand for the head of the first and third lists:

     % 2 recursive
     app([Hd|Tl1], List2, [Hd|Tl3]) :-
          app(Tl1, List2, Tl3).
If we put these two clauses together, we get a procedure that looks like:
     % 1 terminating condition
     app([], List, List).
     % 2 recursive
     app([Hd|Tl1], List2, [Hd|Tl3]) :-
          app(Tl1, List2, Tl3).
Try out a few queries to ensure that this works:
     | ?- app([alpha, beta, gamma], [chi, psi, omega], List3).
     | ?- app([], [chi, psi, omega], List3).
     | ?- app([alpha, beta, gamma], [], List3).
     | ?- app([], [], List3).

Instantiation of variables in app/3

We now have a working version of app/3. We'll now consider in detail how and when each argument in the app/3 procedure becomes instantiated. We could do this by using a trace of app/3, but instead we'll use a special version that includes some extra code. We'll call this demo_app/3.
     | ?- demo_app([alpha, beta, gamma], [chi, psi, omega], List3).
          Before recursion at depth 1
             List1 is: [alpha,beta,gamma]
             List2 is: [chi,psi,omega]
             List3 is: [alpha|_4856]
               Before recursion at depth 2
                  List1 is: [beta,gamma]
                  List2 is: [chi,psi,omega]
                  List3 is: [beta|_5424]
                    Before recursion at depth 3
                       List1 is: [gamma]
                       List2 is: [chi,psi,omega]
                       List3 is: [gamma|_6243]
                         At the termination condition
                            List1 is: []
                            List2 is: [chi,psi,omega]
                            List3 is: [chi,psi,omega]
                    After recursion at depth 3
                       List1 is: [gamma]
                       List2 is: [chi,psi,omega]
                       List3 is: [gamma,chi,psi,omega]
               After recursion at depth 2
                  List1 is: [beta,gamma]
                  List2 is: [chi,psi,omega]
                  List3 is: [beta,gamma,chi,psi,omega]
          After recursion at depth 1
             List1 is: [alpha,beta,gamma]
             List2 is: [chi,psi,omega]
             List3 is: [alpha,beta,gamma,chi,psi,omega]
     
     List3 = [alpha,beta,gamma,chi,psi,omega] ;
     
     no
Look carefully at how List3 is instantiated.
  • At recursion of depth 1, the head is instantiated, but the tail isn't, so it is: [alpha|_4856].
  • At depth 2, the head again is instantiated, but the tail isn't, so it is: [beta|_5424]. However, the alpha from the previous stage seems to have disappeared. This is because the recursive condition works on the tail of List3.
  • At depth 3, the same happens. Recursion is again on the tail of List3.
  • At the terminating condition, List3 is unified with List2, so is instantiated to the value: [chi,psi,omega].
  • On the way "out" of the recursion, note that the tail of List3 is now instantiated. Also, note how the head is attached at each successive stage "out" of recursion.

  •