Module 5 , Part 2
Termination criteria
 
-
Terminate when a specified element is found

 

 
The pattern for this has two arguments, one being the element to be found, the other the list to be searched:
     % 1 terminating condition
     rule(Elem, [Elem|_]) :-
          some_processing.
     % 2 recursive
     rule(Elem, [Head|Tail]) :-
          some_processing,          % it's unusual to have processing
                                    % in the recursive condition
          rule(Elem, Tail).
The major differences between this pattern and that for working through a list until it is empty lie in when any processing on the list is done.
  • in empty list termination, we are interested in every element in a list, eg to count them or to append them to another list.
  • in specified member termination, we are interested in the element that we find to terminate the computation: all other elements are usually irrelevant.
As with empty list termination, 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.
memb/2

Membership is the most widely given example in textbooks and it is the simplest. The idea is that we look through a list until we find that a specified item is the current head of the list.
     % 1 terminating condition
     memb(Elem, [Elem|_]).
     % 2 recursive
     memb(Elem, [_|Tail]) :-
          % we don't have any processing here - which is why we can
          % use an anonymous variable (instead of Head) in the argument
          memb(Elem, Tail).
Try the following goals:
     | ?- memb(gamma, [alpha, beta, gamma]).
     | ?- memb(alpha, [alpha]).
     | ?- memb(delta, [alpha, beta, gamma]).
     | ?- memb(alpha, []).
Inexperienced Prolog programmers often add an extra clause:
     % 3 terminating condition (incorrect)
     memb(_, []).
If you add this to the previous procedure, you will find that the query:
     | ?- memb(alpha, []).
will be successful. If this is what you want the procedure to do, then this is fine. However, most people feel that if an item doesn't exist in a list, then this should be failure. We don't need to do anything extra to program failure: Prolog will do this for us if we leave the condition out of the procedure.
 
memb/2 with a counter

memb/2 as given is often used and is frequently included in Prolog libraries. We can use it as the base of an example to show how to extend a procedure. Suppose we want to know the position at which an item occurs. We will accept that if the element occurs in the list of the goal, the procedure will write the position of that element (taking the first element as one, rather than zero), and that if an element doesn't occur in the list, then the goal will fail.

We need to add some extra processing to both clauses and, of course, an extra argument. We'll look first at the recursive rule. Here we need just add one to a counter each time we recurse:

     % 2 recursive
     memb(Elem, [_|Tail], Cnt) :-
          Cnt1 is Cnt + 1,
          memb(Elem, Tail, Cnt1).
The terminating clause can just write the position:
     % 1 terminating condition
     memb(Elem, [Elem|_], Cnt) :-
          write(Cnt),
          nl.
Putting these two together, we have:
     % 1 terminating condition
     memb(Elem, [Elem|_], Cnt) :-
          write(Cnt),
          nl.
     % 2 recursive
     memb(Elem, [_|Tail], Cnt) :-
          Cnt1 is Cnt + 1,
          memb(Elem, Tail, Cnt1).
Try the following goals:
     | ?- memb(gamma, [alpha, beta, gamma], 1).
     | ?- memb(alpha, [alpha], 1).
     | ?- memb(delta, [alpha, beta, gamma], 1).
     | ?- memb(alpha, [], 1).
We have defined memb/2 and memb/3. Prolog doesn't confuse the two because, although they have the same functor, they have different arities. However, it is a bit irritating to have to type the ', 1' each time and we have to ensure that each time we get it correct. It is more convenient to write an extra, "calling" rule that supplies the extra argument for us. However, we can't call this memb/2, because this time Prolog will confuse it with our previous definition of memb/2, So we will call this one memb_count/2:
     % 1
     memb_count(Elem, List) :-
          memb(Elem, List, 1).
Try the following goals to assure yourself they give the same solutions as before:
     | ?- memb_count(gamma, [alpha, beta, gamma]).
     | ?- memb_count(alpha, [alpha]).
     | ?- memb_count(delta, [alpha, beta, gamma]).
     | ?- memb_count(alpha, []).

 
delete_element/3

In the next example, an element is removed from a list. This is extremely similar to memb/2, but it is necessary to have a third argument which is used to represent the list without the specified element.
     % 1 terminating condition
     delete_element(Elem, [Elem|Tail], Tail).
     % 2 recursive
     delete_element(Elem, [Head|Tail1], [Head|Tail2]) :-
          delete_element(Elem, Tail1, Tail2).
We'll look at the terminating condition first:
     % 1 terminating condition
     delete_element(Elem, [Elem|Tail], Tail).
This is true when the specified element (Elem) is the head of the list being searched. When this is true, the third argument is the same as the tail of the list.

The recursive rule looks more like app/3:

     % 2 recursive
     delete_element(Elem, [Head|Tail1], [Head|Tail2]) :-
          delete_element(Elem, Tail1, Tail2).
In this rule, the Head of the list to be searched is unified with the Head of the list which represents the list minus the specified element. The recursive sub-goal specifies that Elem is in Tail1 with Tail2 being the list to be searched without Elem.

Try the following goals to assure yourself they give the same solutions as before:

     | ?- delete_element(gamma, [alpha, beta, gamma, delta], List).
     | ?- delete_element(alpha, [alpha], List).
     | ?- delete_element(delta, [alpha, beta, gamma], List).
     | ?- delete_element(alpha, [], List).
As with app/3, we can write a version of the procedure called demo_delete_element/3 that displays the instantiations of the arguments during recursion:
     | ?- demo_delete_element(gamma, [alpha, beta, gamma, delta], List).
          Before recursion at depth 1
             Elem is: gamma
             "Search list" is: [alpha,beta,gamma,delta]
             "Result list" is: [alpha|_18743]
               Before recursion at depth 2

                  Elem is: gamma
                  "Search list" is: [beta,gamma,delta]
                  "Result list" is: [beta|_19292]
                    At the termination condition
                       Elem is: gamma
                       "Search list" is: [gamma,delta]
                       "Result list" is: [delta]
               After recursion at depth 2
                  Elem is: gamma
                  "Search list" is: [beta,gamma,delta]
                  "Result list" is: [beta,delta]
          After recursion at depth 1
             Elem is: gamma
             "Search list" is: [alpha,beta,gamma,delta]
             "Result list" is: [alpha,beta,delta]
     
     List = [alpha,beta,delta]
There are many variants on searching lists for a given element. Some of these are explored in the self-tests.
 
Take time to work through the Self-Test 5