CHAPTER 11    Advanced Topics

 

This is an advanced chapter; we expect that you have been working with the various examples earlier in this book and are now beginning to be an experienced Visual Prolog user. In this chapter, we illustrate how you can control the flow analysis by using the standard predicates free and bound, reference domains, how to use them and how to separate them from the other domains. We also discuss more advanced topics about domains, including the binary domain, pointers to predicates and functions, and return values from functions. Finally, we look at error-handling, dynamic cutting, free type conversions, and a discussion of some programming style issues that will improve your programs' efficiency.

The Flow Analysis

In a given predicate call, the known arguments are called input arguments (i), and the unknown arguments are called output arguments (o). The pattern of the input and output arguments in a given predicate call is called the flow pattern.

For example, if a predicate is to be called with two arguments, there are four possibilities for its flow pattern:

    (i, i)   (i, o)   (o, i)   (o, o)

When compiling programs, Visual Prolog carries out a global flow analysis of the predicates. It starts with the main goal and then performs a pseudo-evaluation of the entire program, where it binds flow patterns to all the predicate calls in the program.

The flow analysis is quite simple; you are actually carrying it out yourself when you write your program. Here are some examples:

    GOAL
        cursor(R, C), R1 = R+1, cursor(R1, C).

In the first call to the cursor, the two variables R and C are free; this means that the cursor predicate will be called with the flow pattern cursor(o,o). You know that the variables are free because this is the first time they've been encountered.

In the expression R1=R+1, the flow analyzer knows that the variable R is bound because it comes from the cursor predicate. If it were free, an error message would have been issued. R1 will be a known argument after this call.

In the last call to cursor, both of the variables R1 and C have been encountered before, so they will be treated as input arguments; the call will have the flow pattern cursor(i,i).

For each flow pattern that a user-defined predicate is called with, the flow analyzer goes through that predicate's clauses with the variables from the head set to either input or output (depending on the flow pattern being analyzed).

Here's an example illustrating this:

% This example will only run for DOS Textmode Target
PREDICATES
    changeattrib(Integer, Integer)
CLAUSES
    changeattrib(NewAttrib, OldAttrib) :-
        attribute(OldAttrib), attribute(NewAttrib). 

GOAL
    changeattrib(112, Old), write("Hello"),
    attribute(Old), write(" there").

In the goal section, the first call to the predicate changeattrib is made with the flow pattern changeattrib(i, o) (because 112 is known, and Old is not). This implies that, in the clause for changeattrib, the variable NewAttrib will be an input argument, and OldAttrib will be an output argument. Therefore, when the flow analyzer encounters the first subgoal attribute(OldAttrib), the predicate attribute will be called with the flow pattern attribute(o), while the second call to attribute will have the flow pattern attribute(i). Finally, the call to attribute in the goal will have an input flow pattern, because Old came out of changeattrib.

(1) Compound Flow

If a predicate argument is a compound term it's also possible to have a compound flow pattern, where the same argument has both input and output flow. Suppose for instance that you have a database of information about countries. To enable easy expansion with new data, it may well be desirable to contain each piece of information in its own domain alternative:

/* Program ch11e01.pro */

    diagnostics

    DOMAINS
        cinfo = area(string,ulong); popn(string,ulong); apital(string,string)

    PREDICATES
        nondeterm country(cinfo)

    CLAUSES
        country(area("Denmark",16633)).
        country(popn("Denmark",5097000)).
        country(capital("Denmark","Copenhagen")).
        country(area("Singapore",224)).
        country(popn("Singapore",2584000)).
        country(capital("Singapore","Singapore")).

The following depicts some of the different flow patterns country can be called with:

    country(C)                                                (o)
    country(area(Name,Area))area
                  (o,o)
    country(popn("Denmark",Pop))popn
            (i,o)
    country(capital("Singapore","Singapore"))                     (i)

Note that as all elements of the term are known in the last example, the flow pattern defaults to plain input.

Load 1 and try the examples above. When you look at the diagnostics output, don't be confused by the presence of several flow variants as you progress. The compiler keeps previously compiled code between executions of external goals, unless the source code is changed.

When the domains involved in a compound flow pattern are reference domains, the distinction between known and unknown arguments becomes blurred. We'll return to this example in the reference domain section later.

1. Specifying Flowpatterns for Predicates

It is sometimes convenient to specify flowpatterns for your predicates. If you know, that your predicates will only be valid for special flow patterns, it is a good idea to specify flowpatterns for your predicates because the flow analyzer will then catch any wrong usage of these predicates. After specifying the domains, a dash and the possible flowpatterns can be given like in:

    PREDICATES
        frame_text_mask(STRING,STRING,SLIST) - (i,o,o)(o,i,o)

2. Controlling the Flow Analysis

When the flow analyzer recognizes that a standard predicate is called with a nonexistent flow pattern, it issues an error message. This can help you identify meaningless flow patterns when you're creating user-defined predicates that call standard predicates.

For example, if you use:

    Z = X + Y

where the variable X or Y is not bound, the flow analyzer will give an error message saying that the flow pattern doesn't exist for that predicate. To control this situation, you can use the standard predicates free and bound.

Suppose you want to create a predicate for addition, plus, which can be called with all possible flow patterns. Program 2 gives the code for such a predicate.

/* Program ch11e02.pro */

        num(A),

        X = A+1.

3. Reference Variables

When the flow analyzer has been through a clause, it checks that all output variables in the clause head have been bound in the clause body. If a variable is not bound in a clause, it needs to be treated as a reference variable. Here's an example demonstrating this dilemma:

    PREDICATES
        p(integer)

    CLAUSES
        p(X):- !.

    GOAL
        p(V), V = 99, write(V).

In the goal, the predicate p is called with an output pattern but, in the clause for p, the argument X is not bound. When the flow analyzer recognizes this, it will take a look at the domain corresponding to the variable. If the domain is already declared as a reference domain, there's no problem; if it's not, Visual Prolog gives a warning.

When a variable is not bound in a clause, the clause can't return a value. Instead, it will return a pointer to a reference record where the actual value can be inserted at a later time. This requires that the whole domain be treated equally; instead of just passing the values directly for some of the variables of that type, pointers to records will be passed through arguments belonging to the reference domain. When a compound domain becomes a reference domain, all of its subdomains must also become reference domains, because they must also be capable of containing free variables. If you just declare a compound domain to be a reference domain, the compiler will automatically know that all the subdomains are also reference domains.

4. Declaring Domains as Reference

When the flow analyzer encounters an unbound variable, it will only give a warning if the variable is not bound on return from a clause. If you accept this, the domain will automatically be treated as a reference domain. However, you should always explicitly declare the domains intended to be reference domains in the domains section. This is also required in projects (programs consisting of several modules); when global domains should handle unbound values, the compiler will not allow automatic conversion of the domains. Global domains and predicates are covered in the chapter 17.

Notice that the following special predefined domains are not allowed to become reference domains: file, reg, db_selector, bt_selector, and place.

5. Reference Domains and the Trail Array

Because coercion¡¯s and some extra unification are needed, reference domains will in general give a reduction in execution speed. However, some problems can be solved far more elegant and efficiently when you use reference domains, and Visual Prolog has facilities to limit their effect.

When you use reference domains, Visual Prolog uses the trail array. The trail array is used to remember when reference variables become instantiated. This is necessary because if you backtrack to a point between the creation and the instantiation of a reference variable, it must be uninstantiated. This problem doesn't exist with ordinary variables, as their points of creation and instantiation are the same. Each instantiation recorded in the trail uses 4 bytes (the size of a 32-bit pointer). However, the trail usage is heavily optimized and no record will be placed there if there are no backtrack points between the variable's creation and instantiation.

The trail is automatically increased in size when necessary. The maximum size is 64K in the 16-bit versions of Visual Prolog, and practically unbounded in the 32-bit versions.

Because the code is treated the same for the whole domain, it is usually not a good idea to treat the basic domains as reference domains. Instead, you should declare a domain as being a reference domain to the desired base domain. For instance, in the following code excerpt, the user-defined domain refinteger is declared to be a reference domain to the integer domain. All occurrences of refinteger types will be handled as reference domains, but any occurrence of other integers will still be treated as integers.

    DOMAINS
        refinteger = reference integer

    PREDICATES
        p(refinteger)

    CLAUSES
        p(_).

6. Using Reference Domains

The right way to use reference domains is to use them only in the few places where they are needed and to use non-reference domains for all the rest. Visual Prolog allows you to convert reference domains to non-reference domains whenever needed. For example, you can create a predicate that converts a reference integer to a non-reference integer with a single fact:

    DOMAINS
        refint = reference integer

    PREDICATES
        conv(refint,integer)

    CLAUSES
        conv(X, X).

Visual Prolog does the conversion automatically when the same variable is used with both a reference domain and a non-reference domain, as it does in the clause when converting X from a refint to an integer. The above is only an explicit example, you don't need to write any special code to convert from reference to non-reference domains. Note that the reference variable needs to be instantiated to a value before it can be converted to the non-reference value. In the same way, if you try to convert a variable from one reference domain to another (such as from reference integers to reference characters), you should make sure the value is bound. Otherwise, Visual Prolog will issue an error message to the effect that free variables are not allowed in the context.

Pay attention to the automatic type conversions when you're creating a new free reference variable through a call to free, like so:

    free(X), Y = X, bind_integer(X), ...

or creating a free variable with the = predicate (equal), like this:

    Y = X, bind_integer(X), ...

In these examples, free and the = predicate have difficulty finding the correct domain. The type-checker will try to find a suitable domain for the variable during backtracking by means of successive attempts to carry out the flow analysis. The type-checker starts with the character domain and (because char types can be converted to integer types) will choose the character domain instead of proceeding to the integer domain.

With reference domains you can return variables that will receive values at a later point. You can also create structures where some places are left uninstantiated until later.

(1) Example

To get a feel for how reference domains work, you should try some goals with the well-known predicates member and append:

/* Program ch11e03.pro */

 

Load and run this example program, and try the following goals:

 

You will discover that the answers are what you logically expect them to be.

7. Flow Patterns Revisited

A reference variable may well be unbound and yet exist at the time it's used in a predicate call. In example 1, this will happen if for instance you want to find all countries having the same name as their capital, using e.g.

    samecaps:- country(capital(C,C)), write(C,'¡¬n'), fail.

Here the variable C is used twice with output flow, but what the code really says is that the two variables in capital should share the same value once one of them becomes instantiated. Therefore, both variables are created and unified before the call. In order to do this their domain is converted to a reference domain, and both variables are in effect known at the time of call, giving a straight input flow pattern.

Note that, as said before, it's bad practice to let the standard domains become reference domains. If you want to use the above call, you should declare a suitable reference domain. However, this would create an overhead in all accesses of the country predicate, and it would probably be more efficient to use backtracking to find the special case where name and capital are identical, by using.

    country(capital(Co,Ca)), Co = Ca, !, ...

Whether this is true or not depends on the size of the database, how many times you perform the call, how many other calls you have, how the arguments are used after the calls, etc.

8. Using Binary Trees with Reference Domains

In chapter 6, you saw how binary trees could be used for fast and efficient sorting. However, sorting can actually be done in a more elegant fashion with reference domains. Because there is no way to change the leaves of a tree when they get new values, a lot of node copying occurs when the tree is created. When you are sorting large amounts of data, this copying can result in a memory overflow error. A reference domain can handle this by letting the leaves of the tree remain as free variables (where the subtrees will later be inserted). By using a reference domain this way, you don't need to copy the tree above the place where the new node is to be inserted.

Consider the predicate insert in ch11e04.pro during the evaluation of the following goal:

    GOAL
        insert("tom", Tree),
        insert("dick", Tree),
        insert("harry", Tree).

In this program, the insert predicate creates a binary tree using the reference domain tree.

/* Program ch11e04.pro */

The first subgoal, insert("tom",Tree), will match with the first rule, and the compound object to which Tree is bound takes this form:

    t("tom", _, _)

Even though the last two arguments in t are not bound, t carried is forward to the next subgoal evaluation:

    insert("dick", Tree)

This, in turn, binds Tree to

    t("tom", t("dick", _, _), _)

Finally, the subgoal

    insert("harry", Tree)

binds Tree to

    t("tom", t("dick", _, t("harry", _, _)), _)

which is the result returned by the goal.

9. Sorting with Reference Domains

In this section, we add onto the preceding binary tree example (ch11e04.pro) to show how you can isolate the use of reference domains and convert between reference and non-reference domains. The next example defines a predicate that is able to sort a list of values.

/* Program ch11e05.pro */

 

    instree([],_).

    instree([H|T],Tree):-

        insert(H,Tree),

        instree(T,Tree).

 

    treemembers(_,T):-

        free(T),!,fail.

    treemembers(X,t(_,L,_)):-

        treemembers(X,L).

    treemembers(X,t(Refstr,_,_)):-

        X = Refstr.

    treemembers(X,t(_,_,R)):-

        treemembers(X,R).

 

    sort(L,L1):-

        instree(L,Tree),

        findall(X,treemembers(X,Tree),L1).

 

GOAL

        sort([3,6,1,4,5],L),

        write("L=",L),nl.

In this example, note that reference domains are only used in the tree. All the other arguments use non-reference domains.