Dynamic Cutting

The traditional cut in Prolog is static. One problem with this is that the effect of the cut happens when execution passes the ! symbol, and it affects only those clauses in which it was placed (in the source text). There is no way of passing the effect of a cut in an argument to another predicate, where the cut might only be evaluated if some conditions were fulfilled. Another problem with the traditional cut is that it is impossible to cut away further solutions to a subgoal in a clause, without also cutting away the backtrack point to the following clauses in the predicate.

Visual Prolog has a dynamic cutting mechanism, which is implemented by the two standard predicates getbacktrack and cutbacktrack. This mechanism allows you to handle both of these problems. The predicate getbacktrack returns the current pointer to the top of the stack of backtrack points. You can remove all backtrack points above this place, at some later time, by giving the pointer thus found to the cutbacktrack predicate.

ΆΓ Examples

Here are some examples that illustrate the use of these two predicates.

Suppose you have a database of people and their incomes, and you have registered who their friends are.

    DATABASE
        person(symbol, income)
        friends(symbol, symbol)

If you define a happy person as one who either has some friends or pays little tax, the clauses that return happy persons could be as follows:

    happy_person(has_friends(P)) :- person(P, _), friends(P, _).
    happy_person(is_rich(P)) :- person(P, Income), not(rich(Income)).

If a person has more than one friend, the first clause will return a multiple number of solutions for the same person. You could, of course, add another predicate have_friends(P,P) that has a cut, or you could use the dynamic cut instead.

    happy_person(has_friends(P)) :-
        person(P, _),
        getbacktrack(BTOP),
        friends(P, _),
        cutbacktrack(BTOP).

Although the friends predicate might return many solutions if backtracked into, that possibility is cut away with the call to cutbacktrack. A subsequent failure would backtrack into the person predicate.

The more important use of a dynamic cut is when you pass the backtrack pointer to another predicate and execute the cut conditionally. The pointer is of unsigned type and can be passed in arguments of unsigned type.

As an illustration of this, let's say you want a predicate to return numbers until the user presses a key.

    PREDICATES
        number(integer)
        return_numbers(integer)
        checkuser(unsigned)

    CLAUSES    
        number(0).
        number(N) :- number(N1), N = N1+1.
        return_numbers(N) :- getbacktrack(BTOP), number(N), checkuser(BTOP).
        checkuser(BTOP) :- keypressed, cutbacktrack(BTOP).
        checkuser(_).

The compiler does not recognize the cutbacktrack predicate in the pass that analyzes the clauses for determinism. This means you could get the warning Non-deterministic clause when using the check_determ directive, even if you called cutbacktrack.

You should use dynamic cutting very judiciously. It's all too easy to destroy program structure with dynamic cutting, and careless use will invariably lead to problems that are very hard to track down.