Determinism Monitoring in Visual Prolog

Most programming languages are deterministic in nature. That is, any set of input values leads to a single set of instructions used to produce output values. Furthermore in most languages, for example in C, a called function can produce only a single set of output values. On the contrary, Visual Prolog naturally supports non-deterministic inference based on non-deterministic predicates.

The object behind the determinism monitoring is to save run-time storage space. In fact, when a deterministic clause succeeds, the corresponding run-time stack space can be dispensed with at once, thus freeing the storage it occupied. There are a number of reasons why determinism should also concern programmers, most of them involving programming optimization.

Visual Prolog has a strongly typed determinism system. Visual Prolog's determinism checking system enforces the programmer to declare the following two behavior aspects of predicates:

whether a call to a predicate can fail;

number of solutions a predicate can produce.

According to these aspects of determinism the following Types of Predicates (rules) are supported in Visual Prolog:

Predicate Types

Number of Solutions, that can be produced

 

0

1

> 1

Can fail:|

failure

determ

nondeterm

Never fails:

erroneous

procedure

multi

Using keywords from the above table in declarations of predicates and predicate domains the programmer can declare the six different types of predicates.

Applied these aspects of determinism to declarations of facts we can obtain the following table:

 Facts Types

Number of Solutions can be Produced

 

0

1

> 1

Can fail:|

 

determ

nondeterm

Never fails:

 

 

single

In this table Never fails means that as less one instance of a fact always exists, and therefore such a fact never fails if it is called with free arguments. Using keywords from the above table in declarations of facts the programmer can declare the three different types of database predicates (facts).

1. Visual Prologs determinism checking system

Visual Prolog offers unique determinism monitoring facilities based on declarations of types of predicates and facts. All Visual Prolog's standard predicates are internally defined as nondeterm, multi, determ, procedure, failure or erroneous. For user-defined predicates declared with the keywords determ, procedure, failure or erroneous, the compiler always checks and gives warnings for each program clause that results in a non-deterministic predicate. There are two kinds of non-deterministic clauses:

If a clause does not contain a cut, and there are one or more clauses that can match with the same input arguments for that flow pattern.

If a clause calls a non-deterministic predicate, and that predicate call is not followed by a cut.

Because of the second reason above, non-determinism has a tendency to spread like wildfire throughout a program unless (literally) cut off by one or more cuts.

By default, the compiler checks clauses and gives a warning (595 or 596) if it cannot guarantee that a predicate corresponds to the declared type. For example, if the compiler is unable to guarantee that a predicate declared with the keyword multi, procedure or erroneous never fails.

Take into account that the compiler is able to verify only necessary conditions for fail (not necessary and sufficient). Therefore, the compiler can sometimes generate warnings 595 and 596 for predicates (declared with the keyword multi, procedure or erroneous) that, in fact, will never fail. For example,

    PREDICATES
        procedure str_chrlist(STRING,CHARLIST) - (i,o)

    CLAUSES
        str_chrlist("",[]):-!.
        str_chrlist(Str,[H|T]):-
        frontchar(Str,H,Str1),
        str_chrlist(Str1,T).

The frontchar predicate can fail if the first parameter is an empty string. The compiler is not sophisticated enough to detect that Str in the second clause cannot be empty. For this example the compiler will generate warning 595 "Non-procedure clause in the procedure predicate".

Of course, non-procedure predicates checking can be switched off if the programmer specifies the compiler option -upro- (), but it is not good programming style. Instead you should reorder the clauses like:

    str_chrlist(Str,[H|T]):-
    frontchar(Str,H,Str1),!,
    str_chrlist(Str1,T).
    str_chrlist(_,[]):-!.

The declaration of procedures catches many small mistakes, like forgetting a catchall clause.

There are two rules that you must use when writing predicates declared with the keyword multi, procedure or erroneous:

 If anyone predicate clause can fail than the final catchall clause must be defined (see the str_chrlist example above).

 For any possible (according to declared domains) set of input arguments, a clause, having a head which matches this set, must exist. Otherwise, the compiler will generate the warning 596.

For instance, in the following example the third clause p(_) can be redundant if the predicate is declared without procedure keyword, but is required to satisfy this rule if the predicate is declared as procedure.

    DOMAINS
        BOOLEAN = INTEGER % b_True = 1, b_False = 0

    PREDICATES
        procedure p(BOOLEAN)

    CLAUSES
        p(b_False):- !, ... .
        p(b_True): - !, ... .
        p(_): - dlg_error("An illegal argument value").

Notice that the compiler handles erroneous predicates in a special way providing possibility to use them in the final catchall clauses (for handling error situations) in predicates of other types. For instance, the catchall clause in the previous example can be rewritten as the following:

    p(_): - errorexit(error_vpi_package_bad_data).