A Closer Look at Declarations and Rules

Visual Prolog has several built-in standard domains. You can use standard domains when declaring the types of a predicate's arguments. Standard domains are already known to Visual Prolog and should not be defined in the domains section.

We'll first look at all the integral ones, shown in Table 3.1.

Table 3.1:Integral Standard Domains

Domain

Description and implementation

 

short

A small, signed, quantity.

 

All platforms

16 bits,2s comp

32768 .. 32767

 

ushort

A small, unsigned, quantity.

 

All platforms

16 bits  

0 .. 65535

 

long

A large signed quantity

 

All platforms

32 bits,2s comp

-2147483648 .. 2147483647

 

ulong

A large, unsigned quantity

 

All platforms

 32 bits   

0 .. 4294967295

 

integer

A signed quantity, having the natural size for the machine/platform architecture in question.

 

 

16bit platforms

16 bits,2s comp

-32768 .. 32767

 

 

32bit platforms

32 bits,2s comp

-2147483648 .. 2147483647

 

unsigned

An unsigned quantity, having the natural size for the machine/platform architecture in question.

 

 

16bit platforms

16 bits

0 .. 65535

 

 

32bit platforms

 32 bits 

0 .. 4294967295

 

byte

 

 

 

All platforms

³ 8 bits         

 0 .. 255

 

word

 

 

 

All platforms

16 bits

0 .. 65535

 

dword

 

 

 

All platforms

32 bits

 0 .. 4294967295

 

 

 

 

 

 

 

 

 

 

 

 

 

Syntactically, a value belonging in one of the integral domains is written as a sequence of digits, optionally preceded by a minus-sign for the signed domains, with no white-space. There are also octal and hexadecimal syntaces for the integral domains; these will be illustrated in chapter 9.

The byte, word, and dword domains are most useful when dealing with machine-related quantities, except perhaps for the byte; an 8-bit integral quantity can prove quite relevant, as we have already seen. For general use, the integer and unsigned quantities are the ones to use, augmented by the short and long (and their unsigned counterparts) for slightly more specialized applications. Generally, the most efficient code results from using what's natural for the machine; a short is not as efficient on a '386 platform as a long, and a long is not as efficient on a '286 platform as a short, hence the different implementations of integer and unsigned.

In domain declarations, the signed, and unsigned keywords may be used in conjunction with the byte, word, and dword built-in domains to construct new integral domains, as in

    DOMAINS
        i8 = signed byte

creating a new integral domain having a range of -128 to +127.

The other basic domains are shown in table 3.2. Visual Prolog recognizes several other standard domains, but we cover them in other chapters, after you've got a good grasp of the basics.

Table 3.2: Basic Standard Domains

Domain

Description and implementation

char

A character, implemented as an unsigned byte. Syntactically, it is written as a character surrounded by single quotation marks: 'a'.

real

 

A floating-point number, implemented as 8 bytes in accordance with IEEE conventions; equivalent to C's double. Syntactically, a real is written with an optional sign (+ or -) followed by some digits DDDDDDD, then an optional decimal point (.) followed by more digits DDDDDDD, and an optional exponential part (e(+ or -)DDD):

    <+|-> DDDDD <.> DDDDDDD <e <+|-> DDD>

Examples of real numbers:

    42705      9999       86.72

    9111.929437521e238    79.83e+21

Here 79.83e+21 means 79.83 x 10^21, just as in other languages.

The permitted number range is 1  ) 10-307 to 1  ) 10308 (1e-307 to 1e+308). Values from the integral domains are automatically converted to real numbers when necessary. 

string

A sequnce of characters, implemented as a pointer to a zero-terminated byte array, as in C. Two formats are permitted for strings:

1. a sequence of letters, numbers and underscores, provided the first character is lower-case; or

2. a character sequence surrounded by a pair of double quotation marks.

Examples of strings:

    telephone_number   "railway ticket"    "Dorid Inc"

Strings that you write in the program can be up to 255 characters long. Strings that the Visual Prolog system reads from a file or builds up internally can be up to 64K characters long on 16-bit platforms, and (theoretically) up to 4G long on 32-bit platforms.

symbol

A sequence of characters, implemented as a pointer to an entry in a hashed symbol-table, containing strings. The syntax is the same as for strings.

Symbols and strings are largely interchangeable as far as your program is concerned, but Visual Prolog stores them differently. Symbols are kept in a look-up table, and their addresses, rather than the symbols themselves, are stored to represent your objects. This means that symbols can be matched very quickly, and if a symbol occurs repeatedly in a program, it can be stored very compactly. Strings are not kept in a look-up table; Visual Prolog examines them character-by-character whenever they are to be matched. You must determine which domain will give better performance in a particular program.

The following table gives some examples of simple objects that belong to the basic standard domains.

Table 3.3: Simple Objects

"&&", caitlin, "animal lover", b_l_t

(symbol or string)

-1, 3, 5, 0

(integer)

3.45, 0.01, -30.5, 123.4e+5

(real)

'a', 'b', 'c'  '/', '&'

(char)

Typing Arguments in Predicate Declarations

Declaring the domain of an argument in the predicates section is called typing the argument. For example, suppose you have the following relationship and objects:

    Frank is a male who is 45 years old.

The Prolog fact that corresponds to this natural language relation might be

    person(frank, male, 45).

In order to declare person as a predicate with these three arguments, you could place the following declaration in the predicates section:

    person(symbol, symbol, unsigned)

Here, you have used standard domains for all three arguments. Now, whenever you use the predicate person, you must supply three arguments to the predicate; the first two must be of type symbol, while the third argument must be an integer.

If your program only uses standard domains, it does not need a domains section; you have seen several programs of this type already.

Or, suppose you want to define a predicate that will tell you the position of a letter in the alphabet. That is,

    alphabet_position(Letter, Position)

will have Position = 1 if Letter = a, Position = 2 if Letter = b, and so on. The clauses for this predicate would look like this:

    alphabet_position(A_character, N).

If standard domains are the only domains in the predicate declarations, the program does not need a domains section. Suppose you want to define a predicate so that the goal will be true if A_character is the Nth letter in the alphabet. The clauses for this predicate would look like this:

    alphabet_position('a', 1).
    alphabet_position('b', 2).
    alphabet_position('c', 3).
    ...
    alphabet_position('z', 26).

You can declare the predicate as follows:

    PREDICATES
        alphabet_position(char, unsigned)

and there is no need for a domains section. If you put the whole program together, you get

    PREDICATES
       alphabet_position(char, integer)

    CLAUSES
       alphabet_position('a', 1).
       alphabet_position('b', 2).
       alphabet_position('c', 3).
       /* ... other letters go here ... */
       alphabet_position('z', 26).

Here are a few sample goals you could enter:

    alphabet_position('a', 1).
    alphabet_position(X, 3).
    alphabet_position('z', What).

Exercises

Program 4 is a complete Visual Prolog program that functions as a mini telephone directorytelephone directory. The domains section is not needed here, since only standard domains are used.

/* Program ch03e04.pro */

To illustrate the char domain, program 5 defines isletter, which, when given the goals

    isletter('%').
    isletter('Q').

will return No and Yes, respectively.

/* Program ch03e05.pro */

Multiple Arity

The arity of a predicate is the number of arguments that it takes. You can have two predicates with the same name but different arity. You must group different arity versions of a given predicate name together in both the predicates and clauses sections of your program; apart from this restriction, the different arities are treated as completely different predicates.

/* Program ch03e06.pro */

Rule Syntax

Rules are used in Prolog when a fact depends upon the success (truth) of another fact or group of facts. As we explained in Chapter 2, a Prolog rule has two parts: the head and the body. This is the generic syntax for a Visual Prolog rule:

    HEAD :- <Subgoal>, <Subgoal>, ..., <Subgoal>.

The body of the rule consists of one or more subgoals. Subgoals are separated by commas, specifying conjunction, and the last subgoal in a rule is terminated by a period.

Each subgoal is a call to another Prolog predicate, which may succeed or fail. In effect, calling another predicate amounts to evaluating its subgoals, and, depending on their success or failure, the call will succeed or fail. If the current subgoal can be satisfied (proven true), the call returns, and processing continues on to the next subgoal. Once the final subgoal in a rule succeeds, the call returns successfully; if any of the subgoals fail, the rule immediately fails.

To use a rule successfully, Prolog must satisfy all of the subgoals in it, creating a consistent set of variable bindings as it does so. If one subgoal fails, Prolog will back up and look for alternatives to earlier subgoals, then proceed forward again with different variable values. This is called backtracking. A full discussion of backtracking and how Prolog finds solutions is covered in Chapter 4.

Prolog if Symbol vs. IF in Other Languages

As we have mentioned earlier, the :- separating the head and the body of a rule, is read "if". However, a Prolog if differs from the IF written in other languages, such as Pascal.

In Pascal, for instance, the condition contained in the IF statement must be met before the body of the statement can be executed; in other words,

"if HEAD is true, then BODY is true  (or:  then do BODY)"

This type of statement is known as an if/then conditional. Prolog, on the other hand, uses a different form of logic in its rules. The head of a Prolog rule is concluded to be true if (after) the body of the rule succeeds; in other words,

"HEAD is true if BODY is true  (or:  if BODY can be done)"

Seen in this manner, a Prolog rule is in the form of a then/if conditional.

Automatic Type Conversions

When Visual Prolog matches two variables, it's not always necessary that they belong to the same domain. Also, variables can sometimes be bound to constants from other domains. This (selective) mixing is allowed because Visual Prolog performs automatic type conversion (from one domain to another) in the following circumstances:

An argument from a domain my_dom declared in this form

    DOMAINS
        my_dom = <base domain>
/*<base domain> is a standard domain */

can mix freely with arguments from that base domain and all other standard domains that are compatible with that base domain. (If the base domain is string, arguments from the symbol domain are compatible; if the base domain is integer, arguments from the real, char, word, etc., domains are compatible.

These type conversions mean, for example, that you can

call a predicate that handles strings with a symbol argument, and vice versa

call a predicate that handles reals with an integer argument

call a predicate that handles characters with integer values

use characters in expressions and comparisons without needing to look up their ASCII values.

There are a number of rules deciding what domain the result of the expression belongs to, when different domains are mixed. These will be detailed in chapter 9.