Programming Style

In this section, we provide some comprehensive guidelines for writing good Visual Prolog programs. After summarizing a few rules of thumb about programming style, we give you some tips about when and how to use the fail predicate and the cut.

1. Rules for Efficient Programming

Rule 1. Use more variables rather than more predicates.

This rule is often in direct conflict with program readability. To achieve programs that are efficient (both in their demands upon relatively cheap machines and upon relatively expensive human resources) requires a careful matching of objectives.

Often, the purely declarative style of Prolog leads to code that is significantly less efficient than other (non-declarative) approaches. For instance, if you're writing a predicate to reverse the elements of a list, this code fragment:

    reverse(X, Y) :- reverse1([], X, Y).         /* More efficient */
    reverse1(Y, [], Y).
    reverse1(X1, [U|X2], Y) :- reverse1([U|X1], X2, Y).

makes less demands upon the stack than the next one, which uses the extra predicate append:

    reverse([], []).                             /* Less efficient */
    reverse([U|X], Y) :- reverse(X, Y1), append(Y1, [U], Y).

    append([], Y, Y).
    append([U|X], Y, [U|Z]) :- append(X, Y, Z).

Rule 2. Try to ensure that execution fails efficiently when no solutions exist.

Suppose you want to write a predicate singlepeak that checks the integers in a list to see if, in the order given, they ascend to a single maximum and then descend again. With this predicate, the call:

    singlepeak([1, 2, 5, 7, 11, 8, 6, 4]).

would succeed, while the call:

    singlepeak([1, 2, 3, 9, 6, 8, 5, 4, 3]).

would fail.

The following definition for singlepeak breaks Rule 3, since the failure of a list to have a single peak is only recognized when append has split the list into every possible decomposition:

    /* Definition 1 - Breaks Rule 2 */

    singlepeak(X) :- append(X1, X2, X), up(X1), down(X2).

    up[_].
    up([U, V|Y]) :- U<V,
  up([V|Y]).

    down([]).
    down([U]).
    down([U, V|Y]) :- U>V,
  down([V|Y]).

    append([], Y, Y).
    append([U|X], Y, [U|Z]) :- append(X, Y, Z).

On the other hand, the next definition recognizes failure at the earliest possible moment:

    /* Definition 2 - Follows Rule 2 */

    singlepeak([]).
    singlepeak([U, V|Y]) :- U<V, singlepeak([V|Y]).
    singlepeak([U, V|Y]) :- U>V, down([V|Y]).

    down([]).
    down([U]).
    down([U, V|Y]) :- U>V, down([V|Y]).

The third and final definition shortens singlepeak even further by observing Rule 1.

    /* Definition 3 - Follows Rule 1 */

    singlepeak([], _).
    singlepeak([U, V|W], up) :- U<V, singlepeak([V|W], up).
    singlepeak([U, V|W], _)
  :- U>V, singlepeak([V|W], down).

Using Definition 3, this call to singlepeak

    singlepeak(Y, up)

succeeds if Y is bound to a single peaked list appended to an ascending list. This call

    singlepeak(Y, down)

succeeds if Y is bound to a descending list.

Rule 3. Let Visual Prolog's unification mechanism do as much of the work as possible.

At first thought, you might define a predicate equal to test two lists from the same domain for equality as follows:

    equal([], []).
    equal([U|X], [U|Y]) :- equal(X, Y).

This is unnecessary. Using the definition

    equal(X, X).

or, even simpler, unification by means of =, Visual Prolog's unification mechanism does all the work!

Rule 4. Use backtracking--instead of recursion--for repetition.

Backtracking decreases stack requirements. The idea is to use the repeat ... fail combination repeat--fail combination instead of recursion. This is so important that the next section is dedicated to the technique.

2. Using the fail Predicate

To evaluate a particular sequence of subgoals repeatedly, it is often necessary to define a predicate like run with a clause of the form subgoals, evaluating repeatedly

    run :-
        readln(X),
        process(X, Y),
        write(Y),
        run.

This kind of definition incurs unnecessary recursion overheads that can't be automatically eliminated by the system if process(X,Y) is non-deterministic.

In this case, the repeat ... fail combination avoids the need for the final recursive call. Given

    repeat.
    repeat :- repeat.

you can redefine run without recursion as follows:

    run :-
        repeat,
              readln(X),
              process(X, Y),
              write(Y),
        fail.

fail causes Visual Prolog to backtrack to process and eventually to repeat, which always succeeds. But how do you break out of a repeat ... fail combination? Well, in the cases where you want infinite execution (the run:- ..., ..., run variety, you will usually only want to quit if some exceptional condition arises. To this end, you can use the exit predicate in non-interactive programs, or just press break in interactive ones. In other cases, where you have a clear condition of completion, replace the fail with a test for completion:

    run:-
        repeat,
              getstuff(X),
              process(X,Y),
              putstuff(Y),
        test_for_completion(Y),
        !.

3. Determinism vs. Non-determinism: Setting the Cut

The compiler directive check_determ is useful when you need to decide where to place the cut, since it marks those clauses that give rise to non-deterministic predicates. If you want to make these predicates deterministic, you must insert the cut to stop the backtracking (which causes the non-determinism).

As a general rule, in such cases, the cut should always be inserted as far to the left as possible (close to the head of a rule) without destroying the underlying logic of the program.

Keep in mind these two rules used by the compiler to decide that a clause is non-deterministic:

There is no cut in the clause, and there is another clause that can match the input arguments in the clause head.

There is a call to another non-deterministic predicate in the clause body, and this non-deterministic call is not followed by a cut.