Program Sections

A Visual Prolog program consists of several program sections. Each program section is identified by a keyword, as shown in this table.

Table 17.1: Contents of Program Sections

Section

Contents

compiler options

Options are given at the top of a program.

constants section

Zero or more constants.

domains section

Zero or more domain declarations.

facts section

Zero or more database predicates.

Class section

Zero or more class declarations

Implement section

Zero or more implementations of class-predicates

predicates section

Zero or more predicate declarations.

goal section

Zero or one goal.

clauses section

Zero or more clauses.

To generate an executable stand-alone application, your program must contain a goal. Usually, a program requires at least a predicates and a clauses section. For most programs, a domains section is needed to declare lists, compound structures and your own names for the basic domains.

For modular programming, you can prefix the keywords domains, predicates and database with the word global, indicating that the subsequent declarations affect several program modules globally. (Modular programming is discussed on page 257).

A program can contain several domains, predicates, database or clauses sections, provided you observe the following restrictions:

Constants, domains and predicates should be defined before you use them. However, within the domains section you can refer to domains that are declared at a later point.

Only one goal must be met during compilation. However, the goal can appear anywhere.

All clauses that describe the same predicate must occur in sequence (one after the other).

All global declarations must come before any local declarations.

The database sections can be named, but a given name can only appear once. Because the default name is dbasedom, there can only be one unnamed database section.

1. The Domains Section

A domains section contains domain declarations. Five generic formats are used:

    name = d                                                       /*standard domain*/
    mylist = elementDom*
                                              /*list domain*/
    my_CompDom = f1(d11,d12,...,d1n);
      /*compound object domain*/
                           f2(d21,d22,...,d2n);
                           ...

    predefdom = name1;name2;...;nameN
                                                 /*eg db_selector and file domains*/
    pclass = determspec args flow langspec
                     
                                /* predicate class declaration */

(1) Standard Domains

    name = d

This declaration specifies a domain, name, which consists of elements from a standard domain type d; the domain type d must be char, real, ref, string,  symbol, or one of the integral domains.

This declaration is used for objects that are syntactically alike but semantically different. For instance, NoOfApples and HeightInFeet could both be represented as integers, and consequently be mistaken for one another. You can avoid this by declaring two different domains of integer type, like this:

    apples, height = integer

Declaring different domains in this way allows Visual Prolog to perform domain checks to ensure, for example, that apples and height are never inadvertently mixed. However both domains can interchangeably be mixed with integers, and you can use the equal sign to convert between NoOfApples and HeightInFeet.

(2) List Domains

    mylist = elementDom*

This is a convenient notation for declaring a list domain. mylist is a domain consisting of lists of elements, from the domain elementDom. The domain elementDom can be either a user-defined domain, or one of the standard types of domain. You read the asteriskasterisk as "list". For example, this domain declaration:

    numberlist = integer*

declares a domain for lists of integers, such as [1, -5, 2, -6].

(3) Compound Object Domains

    myCompDom=f1(d11, .., d1N); f2(d21, d22 ..); ...

To declare a domain that consists of compound objects, you state a functor and the domains for all the subcomponents.

For example, you could declare a domain of owners made up of elements like this:

    owns(john, book(wuthering_heights, bronte))

with this declaration:

    owners = owns(symbol, book)
    book = book(symbol,symbol)]

where owns is the functor of the compound object, and symbol and book are domains of the subcomponents.

The right side of this type of domain declaration can define several alternatives, separated by a semicolon (;). Each alternative must contain a unique functor and a description of the domains for the actual subcomponents of the functor. For example, the following domain declaration could be used to say, "For some predicates a key is either up, down, left, right or a character value."

    key = up; down; left; right; char(char)

There is a possibility to include a comment after the domain, for instance

    person= p(string name, integer age).

(4) File Domain

    file = name1;name2;...;nameN

A file domain must be defined when you need to refer to files (other than the predefined ones) by symbolic names. A program can have only one domain of this type, which must be called file. Symbolic file names are then given as alternatives for the file domain. For example, this declaration:

    file = sales ; salaries

introduces the two symbolic file names sales and salaries.

The following alternatives are predefined in the file domain:

    keyboard         stdin
    screen
             stdout
    stderr

(5) Specially Handled Predefined Domains

There are several predefined domains; some are handled specially, like the file domain and the db_selector domain. Here's a summary of these special predefined domains:

Table 17.2: Specially Handled Predefined Domains

dbasedom

generated domain for terms in the global database

bt_selector

returned binary tree selector

db_selector

user-defined external database selectors

place

in_memory; in_ems; in_file

accesmode

read; readwrite

denymode

denynone; denywrite; denyall

ref

domain for database reference numbers

file

symbolic file names

reg

reg(AX,BX,CX,DX,SI,DI,DS,ES) used with bios/4

bgi_ilist

list of integers used in the BGI predicates.

(6) Shortening Domain Declarations

As shown in the standard domain declaration name=d, the left side of a domain declaration (except for a file domain) can consist of a list of names, like this:

    mydom1, mydom2, ... , mydomN = ...

This feature allows you to declare several domains at the same time.

    firstname, lastname, address = string

(7) Declaring Reference Domains

A reference domain is one that can carry unbound variables as input arguments.  To declare a reference domain, precede the right side of the domain declaration with the keyword reference. When you declare a compound domain as a reference domain, all its subdomains are automatically declared as reference domains.

DOMAINS
    reflist = reference refint*
    refint
  = reference integer
    term
    = reference int(refint); symb(refsymb)
    refsymb = reference symbol

(8) Declaring Predicate Domains

A predicate domain declares a group or class of predicates. In a subsequent predicate declaration you may then declare one or more predicates as belonging to such a group, and these may then be specified as arguments to other predicates. Those other predicates will hence be able to do a variable call.

The declaration for a predicate domain is of the form:

    pdom = { determ | nondeterm } [ domain ] arglist
                 [ - flowpattern ] [ language ]

(curly braces indicate "choose one", square brackets indicate optional items) where

    domain is the return domain, if you're declaring a function

    arglist is of the form
            ( [ domain [ , domain ]* ] )

    flowpattern is of the form
               ( flow )
        where flow is
               { i | o | functor flowpattern | listflow }
        where listflow is
               '[' flow [ , flow ]* [ '|' { i | o | listflow } ] ']'

    language is of the form
        language { prolog | c | pascal | asm | stdcall | syscall }

The language specification tells the compiler which calling convention to use, and is only required when declaring domains for routines written in other languages (see the chapter on foreign language interface). The calling convention defaults to pascal if omitted, but this should not be relied upon if a particular convention is desired.

The flowpattern specifies how each argument is to be used. It should be the letter i for an argument with input flow, the letter o for one with output flow, a functor and flowpattern for a compound term (e.g. (i,o,myfunc(i,i),o) ), or a listflow (e.g.  [i,myfunc(i,o),o] or [o,o|i] ).

You can have no more than one flowpattern declaration for a predicate pointer domain, and it must be given unless the argument list is empty or all arguments have input flow.

Hence, the declaration for a group of deterministic predicates taking an integer as argument and returning an integer, would be:

    DOMAINS
        list_process = determ integer (integer) - (i)

This group, or class, is now known as list_process.

2. The Predicates Section

In Visual Prolog, the sections introduced by the keyword predicates contain predicate declarations. You declare a predicate by its name and the domains of its arguments, like this:)

    PREDICATES
        predname(domain1, domain2,...,domainN)

In this example, predname represents the new predicate name and domain1, ..., domainN stand for user-defined domains or pre-defined domains. Multiple declarations for one predicate are also allowed. As an example, you could declare that the predicate member works both on numbers and names by giving the following declarations:

    PREDICATES
        member(name, namelist)
        member(number, numberlist)

In this example, the arguments name, namelist, number, and numberlist are user-defined domains.

You can declare a predicate with several different arities.

    hanoi                 % chooses 10 slices as default
    hanoi(integer)
     % moves N slices

If you give more than one declaration for the same name, these declarations must come right after each other.

You can declare predicates as being deterministic by preceding the predicate declaration with determ, or you can declare a predicate as being non-deterministic by preceding the declaration by nondeterm. If you declare a predicate to be deterministic, the compiler will issue a warning if it finds any non-deterministic clauses for the predicate. This functions exactly as if you had used the general compiler directive check_determ. On the other hand, when you declare a predicate as non-deterministic, the compiler will not complain when you add check_determ for checking the other predicates.

    nondeterm repeat       /*repeat is non-deterministic by design*/
    determ menuact(Integer,String)
       /*menuact is deterministic*/

Note that predicates also can be preceded with the following keywords:

Multi: The keyword multi defines non-deterministic predicates that can backtrack and generate multiple solutions. Predicates declared with the keyword multi always succeed (never fail) and, therefore, always have at least one solution.

Failure: A predicate declared with the keyword failure should always fail. Therefore, such a predicate does not produce a solution. In Visual Prolog failure predicates always enforce a program to backtrack to the nearest backtracking point.

Erroneous: A predicate declared with the keyword erroneous should never fail and should not produce solution. Typical used for errorhandling purposes.

(1) Predicate Classes

If you have declared a predicate domain in the domain section, you may declare one or more predicates as belonging to that domain. The syntax for this is.

    PREDICATES
        pred1: p_domain
        pred2: p_domain
        ...

where pred1, pred2 etc. are the predicate names and p_domain is the predicate domain declared in the domain section.

(2) Functions

By prefixing a predicate declaration with a domain name, you declare a function. The return value is taken from the last argument in the final clause executed, and this argument must not be present in the predicate declaration. A function returning the cube of its argument would hence be declared as:

    PREDICATES
        integer cube(integer)

And the clause for this function would be:

    CLAUSES
        cube(In,Out):- Out = In*In*In.

A function can return any domain.

3. The Facts/Database Section

A facts database section declares predicates just as the predicates section does. However, the clauses for database predicates can only consist of plain facts, they cannot have an associated body. These facts can be inserted at run time by assert, asserta, assertz, or consult, and you can remove them again with retract or retractall. You can have a number of database sections in your program; some of them can be global and some local. You should name your program's database sections, and each name must be unique within the module. If you don't give a name for a database section, the compiler will give it the default name dbasedom. Only one unnamed database is possible. You can precede a database predicate with determ if you know that there will be only one fact for that predicate. This enables the compiler to produce better code, and you will not get non-deterministic warnings for calling such a predicate. This is useful for flags, counters, and other things that are essentially global variables.

When a database section is declared, the compiler will internally declare a corresponding domain with the same name as the name of the database section; this allows predicates to handle facts as terms.

The form of a facts section is:

    [global] DATABASE[ - <databasename> ]
        [determ|single|nocopy] dbpred1(....)
        dbpred2(.....)

An example is:

    FACTS - tables
        part(name,cost)
        salesperson(name,sex)

    PREDICATES
        write_table_element(tables)

    CLAUSES
        write_table_element(part(Name,Cost)):-
            writef("¡¬nPart's Name= % Cost = %",Name,Cost).
        write_table_element(salesperson(Name,Sex)):-
            writef("¡¬nSalesperson's Name= % Sex = %",Name,Sex).

4. The Clauses Section

A clause is either a fact or a rule corresponding to one of the declared predicates. In general, a clause consists of either 1) a fact or 2) a clause head followed first by a colon and hyphen (:-), then by a list of predicate calls separated by commas or semicolons. Both facts and rules must be terminated by a period (.).

The fact:

    same_league(ucla, usc).

consists of a predicate name (same_league), and a bracketed list of arguments (ucla, usc).

(1) Simple Constants

Simple constants belong to one of the following standard domains:

char

A character (an 8-bit ASCII character enclosed between a pair of single quotation marks) belongs to the char domain.

An ASCII character is indicated by the escape character (¡¬) followed by the ASCII code for that character. ¡¬n, ¡¬t, ¡¬r produce a newline , a tab and a  carriage return character, respectively. A backslash (¡¬) followed by any other character produces that character ('¡¬¡¬' produces ¡¬ and '¡¬'' produces ').

integral numbers

 

positive and negative numbers can be represented in the Visual Prologs integral number domains shown in the following table.

real

A real number belongs to the real domain and is a number in the range -)1e-307 to -)1e+308. real numbers.

Real numbers are written with a sign, a mantissa, a decimal point, a fractional part, an e, a sign, and an exponent, all without included spaces. For example, the real value -12345.6789 * 1014 can be written as -1.23456789e+18.

The sign, fractional, and exponent parts are optional (though if you omit the fractional part, you must leave out the decimal point, too). Visual Prolog automatically converts integers to real numbers when necessary.

string

A string (any sequence of characters between a pair of double quotation marks) belongs to the string domain. Strings can contain characters produced by an escape sequence (as mentioned under char); strings can be up to 64 K in length.

symbol

A symbolic constant (a name starting with a lower-case letter) belongs to the symbol domain type.

Strings are accepted as symbols too, but symbols are kept in an internal table for quicker matching. The symbol table takes up some storage space, as well as the time required to make an entry in the table. However, if the same symbols are frequently compared, it's well worth the investment.

binary

A binary constant belongs to the binary domain. It is written as a comma-separated list of integral values, each less than or equal to 255, enclosed in square brackets prefixed with a dollar sign: $[1,0xff,'a'].

predicate pointer

A predicate pointer is the name of a predicate previously declared as belonging to a predicate pointer domain. It is written simply as the name of the predicate, with no argument list or brackets.

Table 17.3:  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

 

 

 

 

 

 

 

 

 

 

 

 

An integral value may be preceded by 0x or 0o, indicating hexadecimal and octal syntax respectively.

(2) Terms

A term is, strictly speaking, any Prolog entity. In practice we tend to mean those (variable) entities holding data or non-compiled information, or compound terms (consisting of a functor and optional arguments).

(3) Variables

Variables are names starting with an upper-case letter or underscore or, to represent the anonymous variable, a single underscore character underscore character). The anonymous variable is used when the value of that variable is not of interest. A variable is said to be free when it is not yet associated with a term, and bound or instantiated when it is unified with a term.

The Visual Prolog has a option so it can give a warning when it detects that a variable has been used only once in a clause. This warning will not be given if the variable starts with an underscore. Note that when a variable name starts with an underscore like _Win, it is still a normal variable, that unlike the anonymous variable can be used to pass values from one call to another.

(4) Compound Objects

A compound object is a single object that consists of a collection of other objects (called subcomponents) and a describing name (the functor). The subcomponents are enclosed in parentheses and separated by commas. The functor is written just before the left parenthesis. For example, the following compound term consists of the functor author and three subcomponents:

    author(emily, bronte, 1818)

A compound object belongs to a user-defined domain. The domain declaration corresponding to the author compound object might look like this:

    DOMAINS
        author_dom = author(firstname, lastname, year_of_birth)
        firstname, lastname = symbol
        year_of_birth = integer

Functorless Compound Objects

By prefixing a compound object declaration with the directive struct, you declare a functorless object.

    DOMAINS
        author_dom = struct author(firstname, lastname, year_of_birth)

The internal representation of such an object has no functor and there can be no alternatives in a functorless domain. Functorless terms can be used just like other terms in your source code, but their primary aim is to be directly compatible with C structs.

Lists--A Special Kind of Compound Object

Lists are a common data structure in Prolog and is actually a form of compound object. Syntactically, it is written as a sequence of comma-separated arguments, enclosed in square brackets. A list of integers would appear as follows:

    [1, 2, 3, 9, -3, 2]

Such a list belongs to a user-defined domain, such as:

    DOMAINS
        ilist = integer*

If the elements in a list are of mixed types (for example, a list containing both characters and integers), you must state this in a corresponding domain declaration. For example, the following declarations

    DOMAINS
        element = c(char) ; i(integer)
        list = element*

would allow lists like this one:

    [i(12), i(34), i(-567), c('x'), c('y'), c('z'), i(987)]

Memory Alignment

By prefixing a compound or list declaration with an alignment specification, you can override the default alignment. The syntax is:

    DOMAINS
        dom = align { byte | word | dword } domdecl

where domdecl is a normal domain declaration:

    DOMAINS
        element = align byte c(char) ; i(integer)
        list = align dword element*

This would make the internal representation for elements byte-aligned and list dword-aligned.

If you want to override the default alignment for a functorless domain, the struct directive must precede the align directive.

    DOMAINS
        bbdom = struct align byte blm(char,integer)

The primary aim of overriding alignment is to make compound objects compatible with external code using a different alignment than the default for your platform. If several program share an external database or communicate over pipes, the domains involved must use the same alignment.

5. The Constants Section

You can define and use constants in your Visual Prolog programs. A constant declaration section is indicated by the keyword constants, followed by the declarations themselves, using the following syntax:

    <Id> =  <definition>

Each <definition> is terminated by a newline character, so there can be only one constant declaration per line. Constants declared in this way can then be referred to later in the program.

Consider the following program fragment:

    CONSTANTS
        blue
  = 1
        green = 2
        red
   = 4
        grayfill = [0xaa, 0x55, 0xaa, 0x55, 0xaa, 0x55, 0xaa, 0x55 ]
        language = english
        project_module = true

Before compiling your program, Visual Prolog will replace each constant with the actual string to which it corresponds. For instance:

    ...
    menu_colors(red,green,blue),
    my_fill_pattern(grayfill),
    text_convert(prolog, language),
    status(project_module),
    ...

will be handled by the compiler in exactly the same way as:

    ...
    menu_colors(4, 2, 1),
    my_fill_pattern([0xaa, 0x55, 0xaa, 0x55, 0xaa, 0x55, 0xaa, 0x55]),
    text_convert(prolog, english),
    status(true),
    ...

There are a few restrictions on the use of symbolic constants.

The definition of a constant can't refer to itself. For example:

    list = [1, 2|list].                      /* Is not allowed  */

will generate the error message Recursion in constant definition. The system does not distinguish between upper-case and lower-case in a constant declaration. Consequently, when a constant identifier is used in the clauses section of a program, the first letter must be lower-case to avoid ambiguity with variables. So, for example, the following is a valid construction:

CONSTANTS
   Two = 2

GOAL
   A=two, write(A).

There can be several constants sections in a program, but each constant must be declared before it is used.

Constant identifiers are global for the rest of the file and can only be declared once. Multiple declarations of the same identifier will result in an error message. You can use constants to redefine names of domains and predicates, except the specially-handled predicates. Refer to "Specially-Handled Predicates" earlier in this chapter.

(1) Predefined Constants

Depending on the target platform selected for compilation, one or more constants will be predefined:

Table 17.4: Predefined Constants

Constant

Target selections causing it to be defined

os_dos

os_os2

os_nt

os_unix

ws_win

ws_pm

ws_motif

dosx286

platform_16bit

platform_32bit

DOS, Phar Lap and Windows

OS/2 or PM

Windows 95 or Windows NT 32bit mode

XENIX, UNIX and Motif

MS Windows

Presentation Manager

Motif

Phar Lap286

16-bit platforms

32-bit platforms

Selecting DOS as your target will cause os_dos to be defined, and selecting MS Windows will cause both os_dos and ws_win to be defined.

These predefined constants enable you to control platform-dependent conditional compilation.

6. Conditional Compilation

You use conditional compilation when you need to generate different versions of the same program; for example, one version that uses graphics and another that only uses text mode. The syntax for conditional compilation directives is:

    [ifdef | ifndef] <constantID>
        ...
    elsedef
        ...
    enddef

<constantID> represents a constant identifier declared in a constants section. The value of the constant is irrelevant; only its presence matters. The ifdef directive succeeds if the constant is defined, while the ifndef directive succeeds if the constant is not defined. The elsedef part is optional. The following program shows a typical use of the conditional compilation directives.

    CONSTANTS
        restricted = 1
    ifdef restricted
         /* if restricted is defined, use this */

    savebase(_):-
        write("¡¬nBase cannot be saved in demo version"),
        readchar(_).

    elsedef                                 /* otherwise, use this */

    savebase(Name):-
        write("¡¬nSaving ",Name),
        save(Name).

    enddef