Difference between revisions of "Language Reference Book"

From wiki.visual-prolog.com

(No difference)

Revision as of 13:46, 30 June 2017


This document describes the syntax and semantics of the Visual Prolog programming language.

Visual Prolog is a strongly typed object oriented programming language based on the logical programming language Prolog.

A Visual Prolog program consists of a goal and a number of:

Which contain declarations and definitions of Prolog entities:

The "actual" code of a Visual Prolog is the clauses, which are located in class implementations and which implements predicates.

Basic Concepts

Types and Subtypes

Types

Visual Prolog types are divided into object types and value types. Objects have mutable state, whereas values are immutable.

Object types are defined by interface definitions.

The value types include numerical types, strings, character types, and compound domains (also known as algebraic data types). Simpler forms of compound domains are structure and enumeration types, whereas more complex forms represent tree structures.

Subtypes

Types are organized in a subtype hierarchy. Subtypes provide subsumption polymorphism: any context that expects a value of some type will also accept a value of any subtype. Equivalently, values of a given type are implicitly converted to any super-type where needed; no explicit cast is required.

Subtypes can be derived from any value type, except from algebraic data types. Types derived from algebraic data types are synonym types rather than subtypes (i.e., they denote the same type).

The notion of subtypes relates to the notion of subsets. However, even if a type is "mathematically" a subset of another type, it is not a subtype unless declared as such.

domains
    t1 = [1..17].
    t2 = [5..13].
    t3 = t1 [5..13].

t1 is an integral type whose values are the integers from 1 to 17 (inclusive). Likewise, t2 contains the values from 5 to 13. So t2 is a subset of t1, but t2 is not a subtype of t1. By contrast, t3 (which contains the same values as t2) is a subtype of t1, because it is declared to be so.

The language contains a few implicit subtype relations; otherwise, subtype relations are stated explicitly in type definitions.

Object types are organized in a subtype hierarchy rooted in the predefined object type object, i.e., any object type is a subtype of object. Object subtypes are formed by stating that one interface supports another. If an object has an interface/object type that supports another interface, the object also has that type and can be used as such without further changes.

See also: Universal and Root Types

Object System

External View

This section clarifies the class-related notions in Visual Prolog at a conceptual level. It does not discuss syntax or implementation details.

The class concept in Visual Prolog is based on three semantic entities:

  • objects
  • interfaces
  • classes
Object

An object is a set of named object member predicates together with a set of supported interfaces. Objects also have state, but this state can only be observed and changed through member predicates; the state is therefore encapsulated in the object.

Interface

An interface is an object type. It has a name and defines a set of named object predicates.

Interfaces form a supports hierarchy (a semi-lattice) rooted at the object interface. If an object has a type denoted by some interface, it also has the types of all supported interfaces. Thus the supports hierarchy is a type hierarchy: an interface is a subtype of each interface it supports.

Class

A class is a named object factory; it constructs objects that correspond to a given interface. If a class constructs objects of interface iii, then its objects are "iii objects". All objects constructed by the same class share the same definitions of the object member predicates, but each object has its own state; the predicate definitions belong to the class, while the state belongs to each object.

The set of object member predicates a class defines is the union of the predicates declared (transitively) in its interfaces. If the same predicate is declared in multiple interfaces, the class provides one common definition; this is only valid if the intended semantics coincide. Interface support must be specified explicitly.

Module

A class need not construct objects. A class without a construction type acts as a module: it may have only class members and class state.

Identity

Every object is unique. Even if two objects currently have identical state, they are not identical: one can be changed without affecting the other. We never access object state directly; we access it through references, and many references may denote the same object. Classes and interfaces are also unique and identified by name (with namespace); duplicate names are not allowed within a program. Structural equality does not imply identity for objects, classes, or interfaces.

Internal View

This section complements the external view with internal aspects: how declarations and implementations are organized. From a programmatic point of view, classes are central (they contain the code). Interfaces have mainly static importance and have no direct runtime representation; objects are dynamic and exist only when the program runs.

A class has a declaration and an implementation. The declaration states the public accessible parts of the class and of the objects it constructs; the implementation defines what the declaration introduces (predicates are implemented by clauses, by inheritance, or resolved to external libraries). A class declaration is purely declarative.

An implementation can declare additional private entities (domains, predicates, etc.). Object state is stored as facts in the implementation; such facts are per-object, while class facts are shared across all objects of the class. Facts are declared only in implementations and are not directly accessible from outside. Implementations may also (privately) support more interfaces than stated in the declaration.

Code Inheritance

Code inheritance occurs only in class implementations. Visual Prolog supports multiple inheritance via an inherits section in the implementation. The classes you inherit from are parent (super) classes; the inheriting class is the child (sub) class. A child class can only access its parent classes through their public interfaces; it receives no special privileges.


Scoping & Visibility

Name Categories

All names (identifiers) in Visual Prolog are syntactically divided into two major groups:

  • Constant names (starting with a lowercase letter)
  • Variable names (starting with an uppercase letter or an underscore)

Constant names (identifiers) are divided into the following categories:

  • Type names (i.e., domains and interfaces)
  • Domain carriers (i.e., classes and interfaces)
  • Names without parentheses (i.e., constants, fact variables of non-function type, and nullary-functors)
  • Value-returning names of arity N (i.e., functions, functors, and fact variables of function type)
  • Non-value-returning names of arity N (i.e., predicates, facts, and fact variables of predicate type)

Visual Prolog requires that names do not conflict at the point of declaration; otherwise, conflicts cannot be resolved at the point of use. Declarations can only conflict if they are in the same scope, because scope qualification can resolve conflicts. A name in one category can never conflict with a name in another category, but a single declaration can place a name in several categories.

Packages

Packages are the basic units of code organization in Visual Prolog. They group related interfaces and classes.

Each declaration or implementation of an interface or class in a package is placed in a separate file. Each filename matches the interface or class that it declares or implements. All package files are stored in the package directory; subpackages are stored in subdirectories of that directory.

Packages can act as class libraries. You can include packages in your program instead of placing all used interfaces and classes directly in the program.

How packages are structured and included in projects is described in the IDE documentation (see Creating a Package in Creating New Project Items).

Visibility, Shadowing, and Qualification

Most scoping rules were introduced above; this section completes the picture.

An interface definition, a class declaration, and a class implementation are scopes (scopes cannot be nested). An implementation (privately) extends the scope of the corresponding class declaration. Visibility is the same everywhere in a scope; i.e., no matter where something is declared in the scope, it is visible in the whole scope.

Public names from supported interfaces and super-classes are directly (i.e., without qualification) available inside a scope when their origin is unambiguous. It is illegal to use a name whose origin is ambiguous. Ambiguities in predicate calls can be removed by qualifying the predicate name with the class name (e.g., cc::p).

This qualification is also used to qualify calls to object member predicates of super-classes on the current object.

Visual Prolog has the following shadowing hierarchy:

  • Local
  • Opened scopes and super-classes

Opened scopes have the same status as super-classes. Local declarations shadow declarations in opened scopes. If two or more opened scopes contain conflicting declarations, you can only access them by using qualification.

Example Assume the interface ixx and the classes aa and bb:
interface ixx
 
predicates
    p1 : ().
    p2 : ().
    p3 : ().
 
end interface ixx
 
%========================
 
class aa : ixx
end class aa
 
%========================
 
class bb
 
predicates
    p3 : ().
    p4 : ().
    p5 : ().
 
end class bb

The class aa creates objects of type ixx, whereas the class bb does not create objects at all.

In this context consider the implementation of a class cc:

implement cc inherits aa
    open bb
 
clauses
    p2(). % reimplementation of ixx::p2
 
predicates
    p5 : ().
clauses
    p5().
 
clauses
    new() :-
        p1(), % aa::p1
        p2(), % cc::p2 (shadows aa::p2)
        aa::p2(), % aa::p2
        p3(), % Illegal ambiguous call: aa::p3 or bb::p3
        aa::p3(), % aa::p3
        bb::p3(), % bb::p3
        p4(), % bb::p4
        p5(). % cc::p5 (shadows bb::p5)
 
end implement cc
Since cc inherits aa, all predicates in the interface ixx are visible in cc. Likewise, the open bb directive makes all predicates in bb visible in cc.

Lexical Elements

The Visual Prolog Compiler is applied to a source file. This source file may include other source files, which are (conceptually) inserted into the original source file to constitute one compilation unit. The compilation of a compilation unit is done in two conceptual steps:

  • first the input is transformed into a sequence of tokens;
  • and then these tokens are syntactically analyzed and transformed into executable code.

The lexical analysis of the program will break the compilation unit CompilationUnit into a list of input elements InputElement

CompilationUnit:
   InputElement-list
InputElement:
   Comment
   WhiteSpace
   Token

Only tokens are significant to the subsequent syntax analysis.

Comments

A Visual Prolog comment is written in one of the following ways:

  • The /* (slash, asterisk) characters, followed by any sequence of characters (including new lines), terminated by the */ (asterisk, slash) characters. These comments can be multi-lined. They can also be nested.
  • The % (percent sign) character, followed by any sequence of characters. Comments that begin with character % (percent sign) continue until the end of the line. Therefore, they are commonly called single-line comments.

Notice the following comment example:

/* Begin of Comment1
   % Nested Comment2 */ Comment 1 is not terminated (single-line comment)
   This is the real termination of Comment1 */

Whitespace

WhiteSpace:
   Space
   Tab
   NewLine

Here Space is a space character, Tab is a tabulation character and NewLine is a new line character.

Tokens

Token:
   Identifier
   Keyword
   Punctuator
   Operator
   Literal

Identifiers

Identifier:
   LowercaseIdentifier
   UppercaseIdentifier
   AnonymousIdentifier
   Ellipsis

A LowercaseIdentifier is a sequence of letters, digits, and underscores that starts with a small letter. An UppercaseIdentifier is a sequence of letters, digits, and underscores that starts either with a capital letter or with an underscore.

AnonymousIdentifier :    _
Ellipsis :
   ...

Keywords

Keywords are divided into major and minor keywords, this division is only cosmetic however, there is no formal difference between major and minor keywords. In the sequel we will however use different coloring for them.

Keyword :
   MajorKeyword
   MinorKeyword
MajorKeyword : one of
   class clauses constants constructors
   delegate domains
   end
   facts
   goal
   implement inherits interface
   monitor
   namespace
   open
   predicates
   properties
   resolve
   supports
   where
MinorKeyword : one of
   align and anyflow as 
   bitsize
   catch
   determ digits div do
   else elseif  erroneous externally
   failure finally foreach from
   guard
   if in 
   language
   mod multi
   nondeterm
   otherwise or orelse
   procedure
   quot
   rem
   single
   then to try

All keywords except as and language are reserved words.

end is always combined with another key word:

end class
end implement
end interface
end if
end foreach
end try

Punctuation Marks

Punctuation marks in Visual Prolog have syntactic and semantic meaning to the compiler, but do not specify by themselves an operation that yields a value. Some punctuation marks, either alone or in combinations, can also be Visual Prolog operators.

Punctuation marks are:

PunctuationMarks: one of
   ;    !    ,    .    #    [    ]    |    (    )    {    }    :-    :    ::

Operators

Operators specify an evaluation to be performed on involved operands.

Operators: one of
   ^
   /    *  div mod quot rem
   +    -
   =    <    >    <>    ><    <=    >=    :=    ==
   ~~   ++    **    ^^    >>    <<

div, mod, quot and rem are reserved words.

Literals

Literals fall into following categories: integer, character, floating-point, string, binary and list.

Literal:
   IntegerLiteral
   RealLiteral
   CharacterLiteral
   StringLiteral
   BinaryLiteral

Integral Literals

IntegerLiteral:
   UnaryPlus-opt    DecimalDigit-list
   UnaryMinus-opt   DecimalDigit-list
   UnaryPlus-opt    OctalPrefix OctalDigit-list
   UnaryMinus-opt   OctalPrefix OctalDigit-list
   UnaryPlus-opt    HexadecimalPrefix HexadecimalDigit-list
   UnaryMinus-opt   HexadecimalPrefix HexadecimalDigit-list
 
UnaryPlus:
   +
 
UnaryMinus:
   -
 
OctalPrefix:
   0o
 
OctalDigit: one of
   0 1 2 3 4 5 6 7
 
DecimalDigit: one of
   0 1 2 3 4 5 6 7 8 9
 
HexadecimalPrefix:
   0x
 
HexadecimalDigit: one of
   0 1 2 3 4 5 6 7 8 9 A a B b C c D d E e F f

An integral literal can belong to integer or unsigned domains and it should not exceed maximum and minimum integer or unsigned values.

Example Here are some examples of integral literals
100
-100
 
0o77 % Octal
-0o17
 
0xFF % Hexadecimal
-0x5A

Real Literal

RealLiteral:
   UnaryMinus-opt DecimalDigit-list FractionOfFloat-opt Exponent-opt
 
FractionOfFloat:
   . DecimalDigit-list
 
Exponent:
   ExponentSymbol ExponentSign-opt DecimalDigit-list
 
ExponentSymbol: one of
   e E
 
ExponentSign: one of
   - +

A real literal should not exceed maximum and minimum real values. Notice that any integral literal can also be used as a real value.

Example Some real literals
0.5
.5
1.23e-12
-10.25

Character Literals

CharacterLiteral:
   ' <CharacterValue> '

CharacterValue can be any printable character or an escape sequence:

  • \\ representing \
  • \t representing Tab character
  • \n representing New Line character
  • \r representing carriage return
  • \' representing single quote
  • \" representing double quote
  • \uXXXX, here XXXX should be exactly four HexadecimalDigit's representing the Unicode character corresponding to the digits.
Example Some character literals
'a'
'\t' % TAB character

String Literals

StringLiteral:
   StringLiteralPart-list
StringLiteralPart:
   ' <CharacterValue>-list-opt '
   " <CharacterValue>-list-opt "
   @AtOpenChar AnyCharacter-list-opt AtCloseChar

A string literal consists of one or more StringLiteralPart's, which are concatenated.

The first two forms (the ' and " forms) uses escape sequences to express certain characters

  • \\ representing \
  • \t representing Tab character
  • \n representing New Line character
  • \r representing carriage return
  • \" representing double quote
  • \' representing single quote
  • \uXXXX, here XXXX should be exactly four HexadecimalDigit's representing the Unicode character corresponding to the digits.

In single quoted strings it is optional to escape double quotes, and likewise it is optional to escape single quotes in double quoted strings.

Single quoted strings must contain at least two characters otherwise they will be assumed to be a character literal.

Example Some string literals
"string\nnext line"
'string'

The @-literals can be used to avoid obscuring the string literals with escape characters. The literals starts with @ followed by some non-letter character AtOpenChar. And it terminates when the close character AtCloseChar is met. For most characters the close character is the same as the opening character, but for diverse paranthesis charactes the close character is the corresponding opposite paranthesis.

Open Close Open Close
@( ) @) (
@[ ] @] [
@{ } @} {
@< > @> <

For all non-paranthesis opening character the close character is the same as the open character, for example @" is closed by ".

For all @-strings it is the case the twice the closing character does not close the string, but means one occurence of the closing character in the string.

Example

This example uses @[ as opening and ] as closing, inside the string literal both " and ' can be used unescaped: AtString.png

Binary Literals

BinaryLiteral:
   $[ ElementValue-comma-sep-list-opt ]
ElementValue:
   IntegerLiteral

ElementValue should be any integral arithmetic expression (for example, constant), which should be calculated while compilation-time and be in the range from 0 till 255.

Example A binary literal
$[12, 34, 12, 0x22]

Compilation Units

A program consists of a number of compilation units. The compiler compiles each of these compilation units separately. The result of a compilation is an object file. These object files (and perhaps other files) are linked together to produce the project target. A program must contain exactly one goalSection, which is the entry point to the program.

A compilation unit has to be self-contained in the sense that all referenced names have to be either declared or defined in the unit. Interface definitions and class declarations can be included in several compilation units (the definitions/declarations must be identical in all units where they are included), whereas class implementations (definitions) may only be defined in a single unit. Every declared item must also be defined in the project, but some items can be defined in libraries, meaning that they do not need a textual definition.

A compilation unit (which is perhaps composed by using #include directives) is a sequence of compilation items.

CompilationUnit :
   CompilationItem-list-opt

A compilation item is an interface, a class declaration, a class implementation, the goal section or it can be a conditional compilation item, which are described in Conditional Compilation.

CompilationItem :
   Directive
   NamespaceEntrance
   ConditionalItem
   InterfaceDefinition
   ClassDeclaration
   ClassImplementation
   GoalSection

See also

Interfaces

An interface definition defines a named object type. Interfaces can support other interfaces. See Supports Qualification for further details.

All predicates declared in an interface are object members in objects of the interface type.

An interface is also a global scope, in which constants and domains can be defined. Thus constants and domains defined in an interface are not part of the type that the interface denotes (or of objects having this type).

Such domains and constants can be referenced from other scopes by qualification with the interface name: interfaceName::constant, or by using an open qualification. (See Open Qualification.)

InterfaceDefinition :
   interface InterfaceName
       ScopeQualifications
   Sections
   end interface IinterfaceName-opt
InterfaceName :
   LowerCaseIdentifier

See also Generic Interfaces and Classes and Monitors.

The InterfaceName in the end of the construction must (if present) be identical to the one in the beginning of the construction.

The ScopeQualifications must be of the kinds:

The Sections must be of the kinds:

All sections contained (transitively) in conditional sections must also be of those kinds.

The interface: object

If an interface does not explicitly support any interfaces, then it implicitly supports the build-in interface object.

The object is an empty interface, i.e. it contains no predicates etc. The constant null is however defined for the interface.

The purpose of object is to be a universal base-type of all objects.

Open Qualification

Open qualifications are used to make references to class level entities more convenient. The open section brings the names of one scope into another scope, so that these can be referenced without qualification.

Open has no effect on the names of object members as these can only be accessed by means of an object anyway. But names of class members, domains, functors and constants can be accessed without qualification.

When names are brought into a scope in this way it may happen that some names becomes ambiguous (see Scoping).

Open sections have only effect in the scope in which they occur. Especially this means that an open section in a class declaration has no effect on the class implementation.

OpenQualification :
   open ScopeName-comma-sep-list

Supports Qualification

Supports qualifications can only be used in InterfaceDefinition and ClassImplementation.

Supports qualifications are used for two things:

  • specifying that one interface A extends another interface B and, thereby, that the object type A is a subtype of the object type B
  • declaring that the objects of a certain class "privately" have more object types, than the one specified as construction type.

supports is a transitive relation: if an interface A supports an interface B and B in turn supports C, then A also supports C.

If an interface does not explicitly support any interfaces, then it implicitly supports the predefined interface object.

Functionally, it makes no difference whether an interface supports a certain interface more that once (directly and/or indirectly), but it might make a representational difference for the objects.

When supports is used in the implementation of a class, the result is that "This" not only can be used with the construction type, but also with any privately supported object type.

SupportsQualification :
   supports InterfaceName-comma-sep-list

SupportsQualification can only be used in InterfaceDefinition and ClassImplementation.

Notice interfaces cannot be used together in a supports qualification, if they have conflicting predicates.

Predicates are conflicting if they have the same name and the arity but different origin interfaces.

The origin interface of a predicate is the interface in which the predicate is literally declared, as opposed to interfaces where it is indirectly declared by a supports qualification.

So it does not give conflicts, if the same interface is met twice or more in the supports chains.

Example Consider the following definitions and declarations:
interface aaa
predicates
    insert : (integer X).
end interface
 
interface bbb
   supports aaa
predicates
   insert : (integer X, string Comment).
end interface
 
interface cc
   supports aaa
predicates
   extract : () -> integer.
end interface
 
interface dd
   supports aaa, bbb, cc
predicates 
   extract : (string Comment) -> integer.
end interface

Here is a list of all predicates found in dd (found by a depth traversal):

predicates
   insert : (integer).     % dd -> aaa
   insert : (integer).     % dd -> bbb -> aaa
   insert : (integer, string).     % dd -> bbb
   insert : (integer).     % dd -> cc -> aaa
   extract : () -> integer.     % dd -> cc
   extract: : (string) -> integer.     % dd

Some of the predicates are the same, so all in all, dd will contain the following members:

predicates
   insert : (integer).     % origin interface: aaa
   insert : (integer, string).     % origin interface: bbb
   extract : () -> integer.     % origin interface: cc
   extract : (string) -> integer.     % origin interface: dd
Example Consider the following interfaces:
interface aaa
predicates
   insert : (integer X).
end interface
 
interface bbb
predicates
   insert : (integer X).
end interface
 
interface cc
   supports aaa, bbb     % conflicting interfaces
end interface

The interface cc is illegal, because insert/1 supported in aaa has aaa as origin, whereas insert/1 supported in bbb has bbb as origin.

Classes

A class declaration defines the appearance of the class to the surroundings: the surroundings can see and use exactly those entities mentioned in the class declaration. We say that the declaration of a class specifies the public part of the class.

A class declaration can contain constant and domain definitions and predicate declarations.

If the class states a construction type ConstructionType, then it constructs objects of that type. Object constructing classes have at least one constructor, but more can be declared. Classes that do not explicitly declare any constructors are automatically equipped with the default constructors (i.e. new/0).

Objects are constructed by invoking one of constructors of the class.

Constructors are also used when initializing inherited classes.

Everything mentioned in a class declaration belongs to the class, rather than to objects it constructs. Everything that relates to the objects must be declared in the construction type of the objects constructed by the class.

Any class declaration ClassDeclaration must have an accompanying class implementation ClassImplementation. The definition/implementation of predicates declared in the class declaration is provided by the class implementation. Likewise the definition of the predicates supported by the objects constructed by the class is provided by the class implementation. Both kinds of predicates can be implemented by clauses, but object predicates can also be inherited from other classes.

It is important to notice that a class declaration does not state anything about code inheritance. Code inheritance is a completely private matter that can only be stated in the class implementation. (This is unlike many other object oriented programming languages, and serves to hide all implementation details in the implementation).

If the class does not state a construction type ConstructionType, then the class cannot manufacture any objects; it therefore plays the role of a module rather than a "real" class.

ClassDeclaration :
    class ClassName ConstructionType-opt
        ScopeQualifications
    Sections
    end class ClassName-opt
ConstructionType :
    : InterfaceName
ClassName :
    LowerCaseIdentifier

See also Generic Interfaces and Classes and Monitors.

The ClassName in the end of the class declaration must (if present) be identical to the one in the beginning of the class declaration.

Notice that you can use the same class name ClassName as the interface name ConstructionType specified as the construction type to this class. That is you can write:

class interfaceAndClassName : interfaceAndClassName

Notice that both the class and the interface can declare domains and constants and these must not conflict with each other since they end up in the same name space (because they can be qualified only with the same name of the interface or the class).

The ScopeQualifications must be of the kind OpenQualification.

The Sections must be of the kinds:

constructorsSections are only legal if the class states a ConstructionType.

All sections contained (transitively) in conditional sections must also be of those kinds.

Implementations

A class implementation is used to provide the definitions of the predicates and constructors declared in the class declaration, as well as the definitions of any predicates supported by its constructed objects.

A class can privately (i.e. inside the implementation) declare and define more entities than those mentioned in the declaration. Especially, an implementation can declare fact databases that can be used to carry class and object state.

An implementation is a mixed scope, in the sense that it both contains the implementation of the class and of the objects produced by the class. The class part of a class is shared among all objects of the class, as opposed to the object part, which is individual for each object. Both the class part and the object part can contain facts and predicates, whereas domains, functors and constants always belong to the class part, i.e. they do not belong to individual objects.

By default all predicate and fact members declared in the implementation of a class are object members. To declare class members the section keyword (i.e. predicates and facts) must be prefixed with the keyword class. All members declared in such sections are class members.

Class members can reference the class part of a class, but not the object part.

Object members, on the other hand, can access both the class part and the object part of the class.

In the code in the implementation, the owner object is subsumed by all object predicates. The subsumed owner object can also be accessed directly through the special variable "This".

ClassImplementation :
    implement ClassName
        ScopeQualifications
    Sections
    end implement ClassName-opt

See also Generic Interfaces and Classes.

The ClassName in the end of the class implementation must (if present) be identical to the one in the beginning of the class implementation.

The ScopeQualifications must be of the kinds:

A Supports qualification states the list of interfaces, which are supported privately by the class implementation.

A Delegate qualification delegates functionality of (object) predicates from interfaces to predicates from objects, which can be stored as fact variables.

The Sections must be of the kinds:

constructorsSections are only legal if the class ClassName states a ConstructionType. Classes that states a ConstructionType are also object constructors, which construct objects of the stated construction type.

Example

This example illustrates how class facts are shared among the objects of the class and how object facts are not shared.

Consider the interface aa and class aa_class:

interface aa
   predicates
       setClassFact : (integer Value).
       getClassFact : () -> integer.
       setObjectFact : (integer Value).
       getObjectFact : () -> integer.
end interface
class aa_class : aa
end class

The point of the predicates is that they store and fetches values from respectively class and object facts:

implement aa_class
   class facts
       classFact : integer := 0.
   facts
       objectFact : integer := 0.
   clauses
       setClassFact(Value) :- 
           classFact := Value.
       getClassFact() = classFact.
   clauses
       setObjectFact(Value) :- 
           objectFact := Value.
       getObjectFact() = objectFact.
end implement aa_class

Given this class consider the goal:

goal
   A1 = aa_class::new(),
   A2 = aa_class::new(),
   A1:setClassFact(1),
   A1:setObjectFact(2),
   ClassFact = A2:getClassFact(),
   ObjectFact = A2:getObjectFact().

The class fact is shared among all objects, so setting the class fact via A1 also affects the value obtained via A2. Hence, the value of ClassFact will be one, the value set via A1.

On the other hand, object facts belong to each object. Therefore setting the object fact in A1 will not affect the value stored in A2. Hence value of ObjectFact is zero, the value that the fact was initialized to in A2.

Construction

This section describes object construction and, as such, it only deals with classes that produce objects.

Objects are constructed by calling a constructor.

Constructors are explicitly declared in constructors sections in class declarations and implementations (see also Default Constructor).

A constructor actually has two associated predicates:

  • A class function, which returns a new constructed object.
  • An object predicate, which is used when initializing inherited objects.

The associated object predicate is used to perform initialization the object. This predicate can only be called from a constructor in the class itself and from a constructor in a class, which inherits from the class (i.e. base class initialization).

The associated class function is defined implicitly, i.e. there are no clauses for it anywhere.

The class function allocates memory to hold the object, perform internal initialization of the object and then invokes the object constructor on the created object. Finally, the constructed object is returned as the result of the constructor execution.

So before the clauses of the constructor are invoked:

  • All object facts variables that have an initialization expression are initialized.
  • All object facts that have clauses are initialized from these clauses.

This initialization is also performed on all (transitively) inherited sub-objects, before the clauses of the constructor are invoked.

The constructor clauses must:

  • Initialize all those single object facts and object fact variables that are not initialized before entrance.
  • Initialize all sub-objects.

The constructor clauses can do other things as well, but it must perform the initialization mentioned here to ensure that the object is valid after construction.

Note. During construction objects might not be valid and care must be taken not to access un-initialized parts of the object (see Rules for Constructing Objects).

Default Constructor

A default constructor is a null-ary constructor with the name new/0. If a class that constructs objects does not declare any constructors in the class declaration, then the default constructor (i.e. new/0) is implicitly declared (in the class declaration). This means that each class has at least one constructor. So writing:

class aaa
end class aaa

is exactly the same as writing

class aaa
  constructors
     new : ().
end class aaa

It is legal to re-declare the default constructor explicitly.

It is not necessary to define (i.e. implement) the default constructor; if it is not defined then an effect-less definition is implicitly assumed. So writing

implement aaa
end implement aaa

is exactly the same as writing:

implement aaa
  clauses
     new().
end implement aaa

(Given that aaa has a default constructor).

Notice that a class has a default constructor if and only if:

  • it does not (publicly) declare any constructors at all;
  • or it declares new/0 as a constructor.

Which is the same (negated) as: A class does not have a default constructor if:

  • It publicly declares constructors;
  • and it does not publicly declare new/0 as a constructor.

Example

Given an interface aa, consider the following code:

class aa_class : aa
end class

The class aa_class declares no constructors; therefore, it implicitly declares the default constructor. Thus you can create an aa_class object like:

goal
   _A = aa_class::new(). % implicitly declared default constructor

Example

It is legal to implement the implicitly declared default constructor of aa_class:

implement aa_class
   clauses
       new() :-
          ...
end implement

Example

The bb_class class explicitly declares a constructor, which is not the default constructor; subsequently the class does not have the default constructor

class bb_class : aa
   constructors
       newFromFile : (file File).
end class

Example

The cc_class class declares the newFromFile/1 constructor, but it also declares the default new/0 constructor; so obviously, it has the default new/0 constructor

class cc_class : aa
   constructors
       new : ().                                          % default constructor
       newFromFile : (file File).
end class

Private Constructors

You also can declare "private" constructors in class implementations. This can be reasonable, for example, in the following situations:

  1. When some predicate returns an object of construction type, then in a class implementation can be declared, implemented and called a "private" constructor to create such objects.
  2. When some class declares several "public" constructors having a "same big part", then it can be reasonable to define in the class implementation a "private" constructor, which implements this "same big part". Then clauses of all these "public" constructors can simply call this "private" constructor to implement this "same big part".

Notice that if a class, which can construct objects, does not declare any constructors in the class declaration, then the default constructor (i.e. new/0) will be declared implicitly independently of whether the class implementation declares or not "private" constructors. That is, it is possible to write:

interface aa
end interface
 
class aa : aa
end class
 
implement aa
    constructors
           myCreate : ().
    clauses
            myCreate() :-
                  ...
end implement
 
% program code
   ...
   Obj = aa::new(),      % This is the declared IMPLICIT default class constructor
   ...

Sub-object Construction

All constructors are responsible for initializing constructed objects to valid states. In order to obtain such a valid state all sub-objects (i.e. inherited classes) must be initialized as well.

The sub-objects can be initialized in one of two ways, either the programmer calls a constructor of the inherited class or the default constructor is automatically invoked. The latter requires that the inherited class actually has the default constructor, but this is no difference whether this default constructor is declared explicitly or implicitly - it will be called in both cases!

If the inherited class does not have a default constructor, then another constructor must be invoked explicitly. The default invocation of constructors of inherited classes takes place immediately after initialization of fact variables and facts with clauses and before entrance to the clauses of the constructor.

Constructors of inherited classes are invoked by the versions that does not return a value. If you call the version that returns a value then you are actually creating a new object, rather than invoking the constructor on "This" (see the example below).

Example

This implementation of the class bb_class inherits from the class aa_class and the default constructor of bb_class call a constructor of aa_class with a newly created cc_class object

implement bb_class inherits aa_class
   clauses
       new() :-
           C = cc_class::new(), % create a cc_class object
           aa_class::newC(C). % invoke constructor on inherited sub-object
      ...
end implement

Example 2

If a base class is not explicitly constructed, then it is implicitly constructed using the default constructor. So writing:

implement bbb
   inherits aaa
clauses
   myNew() :-
       doSomething().
end implement bbb

is exactly the same as writing:

implement bbb
   inherits aaa
clauses
   myNew() :-
       aaa::new(),
       doSomething().
end implement bbb

If aaa does not have a default constructor then this will, of course, give an error.

Notice that this rule (of course) can be combined with the rule discussed in the first paragraph of Default Constructor. So writing:

implement bbb
   inherits aaa
end implement bbb

Is exactly the same as writing (according to the rule discussed in the first paragraph of Default Constructor):

implement bbb
   inherits aaa
clauses
   new().
end implement bbb

Which is exactly the same as writing (the rule discussed above):

implement bbb
   inherits aaa
clauses
   new() :-
       aaa::new().
end implement bbb

Single (Object) Fact Initialization

Just like all constructors have to initialize/construct sub-objects, they also have to initialize all single facts of an object, before they are referenced the first time.

Notice that single class facts can only be initialized with clauses, since they are not related to an object. A class fact can be accessed before the first object is created.

Example

This example shows (1) how to initialize a fact variable by means of an expression; (2) how to initialize a single fact (point) by means of a clause; (3) how to initialize a single fact in the constructor and (4) where the default constructor of an inherited class is invoked:

implement bb_class inherits aa_class
   facts
       counter : integer := 0.
       point : (integer X, integer Y) single.
       c : (cc C) single.
   clauses
       point(0, 1).
       % The object is created and counter and point are initialized before entrance,
       % the default constructor aa_class::new/0 is also invoked before entrance
       new() :-
           C = cc_class::new(),
           assert(c(C)).
      ...
end implement

Construction by Delegation

As an alternative to construct the object directly in a constructor the job can be delegated to another constructor of the same class. This is done simply by invoking the other constructor (i.e. the version that does not return a value). When delegating construction we have to be sure that the object is actually constructed and that it is not "over-constructed". Single facts can be assigned a value as many times as one likes so they cannot be "over-constructed". Inherited classes, on the other hand, may only be initialized once during object construction.

Example

This example shows a typical use of construction by means of delegation. A constructor (new/0) invokes another constructor (newFromC/1) with a default value.

implement aa_class
   facts
       c : (cc C) single.
   clauses
       new() :-
           C = cc_class::new(),
           newFromC(C).
       newFromC(C) :-
           assert(c(C)).
      ...
end implement

Rules for Constructing Objects

The programmer must ensure that:

  • All sub-objects are initialized/constructed exactly once each.
  • All single facts are initialized (at least once).
  • That no sub-object is referenced before it is initialized/constructed.
  • That no single fact is used before it is initialized.

There is no guarantee about how clever the compiler is in detecting such problems at compile time.

The compiler may offer to generate runtime validation, it may also offer to non-safely omit such runtime validations.

"This"

An object predicate is always invoked on an object. This object carries the object facts and is subsumed by the implementation of object predicates. The object predicate has access to this implicit object. We shall call the object "This". There are two kinds of access to "This" implicit and explicit.

Explicit "This"

In every clause of every object predicate the variable This is implicitly defined and bound to "This", i.e. the object whose member predicate is executing.

Implicit "This"

In the clause of an object member predicate other object member predicates can be called directly, because "This" is implicitly assumed for the operation. Members of super-classes can also be invoked directly, as long as it is unambiguous which method is called (see Scoping & Visibility). Likewise the object facts (which are stored in "This") can be accessed.

"This" and Inheritance

Consider this code:

interface iName
 
properties
    className : string (o).
 
end interface iName
 
%=========================
 
class aaa : iName
end class aaa
 
%=========================
 
implement aaa
 
clauses
    className() = "aaa".
 
end implement aaa
 
%=========================
 
class bbb : iName
end class bbb
 
%=========================
 
implement bbb inherits aaa
end implement aaa

We have to classes aaa and bbb that both implement the iName interface. bbb inherits aaa, so this code:

class predicates
    test : (string Class, iName Name).
clauses
    test(Class, Name) :-
        stdio::writef("% className = %\n", Class, Name:className).
 
clauses
    run() :-
        test("aaa", aaa::new()),
        test("bbb", bbb::new()).

will output

aaa className = aaa
bbb className = aaa

I.e. bbb has inherited the implementation of thew className property from aaa.

If we reimplement the className property in bbb:

implement bbb inherits aaa
 
clauses
    className() = "bbb".
 
end implement aaa

then the output will change to

aaa className = aaa
bbb className = bbb

Because now bbb has its own implementation of the className property.

Ley us extend the iName interface with a name property:

interface iName
 
properties
    className : string (o).
    name : string (o).
 
end interface iName

And implement it in aaa like this:

implement aaa
 
clauses
    className() = "aaa".
 
clauses
    name() = className.
 
end implement aaa

We will not implement the name property in bbb so it will inherit the implementation from aaa.

Changing the test clause like this:

clauses
    test(Class, Name) :-
        stdio::writef("% className = %\n", Class, Name:className),
        stdio::writef("% name = %\n", Class, Name:name).

We will get this output:

aaa className = aaa
aaa name = aaa
bbb className = bbb
bbb name = aaa

Notice that the inherited name property in bbb returns "aaa".

This is because the inherited name property references the aaa::className.

Let us perform a similar extension with a property nameThis:

interface iName
 
properties
    className : string (o).
    name : string (o).
    nameThis : string (o).
 
end interface iName

Again we will let bbb inherit the code from aaa, but this time the implementation in aaa will make an indirect reference to className through This:

implement aaa
 
clauses
    className() = "aaa".
 
clauses
    % Direct reference
    name() = className.
 
clauses
    % Indirect reference through "This"
    nameThis() = This:className.
 
end implement aaa

Such an indirect reference through This behaves like calls made to objects from the "outside", so if updating the test in the "obvious" way:

clauses
    test(Class, Name) :-
        stdio::writef("% className = %\n", Class, Name:className),
        stdio::writef("% name = %\n", Class, Name:name),
        stdio::writef("% name This= %\n", Class, Name:nameThis).

will produce this output:

aaa className = aaa
aaa name = aaa
aaa nameThis = aaa
bbb className = bbb
bbb name = aaa
bbb nameThis = bbb

Given an inheritance chain a5 inherits  a4 inherits  a3 inherits  a2 inherits  a1:

  • A direct reference in an implementation in a3 to a predicate/property will refer to the entity as seen inside a3, which will therefore
    • be implemented in a3 or
    • inherited from a2 which may have inherited it from a1
  • An indirect reference through This in an implementation in a3 to a predicate/property will refer to the entity as see from the outside, and will therefore
    • be implemented in a5 or
    • inherited from a4 which may have inherited it from a3, ...

Inherits Qualification

Inherits qualifications are used to state that an implementation inherits from one or more classes. Inheritance has only influence on the object part of a class.

The purpose of inheriting from other classes is to inherit behavior from these classes.

When a class cc inherits from a class aa, this means that the implementation of the cc class automatically implicitly (privately) supports the construction type (interface) of the aa class. (If the class aa implementation already support the cc construction type explicitly then there is of course no difference.)

Therefore, notice that the same predicate, for example p, cannot be declared in the construction type interface of a cc class and in the construction type interface of an inherited aa class. (The compiler will detect this and generates an error that a predicate is declared in 2 places.) Let us discuss this in some details. Let us suppose that a cc class has a construction type interface cci and some other aa class has a construction type interface aai. Let both aai and cci interfaces declare the same predicate p. Till the aa and cc classes are independent, the compiler does not detect any problems. But as soon as we declare that the cc class inherits from the aa class, then cc class starts to support also the aai interfaces. Therefore, the cc class starts to see both declarations of the predicate p, which will be reported as a compiling time error. The only possibility to avoid such ambiguity in the predicate p declaration is using of the Predicates from Interface section in the cci interface declaration. For example like:

interface cci
 predicates from aai
    p(), ...
end interface cci

Object predicates can be inherited: If the class does not implement a certain of its object predicates, but one of the classes it inherits from does implement this predicate, then that predicate will be used for the current class.

The class that inherits from another class does not have any special privileges towards the inherited class: It can only access the embedded object through its construction type interface.

Inheritance must be unambiguous. If the class defines the predicate itself then there is no ambiguity, because then it is this predicate definition that is exposed. If only one inherited class supports the predicate then it is also unambiguous. But if two or more classes supports the predicate then it is ambiguous which class provides the definition. In that case the ambiguity must be resolved by means of a resolve qualification (see Resolve Qualification).

Object predicates from inherited classes can be called directly from object predicates in the current class, since the embedded sub-object is implicitly used as predicate owner. Class qualification can be used to resolve calling ambiguities for object predicates from inherited classes.

InheritsQualification :
   inherits ClassName-comma-sep-list

Resolve Qualification

As mentioned elsewhere all ambiguities related to calling predicates can be avoided by using qualified names.

But when it comes to inheritance this is not the case. Consider the following example:

interface aa
   predicates
       p : () procedure ().
       ...
end interface
 
class bb_class : aa
end class
 
class cc_class : aa
end class
 
class dd_class : aa
end class
 
implement dd_class inherits bb_class, cc_class
end implement

In this case it is ambiguous which of the classes bb_class and cc_class that would provide the implementation of aa for dd_class. (Notice that when we say that a class implements an interface, it means that it provide definitions for the predicates declared in the interface.)

It would of course be possible to add clauses to the implementation of dd_class, which would effectively solve the job. Consider, for example, the following clause, which would "export" the predicate p from bb_class:

clauses
   p() :- bb_class::p().

But, with this code we have not really inherited the behavior from bb, we have actually delegated the job to the bb_class part of our class.

So to resolve this kind of ambiguities (and use real inheritance rather than delegation) we use a resolve section. A resolve section contains a number of resolutions:

ResolveQualification :
   resolve Resolution-comma-sep-list
Resolution :
    InterfaceResolution
    PredicateFromClassResolution
    PredicateRenameResolution
    PredicateExternallyResolution

A resolve qualification is used to resolve an implementation from the specified source.

Predicate Resolution

PredicateFromClassResolution :
    PredicateNameWithArity from ClassName

A predicate from class resolution states that the predicate is implemented by the specified class.

To resolve a predicate to a class:

  • the class must implement the predicate to be resolved, this implies that the predicate must origin in the same interface as the one that should be inherited
  • the class must be mentioned in the inherits section

Predicate Rename Resolution

A predicate rename resolution states that the predicate is implemented as predicate with another name. The predicate must come from an inherited class and its type, mode and flow must match exactly.

PredicateRenameResolution :
   PredicateNameWithArity from ClassName :: PredicateName

Interface Resolution

An interface resolution is used to resolve a complete interface from one of the inherited classes. Thus an interface resolution is a short way of stating that all the predicates in the interface should be resolved from the same class.

InterfaceResolution :
   interface InterfaceName from ClassName

The class must publicly support the resolved interface.

If both a predicate resolution and an interface resolution cover some predicate name, then the predicate resolution is used. I.e. the specific resolution overrides the less specific ones.

It is valid for a predicate to be covered by several interface resolutions, as long as these all resolve the predicate to the same class. If on the other hand a predicate is resolved to different classes by interface resolutions, then the resulting ambiguity must be resolved by a predicate resolution.

Note: The syntax of resolutions is not capable of resolving different overloading of a predicate to different classes.

Example

We can solve the ambiguity from the example above by providing an interface resolution. In this case we have chosen to inherit the implementation of aa_class from cc_class, except that we will inherit p from bb_class

implement dd_class
   inherits bb_class, cc_class
   resolve
       interface aa from cc_class
       p from bb_class
end implement

External Resolution

A predicate externally resolution states that the predicate is not at all implemented in the class itself, but in an external library. External resolutions can only be used for class predicates. I.e. object predicates cannot be resolved externally.

It is important that the calling convention, link name and argument types correspond to the implementation in the library.

Both private and public predicates can be resolved externally.

PredicateExternallyResolution : PredicateNameWithArity externally

Dynamic External Resolution

A predicate externally resolution also provide syntax for dynamic loading of private and public class predicates from DLLs.

The syntax is:

PredicateExternallyResolutionFromDLL :
  PredicateNameWithArity externally from DllNameWithPath
DllNameWithPath :
   StringLiteral

If the predicate predicateNameWithArity is not available in the DLL DllNameWithPath, then the dynamic loading provides the possibility to run a program until it actually invokes the predicate. A runtime error will occur on such invocation. The DllNameWithPath is the path to the DLL on the machine where the program should run, it can be absolute or relative. For example if the required dll is situated in the one level up from directory which the application loaded, then the DllNameWithPath should be like "../DllName". See also Dynamic-Link Library Search Order.

Finalization

Once an object cannot be reached by the program it can be finalized, the semantics of the language does not say exactly when the object will be finalized. The only thing that is guaranteed is that it is not finalized as long as it can be reached from the program. In practice the object is finalized, when it is wasted by the garbage collector. Finalization is the opposite of construction and will remove the object from memory.

Classes can also implement a finalizer, which is a predicate that is invoked when the object is finalized (before it is removed from memory).

A finalizer is a procedure with no arguments and no return value, which has the name finalize. The predicate is implicitly declared and cannot be invoked directly from the program.

The main purpose of finalizers is to be able to release external resources, but there are no restrictions on what it can do. Finalizers should however be used with caution, recall that the time of their invocation is not completely known and, therefore, it might also be difficult to predict the overall program state at the time where they are invoked.

Notice that there is no reason to retract object facts from an object in the finalizer, because this is automatically done in the finalization process.

All objects are finalized before the program can terminate (unless an abnormal situation like power failure prevents this).

Example

This example uses a finalizer to ensure that a database connection is closed properly.

implement aa_class
   facts
       connection : databaseConnection.
   clauses
       finalize() :-
           connection:close().
   ...
end implement aa_class

Delegate Qualification

A delegate section contains a number of delegations:

DelegateQualification :
   delegate Delegation-comma-sep-list
Delegation :
   PredicateDelegation
   InterfaceDelegation

The delegate qualifications are used to delegate implementations of object predicates to the specified source.

There are two kinds of the delegate qualifications. The Predicate Delegation and the Interface Delegation. The Interface Delegation is used to delegate implementations of a complete set of object predicates declared in an interface to an implementation of another object, stored as fact variable. Thus an interface delegation is a short way of stating that implementations of all predicates in the interface should be delegated to an implementation of the object, stored in fact variable.

The delegate sections look like a correspondent (predicate/interface) resolve sections, except that you delegate to fact variables keeping constructed objects of classes, rather than to inherited classes.

Predicate Delegation

A object predicate delegation states that the predicate functionality is delegated to the predicate in the object specified with the fact variable FactVariable_of_InterfaceType.

PredicateDelegation :
   PredicateNameWithArity to FactVariable_of_InterfaceType

To delegate a predicate to an object passed with the fact variable:

  • The fact variable FactVariable_of_InterfaceType must have a type of an interface (or of its sub-type), which declares the predicate predicateNameWithArity.
  • The object supporting the interface must be constructed and be assigned to the fact variable FactVariable_of_InterfaceType.

Consider the following example:

interface a
   predicates
       p1 : ().
       p2 : (). 
end interface
 
interface aa
   supports a
end interface
 
class bb_class : a
end class
 
class cc_class : a
end class
 
class dd_class : aa
  constructors
     new : (a First, a Second).
end class
 
implement dd_class
    delegate p1/0 to fv1, p2/0 to fv2
    facts
       fv1 : a.
       fv2 : a.
   clauses
       new(I,J):-
           fv1 := I,
           fv2 := J.
end implement

Later it will be possible to construct objects of the type a and assign them to fact variables fv1 and fv2 to define to objects of which class we really delegate definitions of p1 and p2 functionality. Consider, for example,

goal
   O_bb = bb_class::new(),
   O_cc = cc_class::new(),
   O_dd = dd_class::new(O_bb, O_cc),
   O_dd : p1(), % This p1 from O_bb object
   O_dd : p2(). % This p2 from O_cc object

Actually in Visual Prolog delegation has the same effect as if you add clauses to the implementation of dd_class that explicitly specify, from object of which class the predicate functionality is "exported". That is for example, as if the following clause is determined in the implementation of dd_class:

clauses
   p1() :- fv1:p1().

Interface Delegation

When you need to specify that functionality of all predicates declared in an interface InterfaceName are delegated to predicates from objects of the same inherited class, you can use the Interface Delegation specification:

InterfaceDelegation :
   interface InterfaceName to FactVariable_of_InterfaceType

Thus an interface delegation is a short way of stating that functionality of all predicates declared in the interface InterfaceName should be delegated to objects stored as the fact variable FactVariable_of_InterfaceType. Objects should be assigned to the fact variable FactVariable_of_InterfaceType, which should be of the InterfaceName type (or its sub-type).

To delegate an interface to an object passed with the fact variable:

  • The fact variable FactVariable_of_InterfaceType must have a type of an interface InterfaceName or of its sub-type.
  • The object supporting the interface must be constructed and be assigned to the fact variable FactVariable_of_InterfaceType.

The predicate delegation has higher priority than the interface delegation. If to a predicate both delegations are specified. That is, the predicate delegation is specified to the predicate and it is declared in an interface, which has the interface delegation. Then the higher priority predicate delegation will be implemented.

Generic Interfaces and Classes

Interfaces and classes can be parametrized with type parameters so that they can be used in different instantiations in different contexts.

This section must be considered as an extension to the individual sections about:

The pragmatic reason to use generic classes and interfaces is to declare parametrized object facts and implement operations on these facts. As illustrated in the Queue example below.

Example: Queue

Consider this interface

interface queue_integer
    predicates
        insert : (integer Value).
        tryGet : () -> integer Value.
end interface queue_integer

An object of this type is a queue of integers, if you replace "integer" with "string" you would have a type describing queues of strings.

A generic interface can be used to describe all such interfaces in a single interface definition:

interface queue{@Elem}
    predicates
        insert : (@Elem Value).
        tryGet : () -> @Elem Value determ.
end interface queue

@Elem is a scope type variable (distinguished from local type variables by the @).

queue{integer} represents integer-queues; queue{string} represents string-queues; and so forth.

We can declare a generic queue class like this:

class queueClass{@Elem} : queue{@Elem}
end class queueClass

queueClass{@Elem} constructs objects type queue{@Elem} for any instantiation of @Elem.

The implementation can look like this:

implement queueClass{@Elem}
    facts
        queue_fact : (@Elem Value).
    clauses
        insert(Value) :-
            assert(queue_fact(Value)).
    clauses
        tryGet() = Value :-
            retract(queue_fact(Value)),
            !.
end implement queueClass

This piece of code illustrates how to create an integer queue and insert an element in it:

..., Q = queueClass{integer}::new(), Q:insert(17), ...

It is not necessary to apply the type explicitly, instead the compiler can infer it from the context:

..., Q = queueClass::new(), Q:insert(17), ...

The compiler sees that Q must be an integer queue, because we insert 17 into it.

Generic Interfaces

Syntax

Generic interfaces have a list of type parameters:

InterfaceDeclaration :
    interface InterfaceName { ScopeTypeVariable-comma-sep-list-opt }
        ScopeQualifications
    Sections
    end interface InterfaceName-opt
 
ScopeTypeVariable :
    @ UppercaseName

The scope type parameters can be used in any declaration/definition in the interface.

Semantics

A generic interface defines all the interfaces that can be obtained by instantiating the type parameters with actual types. The scope type parameters from the opening are bound in the entire interface.

Restrictions

Then closing name should not have parameters:

interface xxx{@A}
    ...
end interface xxx % no parameters here

It is illegal to use same interface name for interfaces with different arity (in the same namespace):

interface xxx % xxx/0
    ...
end interface xxx
 
interface xxx{@A, @B} % error: Several classes, interfaces and/or namespaces have the same name 'xxx'
    ...
end interface xxx

Parameters can be used in supported interfaces:

interface xxx{@P} supports yyy{@P} % legal: @P is bound
    ...
end interface xxx
 
interface xxx supports yyy{@P} % illegal: @P must be bound
    ...
end interface xxx

Supported interfaces can be instantiated with any type expressions (as long as parameters are bound):

interface xxx{@A} supports yyy{integer, @A*}
    ...

Generic Classes

Syntax

Generic classes have a list of type parameters, and constructs objects of an interface type uses the these parameters.

ClassDeclaration :
    class ClassName { ScopeTypeVariable-comma-sep-list-opt } ConstructionType
        ScopeQualifications
    Sections 
    end class ClassName-opt
 
ScopeTypeVariable :
    @ UppercaseName
 
ConstructionType :
   : TypeExpression

The construction type must be generic (i.e. a generic interface).

Semantics

A generic class declares a class with a generic constructor. The type of the constructed object will be inferred from the usage of the constructor.

Restrictions

Then closing name should not have parameters:

class xxx{@A} : xxx{@A}
    ...
end class xxx % no parameters here

It is illegal to use same class name for class with different arity (in the same namespace):

class xxx % xxx/0
    ...
end class xxx
 
class xxx{@A} : yyy{@A} % error: Several classes, interfaces and/or namespaces have the same name 'xxx'
    ...
end class xxx

If a class and interface can have the same name, the class must construct objects of that interface.

interface xxx{@A}
    ...
end interface xxx
 
class xxx{@Q, @P} : object % error: Several classes, interfaces and/or namespaces have the same name 'xxx'
    ...
end class xxx

Parameters in the construction type, etc must be bound:

class bbb : xxx{@Q} % error: Free parameter '@Q' is used in type expression
    ...

All the parameters from the class must be used in the construction type:

class xxx{@P} : object % error: Unused type parameter '@P'
    ...

In class declarations scope parameter can only be used in constructors, domains and constants.

class xxx{@P} : xxx{@P}
    domains
        list = @P*. % legal
    constants
        empty : @P* = []. % legal
    constructors
        new  : (@P Init).  % legal
    predicates
        p : (@P X). % error: Scope parameter '@P' used in a class entity
end class xxx

Generic Implmentations

Syntax

Generic implementations have a list of type parameters.

ClassImplementation :
    implement ClassName { ScopeTypeVariable-comma-sep-list-opt }
        ScopeQualifications
    Sections
    end implement ClassName-opt
 
ScopeTypeVariable :
    @ UppercaseName

Semantics

A generic class declares a class with a generic constructor. The type of the constructed object will be inferred from the usage of the constructor.

Restrictions

Then closing name should not have parameters:

implement xxx{@A}
    ...
end implement xxx % no parameters here

The parameters must be the same as in the corresponding class declaration and have same order.

class xxx{@A} : aaa{@A}
    ...
end class xxx
 
implement xxx{@B} % error: The parameter '@B' is not the same as in the declaration '@A'
    ...
end implement xxx

In class implementations scope parameter can be used in constructors, domains, constants and in object entities (i.e. object facts, object predicates and object properties).

implement xxx{@P}
    domains
        list = @P*. % legal
    constants
        empty : @P* = []. % legal
    constructors
        new  : (@P Init).  % legal
    predicates
        op : (@P X). % legal
    class predicates
        cp : (@P X). % error: Scope parameter '@P' used in a class entity
    facts
        ofct : (@P). % legal
    class facts
        cfct : (@P). % error: Scope parameter '@P' used in a class entity
    ...
end implement xxx

Monitors

A monitor is a language construction to synchronize two or more threads that use a shared resource, usually a hardware device or a set of variables. The compiler transparently inserts locking and unlocking code to appropriately designated procedures, instead of the programmer having to access concurrency primitives explicitly.

Visual Prolog monitor entrances can be controlled by guard predicates (conditions).

Syntax

Monitor interfaces and monitor classes are scopes:

Scope : one of
    ...
    MonitorInterface
    MonitorClass
    ...

A monitor interface is defined by writing the keyword monitor in front of a regular interface definition:

MonitorInterface :
    monitor IntertfaceDefinition

A monitor class is declared by writing the keyword monitor in front of a regular class declaration:

MonitorClass :
    monitor ClassDeclaration

Monitor classes and interfaces cannot declare multi and nondeterm predicate members.

Restrictions

  • A regular interface cannot support a monitor interface
  • A monitor class cannot construct objects.
  • It is not legal to inherit from a monitor (i.e. from a class that implements a monitor interface).

Semantics

The predicates and properties declared in a monitor are the entrances to the monitor. A thread enters the monitor through an entrance and is in the monitor until it leaves that entrance again. Only one thread is allowed to be in the monitor at the time. So each entry is protected as a critical region.

The semantics is simplest to understand as a program transformation (which is how it is implemented). Consider this academic example:

monitor class mmmm
predicates
    e1 : (a1 A1).
    e2 : (a2 A2).
    ...
    en : (an An).
end class mmmm
 
%-----------------------------------------
implement mmmm
clauses
    e1(A1) :- <B1>.
 
clauses
    e2(A2) :- <B2>.
 
...
clauses
    en(An) :- <Bn>.
end implement mmmm

Where <B1>, <B2>, ..., <Bn> are clause bodies. This code corresponds to the following "normal" code:

class mmmm
predicates
    e1 : (a1 A1).
    e2 : (a2 A2).
    ...
    en : (an An).
end class mmmm
 
%-----------------------------------------
implement mmmm
class facts
    monitorRegion : mutex := mutex::create(false).
 
clauses
    e1(A1) :-
        _W = monitorRegion:wait(),
        try
           <B1>
        finally
           monitorRegion:release()
        end try.
 
clauses
    e2(A2) :-
        _W = monitorRegion:wait(),
        try
            <B2>
        finally
            monitorRegion:release()
        end try.
...
clauses
    en(An) :-
        _W = monitorRegion:wait(),
        try
            <Bn>
        finally
            monitorRegion:release()
        end try.
end implement mmmm

So each monitor class is extended with a mutex, which is used to create a critical region around each entry body.

The code for monitor objects is similar, except that the mutex object is owned by the object.

Guards

Consider a monitor protected queue: some threads (producers) inserts elements in the queue and others (consumers) pick-out elements. However, you cannot pick-out elements if the queue is empty.

If we implement the queue using a monitor, the "pick-out" entry could be determ, failing if the queue is empty. But then the consumers would have to "poll" the queue until an element can be obtained. Such polling uses system resources, and normally it is desirable to avoid polling. This problem can be solved by guard predicates.

Each entry can have a guard associated in the implementation. The guard is added as a special guard-clause before the other clauses of the entry.

Clause : one of
    ...
    GuardClause.
GuardClause : one of
    LowerCaseIdentifier guard LowerCaseIdentifier .
    LowerCaseIdentifier guard AnonymousPredicate .
Example The guard can be the name of a predicate
clauses
    remove guard remove_guard.
    remove() = ...
Example The guard can also be an anonymous predicate
clauses
    remove guard { :- element_fact(_), ! }.
    remove() = ...


The guard predicates are evaluated when the monitor is created. For monitor classes this means at program start, for object predicates this is immediately after the construction of the object. The guard predicates are also evaluated whenever a tread leaves the monitor. But they are not evaluated at any other time.

If a certain guard succeeds the corresponding entry is open, if it fails the entry is closed.

It is only possible to enter open entries.

Example Here is a queue class that solves the pick-out problem using a guard predicate on the remove operation:
monitor class queue
predicates
    insert : (integer Element).
predicates
    remove : () -> integer Element.
end class queue
 
%-----------------------------------------
implement queue
class facts
    element_fact : (integer Element) nondeterm.
 
clauses
    insert(Element) :-
        assert(element_fact(Element)).
 
clauses
    remove guard remove_guard.
    remove() = Element :-
        retract(element_fact(Element)),
        !;
        exception::raise_error("The guard should have ensured that the queue is not empty").
 
predicates
    remove_quard : () determ.
clauses
    remove_guard() :-
        element_fact(_),
        !.
end implement queue

Notice that remove is a procedure, because threads that call remove will wait until there is an element for them. The guard predicate remove_guard succeeds if there is an element in the queue.

So remove_guard is evaluated each time a thread leaves the monitor, and the element_fact fact database can only be changed by a thread that is inside the monitor. Therefore the guard value stays sensible all the time (i.e. when there are no threads in the monitor). It is important to ensure such "stays sensible" condition for guards.

Guard predicates are handled in the transformation mentioned above.

Example The queue example is effectively the same as this "monitor-free" code:
class queue
predicates
    insert : (integer Element).
predicates
    remove : () -> integer Element.
end class queue
 
%-----------------------------------------
implement queue
class facts
    monitorRegion : mutex := mutex::create(false).
    remove_guard_event : event := event::create(true, toBoolean(remove_guard())).
    element_fact : (integer Element) nondeterm.
 
clauses
    insert(Element) :-
        _W = monitorRegion:wait(),
        try
            assert(element_fact(Element))
        finally
            setGuardEvents(),
            monitorRegion:release()
        end try.
 
clauses
    remove() = Element :-
        _W = syncObject::waitAll([monitorRegion, remove_guard_event]),
        try
            retract(element_fact(Element)),
            !;
            common_exception::raise_error(common_exception::classInfo, predicate_name(),
                "The guard should have ensured that the queue is not empty")
        finally
            setGuardEvents(),
            monitorRegion:release()
        end try.
 
class predicates
    remove_guard : () determ.
clauses
    remove_guard() :-
        element_fact(_),
        !.
 
class predicates
    setGuardEvents : ().
clauses
    setGuardEvents() :-
        remove_guard_event:setSignaled(toBoolean(remove_guard())).
end implement queue

An event is created for each guard predicate; this event is set to signaled if the guard predicate succeeds. As mentioned it is set during the creation of the monitor and each time a predicate leaves the monitor (before it leaves the critical region).

When entering an entry the threads waits both for the monitorRegion and for the guard event to be in signalled state.

In the code above the initialization of the class itself and the guard events are done in an undetermined order. But actually it is ensured that the guard events are initialized after all other class/object initialization is performed.

Examples of practical usage

This section shows a few cases where monitors are handy.

Writing to a log file

Several threads needs to log information to a single log file.

monitor class log
properties
    logStream : outputStream.
predicates
    write : (...).
end class log
 
%-----------------------------------------
implement log
class facts
    logStream : outputStream := erroneous.
clauses
    write(...) :-
        logStream:write(time::new():formatShortDate(), ": "),
        logStream:write(...),
        logStream:nl().
 end implement log

The monitor ensures that writing of a log lines are not mixed with each other, and that stream changes only takes place between writing of log lines.

Shared output streams

This monitor can be used to thread protect the operations of an output stream:

monitor interface outputStream_sync
    supports outputStream
end interface outputStream_sync
 
%-----------------------------------------
class outputStream_sync : outputStream_sync
constructors
    new : (outputStream Stream).
end class outputStream_sync 
 
%-----------------------------------------
implement outputStream_sync
    delegate interface outputStream to stream
 
facts
    stream : outputStream.
 
clauses
    new(Stream) :- stream := Stream.
end implement outputStream_sync

You should realize however that with code like this:

clauses
    write(...) :-
        logStream:write(time::new():formatShortDate(), ": "),
        logStream:write(...),
        logStream:nl().

consists of three separate operations, so it can still be the case (fx) that two threads first write the time and then one writes the "...", etc.

Queue

The queue above is fine, but actually it may be better to create queue objects. Using generic interfaces we can create a very general queue:

monitor interface queue{@Elem}
predicates
    enqueue : (@Elem Value).
predicates
    dequeue : () -> @Elem Value.
end interface queue
 
%-----------------------------------------
class queue{@Elem} : queue{@Elem}
end class queue
 
%-----------------------------------------
implement queue{@Elem}
facts
    value_fact : (@Elem Value).
 
clauses
    enqueue(V) :-
        assert(value_fact(V)).
 
clauses
    dequeue guard { value_fact(_), ! }.
    dequeue() = V :-
        retract(value_fact(V)),
        !.
    dequeue() = V :-
        common_exception::raise_error(....).
end implement queue

Notice that PFC contains a similar class monitorQueue already.

References

Namespaces

Namespaces can be used to avoid name clashes, without having to use long strange names. The names in two different namespaces will never clash, but it may be necessary to qualify references with the namespace (or part of it) to resolve ambiguities.

A namespaces are declared and defined implicitly using NamespaceEntrance'es:

NamespaceEntrance:
   namespace NamespaceIdentifier
NamespaceIdentifier: one of
   \
   LowercaseIdentifier
   LowercaseIdentifier \ NamespaceIdentifier

In short a NamespaceIdentifier is a sequence of lowercase identifiers separated by backslashes.

Namespace Entrances and Regions

Namespace entrances divide source files into namespace regions.

A namespace entrance marks the beginning of a namespace region, which ends at the next namespace entrance or the end of the file.

Every file starts in the root namespace.

Namespace regions are not influenced by #include directives, meaning:

  • Namespace entrances in an #include-file does not change the namespace region in the including file
  • Any file starts in the root namespace (also if it is included inside a namespace region in another file).

Any interface, class and implementation that is meet inside a namespace region belongs to that namespace.

Example
class aaa
end class aaa
 
namespace xxx
 
class bbb
end class bbb
 
namespace xxx\yyy
 
class ccc
end class ccc

This file is divided in three regions (assuming that it is a complete file). The first region is in the root namespace (\), the second region belongs to the xxx namespace and the third region belongs to the xxx\yyy namespace.

Subsequently, the class aaa belongs to the root namespace, the class bbb belongs to the namespace xxx and finally the class ccc belongs to the namespace xxx\yyy.

Referencing names in namespaces

If ccc is a class in the namespace xxx\yyy, then the full name of ccc is \xxx\yyy\ccc.

The leading backslash indicates that we start from the root namespace.

A class/interface can always be uniquely referenced using its full name.

Open namespaces

The full names are not always convenient and therefore it is possible to use shorter names by opening namespaces.

ScopeQualification: one of
    OpenQualification
    ...
 
OpenQualification: one of
    open NamespaceIdentifier\
    ...

Opening a namespace is distinguished from opening a class/interface by a trailing backslash.

Example
class aaa
    open xxx\yyy\
...
end class aaa

The namespace xxx\yyy is opened inside aaa.

When a namespace is open that part of a full name can be left out.

Example A domains with the full name \xxx\yyy\zzz\ccc::ddd can be as referenced zzz\ccc::ddd inside aaa because xxx\yyy is open.

Notice that the short name does not start with a backslash; A name starting with a backslash is always a full name.

The namespace that a certain scope (i.e. interface/class/implementation) belongs to is (implicitly) open inside that scope.

Program Sections

Sections are used to declare and define entities in scopes.

Section :
   ConstantsSection
   DomainsSection
   PredicatesSection
   ConstructorsSection
   PropertiesSection
   FactsSection
   ClausesSection
   ConditionalSection

Section: ConstantsSection, DomainsSection, PredicatesSection, ConstructorsSection, FactsSection, ClausesSection, PropertiesSection, ConditionalSection

Not all sections can occur in all kinds of scopes, please refer to the description of Interfaces, Class Declarations, and Class Implementations for further details.

Conditional sections are described in Conditional Compilation.

Domains

Domains Sections

A domain section defines a set of domains in the current scope (see Interface, Class Declaration, and Class Implementation).

DomainsSection:
    domains DomainDefinition-dot-term-list-opt

Domain Definitions

A domain definition defines a named domain in the current scope.

DomainDefinition:
    DomainName FormalTypeParameterList-opt = DomainExpression

If the domain on the right hand side denotes an interface or a compound domain, then the defined domain is synonym (i.e. identical) to the type expression. Otherwise the defined domain becomes a subdomain of the domain denoted by the domain expression. Here a domain name DomainName should be a lower case identifier.

There are certain places where you must use a domain name rather than a type expression:

  • as a declaration of a formal argument type;
  • as a type of a constant or a fact variable;
  • as a type in a list domain.

Domain Expressions

A domain expression denotes a type in a domain definition:

DomainExpression: one of
    TypeName
    CompoundDomain
    ListDomain
    PredicateDomain
    IntegralDomain
    RealDomain
    TypeVariable
    ScopeTypeVariable
    TypeApplication

Type Expressions

The full range of DomainExpressions can only be used in a domain definition. TypeExpression is a subset of these expressions that are used in other many other contexts.

TypeExpression: one of
    TypeName
    ListDomain
    TypeVariable
    ScopeTypeVariable
    TypeApplication

Type Names

A type name is either an interface name or the name of a value domain. We use the term value domain to specify domains whose elements are immutable (unchangeable). Here we can say that objects, belonging to domains correspondent to interface names, have mutable state and terms of any other domains are immutable. So actually value types are everything except object types. A type name (obviously) denotes the type corresponding to the name of an existing domain.

TypeName: one of
    InterfaceName
    DomainName
    ClassQualifiedDomainName
InterfaceName:
    LowercaseIdentifier
DomainName:
    LowercaseIdentifier
ClassQualifiedDomainName:
    ClassName::DomainName
ClassName:
    LowercaseIdentifier

Here InterfaceName is an interface name, DomainName is a value domain name, and ClassName is a class name.

Example
domains
    newDomain1 = existingDomain.
    newDomain2 = myInterface.

In this example the domain name existingDomain and the interface name myInterface are used to define new domains.

Compound Domains

Compound domains (also known as algebraic data types) are used to represent lists, trees, and other tree structured values. In its simple forms compound domains are used to represent structures and enumeration values. Compound domains can have a recursive definition. They can also be mutually/indirectly recursive.

CompoundDomain:
   Alignment-opt FunctorAlternative-semicolon-sep-list
Alignment:
    align IntegralConstantExpression

Here IntegralConstantExpression is an expression, which must be compile time evaluated to an integral value.

A compound domain declaration declares a list of functor alternatives with optional alignment. Alignment must be 1, 2 or 4.

If a compound domain consists of one functor alternative, then it is considered as structure and has representation, which is binary compatible with the appropriate structure in language C.

FunctorAlternative: 
    FunctorName FunctorName ( FormalArgument-comma-sep-list-opt )

Here FunctorName is the name of a functor alternative it should be a lower case identifier.

FormalArgument:
    TypeExpression ArgumentName-opt

Here ArgumentName can be any upper case identifier. The compiler ignores it.

Compound domains have no subtype relations to any other domains.

If a domain is defined as being equal to a compound domain, then these two domains are synonym types rather than subtypes. Meaning that they are just two different names for the same type.

Example
domains
    t1 = empty(); cons(integer V, t1 Tail).

t1 is a compound domain with two alternatives. The first alternative is the null-ary functor empty(), while the second alternative is the two-ary functor cons, which takes an integer and a term of the domain t1 itself as arguments. So the domain t1 is recursively defined.

The following expressions are terms of the domain t1:

empty
cons(77, empty())
cons(33, cons(44, cons(55, empty())))

In the example above we used parenthesis after the null-ary function empty. Such parenthesis are optional in all situations, except in a domain definition consisting only of a single null-ary functor. In that case parenthesis are required to distinguish it from a synonym/subtype definition.

Example

t1 is a compound domain with a single null-ary functor, whereas t2 is defined to be synonym to t1.

domains 
    t1 = f(). 
    t2 = t1.
Example
domains 
    t1 = nil; subt2(t2). 
    t2 = hh(t1, t1).

t1 is a compound domain with two alternatives. The first alternative is the null-ary functor nil, while the second alternative is the unary functor subt2, which takes a term of the domain t2 as argument. t2 is a compound domain with one alternative the functor hh, which takes two t1 terms as argument. So the domains t1 and t2 are mutually recursive.

The following are terms in the domain t1:

nil 
subt2(hh(nil, nil)) 
subt2(hh(subt2(hh(nil, nil)), nil)) 
consg(hh(nil, g(hh(nil, nil)))) 
subt2(hh(subt2(hh(nil, nil)), subt2(hh(nil, nil))))

List Domains

List domains represent sequences of values of a certain domain. Thus, all elements in a T list must be of type T.

ListDomain:
    TypeExpression *

T* is the type of lists of T elements.

The following syntax is used for lists:

ListExpression:
    [ Term-comma-sep-list-opt ]
    [ Term-comma-sep-list | Tail ]
Tail:
    Term

Here Tail is a term which should have a value of the ListDomain type. Each Term should be of typeName type.

Actually, lists are just compound domains with two functors: [] denoting the empty list and the mix-fix functor [HD|TL] denoting the list with head HD and tail TL. The head must be of the underlying element type, whereas the tail must be a list of relevant type.

Lists are however syntactically sugared.

[E1, E2, ..., En | L ] is shorthand for [E1 | [ E2 | [ ...[ En | L ]...] ] ]

[E1, E2, ..., En] is shorthand for [E1, E2, ..., En | [] ], which in turn is shorthand for [E1 | [ E2 | [ ...[ En | [] ]...] ] ].

Predicate Domains

Values of a predicate domain are predicates with the same "signature", i.e. the same argument and return types, the same flow pattern and the same (or stronger) predicate mode.

The details concerning predicate domains are described in Predicate Domains.

But notice that predicate domains that are used in domain definitions (in a domains section) can at most state one flow.

Integral Domains

Integral domains are used for representing integral numbers. They are divided in two main categories for signed and unsigned numbers. Integral domains can also have different representation size. The predefined domains integer and unsigned represent signed and unsigned numbers with natural representation length for the processor architecture (i.e. 32bit on a 32bit machine, etc).

IntegralDomain:
     DomainName-opt IntegralDomainProperties

If a DomainName is stated in front of the IntegralDomainProperties, then this domain must itself be an integral domain and the resulting domain will be child-type (i.e. subtype) of this domain. In that case IntegralDomainProperties may not violate the possibility of being a subtype, i.e. the range cannot be extended and the size cannot be changed.

IntegralDomainProperties:
    IntegralSizeDescription IntegralRangeDescription-opt
    IntegralRangeDescription IntegralSizeDescription-opt
 
IntegralSizeDescription:
    bitsize DomainSize
 
DomainSize: 
    IntegralConstantExpression

An integral size description declares the size DomainSize of the integral domain, measured in bits. The compiler implement such representation to the integral domain, which has no less than the specified number of bits. The value of DomainSize should be positive and no greater than the maximal value supported by the compiler.

If integral size description is omitted, then it will become the same as the parent domain. If there is no parent domain, it will become the natural size for the processor.

IntegralRangeDescription:
    [ MinimalBoundary-opt .. MaximalBoundary-opt ]
 
MinimalBoundary:
    IntegralConstantExpression
 
MaximalBoundary: 
    IntegralConstantExpression

An integral range description declares the minimal MinimalBoundary and the maximal MaximalBoundary limits for the integral domain. If a limit is omitted, then the range of the parent domain is used. If there is no parent domain, then the DomainSize is used to determine respectively maximum or minimum value.

Notice that the specified minimum value should not exceed the specified maximum value. That is:

MinimalBoundary <= MaximalBoundary

Also the minimal MinimalBoundary and the maximal MaximalBoundary limits should satisfy the limits implied by the specified bit size bitsize.

The domain bit size DomainSize value and values of the minimal MinimalBoundary and the maximal MaximalBoundary limits must be calculated while compiling time.

Real Domains

Real domains are used to represent numbers with fractional parts (i.e. floating point numbers). Real domains can be used to represent very large and very small numbers. The built-in domain real have the natural precision for the processor architecture (or the precision given by the compiler).

RealDomain:
     DomainName-opt RealDomainProperties

If a DomainName is stated in front of the RealDomainProperties, then this domain must itself be a real domain and the resulting domain will be a subtype of this domain. In that case RealDomainProperties may not violate the possibility of being a subtype, i.e. the range cannot be extended and the precision cannot be increased.

RealDomainProperties: one of
    RealPrecisionDescription RealRangeDescription-opt
    RealRangeDescription RealPrecisionDescription
RealPrecisionDescription:
    digits IntegralConstantExpression

The real precision description declares precision of the real domain, measured in number of decimal digits. If precision is omitted then it will become the same as for the parent domain. If there is no parent domain, then it will be the natural precision for the processor or given by the compiler (in Visual Prolog v.6 the compiler limit is 15 digits). Precision have an upper and a lower limits given by the compiler, if the precisions larger than that limit is used the numbers will only obtain the processor (compiler) specified precision anyway.

RealRangeDescription:
    [ MinimalRealBoundary-opt .. MaximalRealBoundary-opt ]
 
MinimalRealBoundary:
    RealConstantExpression
 
MaximalRealBoundary: 
    RealConstantExpression

Here RealConstantExpression is an expression, which must be compile time evaluated to a floating point value. That is the real domain precision and limits must be calculated while compiling time.

The real range description declares minimal and maximal limits for the real domain. If a limit is omitted then it will be the same as for the parent domain. If there is no parent domain then the largest possible range for the precision will be used.

Notice that the specified minimum value should not exceed the specified maximum value. That is:

MinimalBoundary <= MaximalBoundary

Generic Domains

This section contains the formal syntax for generic domains, for a more complete introduction to generics please see the tutorial Objects and Polymorphism and the section Generic Interfaces and Classes.

FormalTypeParameterList:
     TypeVariable-comma-sep-list-opt

A formalTypeParameterList is a list of typeVariables

TypeVariable:
    UpperCaseIdentifier

A TypeVariable is an upper case identifier. In a domain declaration the type variable must be bound in the FormalTypeParameterList on the left hand side of the domain definition. In a predicate declaration all free type variables are implicitly bound and scoped to that predicate declaration.

TypeApplication:
     TypeName {TypeExpression-comma-sep-list-opt }

A TypeApplication is the application of a typeName to a list of types. The type name must be generic and the number of formal type parameters must match the number of type expressions.

Universal and Root Types

Visual Prolog uses some internal types, called root types and universal types.

Universal Types

A number literal like 1 does not have any particular type, it can be used as a value of any type that contains 1, including real types.

We say that 1 have a universal type. Having a universal type means that it have any type, which can represent its value.

Arithmetic operations also return universal types.

Root Types

Arithmetic operations are very liberal with their operand requirements: You can add integers of any integer domain with each other.

We say that arithmetic operands takes root types as arguments. The integer root type is super-type of any integer type (regardless that it is not mentioned in their declarations). Hence any integer type can be converted to the integer root type, and, since the arithmetic operations exist for the root types, it means one of them will work on any integer domains.

The actual number of root types and which operands exist is a matter of library facilities, and outside the scope of this document to describe.

Constants

Constants Sections

A constants section defines a set of constants in the current scope.

ConstantsSection :
    constants ConstantDefinition-dot-term-list-opt

Constant Definitions

A constant definition defines a named constant, its type, and its value.

ConstantDefinition: one of
    ConstantName = ConstantValue
    ConstantName : TypeExpression = ConstantValue
ConstantName:
    LowerCaseIdentifier

The ConstantValue should be an expression, which can be evaluated at compile time and it should have the type of the correspondent domain. The ConstantName should be a lower case identifier.

The TypeExpression can be omitted only for the following built-in domains:

  1. Numerical (i.e. integral or real) constants. In this case, the corresponding anonymous numerical domain is adopted for a constant (see the numerical domains for details).
  2. Binary constants.
  3. String constants.
  4. Character constants.
Example
constants
    my_char = 'a'.
    true_const : boolean = true.
    binaryFileName = "mybin".
    myBinary = #bininclude(binaryFileName).

Predicates

Predicates Sections

A predicates section declares a set of object or class predicates in the current scope.

PredicatesSection :
   class-opt predicates PredicateDeclaration-dot-term-list-opt

The keyword class can be used only inside class implementations, since:

  • predicates declared in an interface are always object predicates and
  • predicates declared in a class declaration are always class predicates.

Predicate Declarations

The predicate declaration is used to declare the predicate in scopes in which the predicate declaration can be seen. When predicates are declared in an interface definition, this means that objects of the corresponding type must support these predicates. When predicates are declared in a class declaration, this means that the class publicly provides the declared predicates. And if predicates are declared in a class implementation, this means that the predicates are available locally. In all cases a corresponding definitions of the predicates must exist.

PredicateDeclaration :
   PredicateName : PredicateDomain LinkName-opt
   PredicateName : PredicateDomainName LinkName-opt
LinkName :
   as StringLiteral
PredicateName :
   LowerCaseIdentifier

Here PredicateDomainName is the name of a predicate domain declared in a domains section.

Only class predicates can have link names. If the link name is not stated then a link name is derived from the predicate name, the way this name is derived depends on the calling convention.

Predicate Domains

A predicate that returns a value is called a function, whereas a predicate that does not return a value is sometimes called an ordinary predicate, to stress that it is not a function.

PredicateDomain:
   ( FormalArgument-comma-sep-list-opt ) ReturnArgument-opt 
   PredicateModeAndFlow-list-opt CallingConvention-opt
FormalArgument:
   TypeExpression VariableName-opt
   Ellipsis
ReturnArgument:
    -> FormalArgument
VariableName:
   UpperCaseIdentifier

Predicate domains can have Ellipsis argument as the last FormalArgument in the FormalArgument-comma-sep-list.

Predicate domains can have an AnonymousIdentifier as a formal argument type to specify that the argument can be of any type.

PredicateModeAndFlow:
     PredicateMode-opt
     Suspending-opt
     FlowPattern-list-opt


Predicate Mode

The specified predicate mode applies for each member of a flow pattern list following it.

PredicateMode: one of
   erroneous 
   failure 
   procedure 
   determ 
   multi 
   nondeterm

Predicate modes can be described by the following sets:

erroneous = {} 
failure = {Fail} 
procedure = {Succeed} 
determ = {Fail, Succeed} 
multi = {Succeed, BacktrackPoint} 
nondeterm = {Fail, Succeed, BacktrackPoint}

If Fail is in the set it means that the predicate can fail. If succeed is in the set it means that the predicate can succeed. If BacktrackPoint is in the set it means that the predicate can return with an active backtrack point in it.

If such a set, say failure, is a subset of another set, say nondeterm, then we say that the mode is stronger than the other, i.e. failure is stronger than nondeterm.


A predicate domain actually contain all predicates (with correct type and flow), which have the mode specified or a stronger mode.

It is illegal to state a predicate mode for constructors, they always have the procedure mode.

Omitting of a predicate mode means procedure.

Suspending

Adding suspending to a predicate domain makes the predicate a suspending predicate

Suspending: 
   suspending

Flow Pattern

The flow pattern defines the input/output direction of the arguments, which in combination with functor domains can be structures with parts of a single argument being input and other parts of the same argument being output.

A flow pattern consists of a sequence of flows, each flow corresponds to an argument (fist flow to first argument, etc).

FlowPattern:
     ( Flow-comma-sep-list-opt ) AnyFlow
Flow: one of
    i
    o 
    FunctorFlow
    ListFlow
    Ellipsis

Ellipsis flow must match an ellipsis argument and can therefore be only the last flow in the flow pattern.

Ellipsis:
    ...

A functor flow FunctorFlow states a functor and flows of each of the components of that flow. The functor must of course be in the domain of the corresponding argument.

FunctorFlow:
    FunctorName ( Flow-comma-sep-list-opt )

A functor flow declaration cannot contain ellipsis flow.

List flows are just like functor flows, but with the same syntactic sugaring as the list domain.

ListFlow:
    [ Flow-comma-sep-list-opt ListFlowTail-opt]
ListFlowTail:
    | Flow

A list flow cannot contain ellipsis flow.

When declaring a predicate the flow can be omitted. Inside an implementation (i.e. for a local predicate) the needed flows are derived from the usages of the predicate. Inside an interface or a class declaration (i.e. for a public predicate) omitting flows means that all arguments are input.

The special flow pattern anyflow can be stated only in declarations of local predicates (i.e. in predicate declarations inside the implementation of a class). It means that the exact flow pattern(s) will be evaluated during the compilation.

Example
domains
    pp1 = (integer Argument1).

pp1 is a predicate domain. The predicates that have type pp1 takes one integer argument. Since no flow-pattern is stated the argument is input, and since no predicate mode is mentioned the predicates are procedure.

Example
domains
    pp2 = (integer Argument1) -> integer ReturnType.

Predicates of type pp2 take one integer argument and returns a value of type integer. Therefore, pp2 is actually a function domain and the predicates that have type pp2 are actually functions. Since no flow-pattern is stated the argument is input and since no predicate mode is mentioned the predicates are procedure.

Example
predicates
    ppp : (integer Argument1, integer Argument2) determ (o,i) (i,o) nondeterm (o,o).

The predicate ppp takes two integer arguments. It exists in three flow variants: (o,i) and (i,o), which are determ, and (o,o), which is nondeterm.

Calling Convention

The calling convention determines how arguments, etc. are passed to the predicate, it also determines how the link name is derived from a predicate name.

CallingConvention:
     language CallingConventionKind
CallingConventionKind: one of
     c thiscall stdcall apicall prolog

If a calling convention is not stated, then the prolog convention is assumed. The prolog calling convention is the standard convention used for Prolog predicates.

The calling convention c follows the C/C++ standard calling convention. The link name of a predicate is created from the predicate name by adding a leading underscore (_).

The calling convention thiscall follows the C++ standard calling convention for virtual functions. This calling convention uses the c link name strategy but sometimes it may use the different argument and stack handling rules. Calling convention thiscall can be applied to the object predicates only.

The calling convention stdcall uses the c link name strategy but it uses the different argument and stack handling rules. The following table shows the implementation of stdcall calling convention.


Feature Implementation
Argument-passing order Right to left.
Argument-passing convention By value, unless a compound domain term is passed. So it cannot be used to predicates with variable number of arguments.
Stack-maintenance responsibility Called predicate pops its own arguments from the stack.
Name-decoration convention An underscore (_) is prefixed to the predicate name.
Case-translation convention No case translation of the predicate name is performed.


The calling convention apicall uses the same argument and stack handling rules as stdcall, but for convenience to call MS Windows API functions apicall uses the naming conventions that are used by most MS Windows API functions. According to apicall naming conventions the link name of a predicate is constructed as follows:

  • a leading underscore (_) is prefixed to the predicate name;
  • the predicate name in which the first letter is changed in to a capital letter;
  • the 'A', the 'W' or nothing is suffixed, if the arguments and the return type indicate an ANSI, Unicode or neutral predicate, respectively;
  • on the 32bit platform (x86) the sign @ together with the number of bytes in the argument list is suffixed. But this is not used on the 64bit platform.
Example
predicates
     predicateName : (integer, string) language apicall

The argument types of this predicate indicates that it is a Unicode predicate (as string is the domain of Unicode strings). An integer and a string each occupies 4 bytes on the call stack and, therefore, the link name becomes:

_PredicateNameW@8

On x64 the name is:

_PredicateNameW

If apicall is used together with the "as" construction the name stated in the "as" construction is decorated in the same manner.

apicall can only be used directly in a predicate declaration, not in a predicate domain definition. In predicate domain definitions stdcall, must be used instead. A predicate declared with apicall calling convention cannot have clauses and it also cannot be resolved externally without explicit DLL name.

The following table compares implementations of c, apicall, and stdcall calling conventions (the prolog calling convention has the special implementation, which is not discussed here):

Keyword Stack cleanup Predicate name case-translation Link predicate name decoration convention
c Calling predicate pops the arguments from the stack. None. An underscore (_) is prefixed to the predicate name.
thiscall Calling predicate pops the arguments from the stack except the implicit This argument which is passed in the register. None. c link name strategy is used.
stdcall Called predicate pops its own arguments from the stack. None. An underscore (_) is prefixed to the predicate name.
apicall Called predicate pops its own arguments from the stack. The first letter of the predicate name is changed to the capital letter. An underscore (_) is prefixed to the name. The first letter is changed to the upper case. The 'A', the 'W' or nothing is suffixed. And on the 32bit platform (x86) the sign @ together with the number of bytes in the argument list is suffixed.

Visual Prolog notion of predicate domains covers both class and object members. Class members are handled straight forward, but the handling of object members requires attention. The invocation of an object predicate will get "back" in the context of the object to which the member belongs.

Example Assume the following declarations:
interface actionEventSource
domains
     actionListener = (actionEventSource Source) procedure (i).
predicates
     addActionListener : (actionListener Listener) procedure (i).
     ... end interface

Also assume a class button_class which supports the actionEventSource. The event is sent when the button is pressed. In myDialog_class class, which implements a dialog, I create a button and I want to listen to its action events, so that I can react on button presses:

implement myDialog_class 
clauses
    new() :-
        OkButton = button_class::new(...),
        OkButton:addActionListener(onOk),
        ...
facts
    okPressed : () determ.
predicates
    onOk : actionListener.
clauses
    onOk(Source) :-
        assert(okPressed()).
end implement

The important thing about the example is that onOk is an object member and that, when the button is pressed, the invocation of the registered onOk will bring us back in the object that owns onOk. This means that we have access to the object fact okPressed, so that we can assert it.

Decorated

Sometimes a name must have the _...@N decoration, but the default from apicall is wrong. In such cases decorated, decoratedA and decoratedW can be used to control the decoration:

predicates
    myPredicate : (string X)  language stdcall as decorated.

In this case the link name will be "_MyPredicate@4", where apicall would make it "_MyPredicateW@4".

predicates
    myPredicate : (pointer X)  language stdcall as decoratedA.

In this case the link name will be "_MyPredicateA@4", where apicall would make it "_MyPredicate@4".

predicates
    myPredicate : (pointer X)  language stdcall as decoratedW.

In this case the link name will be "_MyPredicateW@4", where apicall would make it "_MyPredicate@4".

All of them change the start of the name from xxxx to _Xxxx and all of them put @N behind. The first never uses a suffix; the second always uses A and the third always uses W. This means that the programmer is responsible for deciding which suffix is needed. But he needs not to worry about calculating argument size and initial "_X".

Constructors Sections

A constructors section declares a set of constructors. The constructors belong to the scope in which the constructors section occurs (see class declaration and class implementation).

ConstructorsSection :
   constructors ConstructorDeclaration-dot-term-list-opt

Constructor sections can only occur in declarations and implementations of classes that construct objects.

Constructor Declarations

A constructor declaration declares a named constructor of a class.

A constructor actually has two associated predicates:

  • A class function, which returns a new constructed object.
  • An object predicate, which is used when initializing inherited objects.

An associated constructor object predicate is used to perform an object initialization. This predicate can only be called from the constructor in the class itself and from a constructor in a class that inherits from the class (i.e. base class initialization).

ConstructorDeclaration :
   ConstructorName : PredicateDomain

It is illegal to state a predicate mode for constructors, constructors always have procedure mode.

Example Consider the following class:
class test_class : test
    constructors
        new : (integer Argument).
end class test_class

The associated class level predicate has the following signature:

class predicates
    new : (integer) -> test.

Whereas the associated object level predicate has the following signature:

predicates
    new : (integer).

Also consider the following implementation:

implement test2_class inherits test_class
    clauses
        new() :-
            test_class::new(7),  % invoke the base class constructor on "This"
            p(test_class::new(8)). % create a new object of the base class and pass it to p(...)
    ...


The first call to test_class::new does not return a value, therefore it is a call to the non-function object version of the constructor. I.e. it is an invocation of the base class constructor on "This".

The second call on the other hand does return a value, therefore it is a call to the class function version of the constructor. I.e. we are creating a new object.

Predicates from Interface

An interface can support a subset of another interface by stating the predicates in a predicates from section. The predicates from section names the interface and all supported predicates. The predicates are stated by name or by name and arity.

If an interface supports a subset of another interface it is neither subtype or super-type related to the other interface.

The important thing about the predicates from section is that the mentioned predicates retain their origin interface. Therefore:

  • there will be no support conflict with any predicates from the origin interface;
  • they can be inherited as the predicates from the origin interface.
PredicatesFromInterface :
    predicates from InterfaceName PredicateNameWithArity-comma-sep-list-opt

PredicatesFromInterface can only be used in interface definitions.

Example
interface aaa
    predicates
        ppp : ().
        qqq : ().
end interface aaa
 
interface bbb
    predicates from aaa
        ppp
    predicates
        rrr : ().
end interface bbb
 
interface ccc supports aaa, bbb
end interface ccc

Even though aaa and bbb both declare a predicate ppp, ccc can support them both without any conflicts, because ppp has aaa as an origin interface in all cases.

Example
interface aaa
    predicates
        ppp : ().
        qqq : ().
end interface aaa
 
interface bbb
    predicates from aaa
        ppp
    predicates
        rrr : ().
end interface bbb
 
class aaa_class : aaa
end class aaa_class
 
class bbb_class : bbb
end class bbb_class
 
implement aaa_class inherits bbb_class
    clauses
        qqq().
end implement aaa_class

aaa_class can inherit ppp from bbb_class, because ppp in both classes has aaa as origin interface.

Extension Predicates

Extension predicates is a syntactic sugaring, which makes it possible use class predicates as if they were object predicates.

Example A typical use case is for code like this:
clauses
    writeMsg(Stream, fct(Receiver, Sender)) :-
        Stream:write("Hello "),
        writeReceiver(Stream, Receiver),
        Stream:write(", how do you do?\nRegards "),
        writeSender(Stream, Sender).

This code writes a number of things to Stream, but some of the calls are object calls Stream:write(...) with the stream in front of a colon, while others are class calls writeReceiver(Stream, ...) with the stream as first argument.

Declaring writeReceiver and writeSender as extension predicates will make all the calls have the same syntactic form:

clauses
    writeMsg(Stream, fct(Receiver, Sender)) :-
        Stream:write("Hello "),
        Stream:writeReceiver(Receiver),
        Stream:write(", how do you do?\nRegards "),
        Stream:writeSender(Sender).

In this code the predicates writeReceiver and writeSender seems to be part of the Streams interface. So they appear to have extended the Streams interface.

Extension predicates can also be used to give give a more natural code flow for binary operations:

Example (Binary operations
class matrix
    add : (matrix A, matrix B) -> matrix R.
    add2 : (matrix A [this], matrix B) -> matrix R.  % extension
 
clauses
   xxx(A, B, C) = add(add(A, B), C).  % add must be used in front of the operands
clauses
   yyy(A, B, C) A:add2(B):add2(C). % add2 can be written infix

You should notice that such infix operations are left associative, if you want add(A, add(B, C)) you must write: A:add2(B:add2(C)). You should also notice that there is no precedence in this context.

A + B * C = A + (B * C) -> A:add2(B:mult2(C))
A:add2(B):mult2(C) -> (A + B) * C

Extension predicates can also support a cascading data flow style:

Example Cascading data flow style:
clauses
    getQ(A, X, F) = qqq::new(A):select(12, X, getList()):filter( { (V) :- V = F } ).

The created qqq object flows into the select predicate the result of this flows into the filter predicate and the result of this is returned. Here select and filter could be regular object predicates declared in an interface, but they can also be extension predicates. Assuming they are extension predicates then the corresponding code with regular class predicates would/could look like this:

clauses
    getQ(A, X, F) = filter(select(qqq::new(A), 12, X, getList()), { (V) :- V = F } ).

An extension predicate is a class predicate whose first argument is marked with the attribute [this].

Example If the regular version of the writeReceiver and writeSender predicates above are declared like this:
class predicates
    writeReceiver : (outputStream Stream, receiver Receiver).
    writeSender : (outputStream Stream, sender Sender).

Then the corresponding extension predicates are declared like this:

class predicates
    writeReceiver : (outputStream Stream [this], receiver Receiver).
    writeSender : (outputStream Stream [this], sender Sender).

I.e. the first argument is marked with the attribute [this].

Extension predicates can also be declared for non-object types.

Example We can for example declare a length extension predicate for lists like this:
class predicates
    length : (Type* List [this]) -> positive Length.

And then we can call it like this:

L1 = List:length(),
L2 = [1, 2]:length(),
L3 = Obj:theList:length() + 7,

Notice that :length() can be put after anything that evaluates to a list.

It is illegal to declare an extension predicate on an interface type if that extension predicate is conflicting with a predicate that exist in the interface itself.

Example Given the interface aaa with predicate ppp/0:
interface aaa
predicates
    ppp : ().
end interface aaa

the following extension predicate is illegal:

class predicates
    ppp : (aaa A [this]).  % Illegal: aaa already has a ppp/0 predicate

Extension predicates follows the visibility rules of class predicates.

Example Given this class
class listExt
predicates
    length : (A* List) -> integer Length.
end class listExt

This code is illegal

implement myClass
clauses
    ppp(L) = L:length(). % length is not visible
end implement myClass

opening the listExt class makes the predicate visible:

implement myClass
    open listExt
clauses
    ppp(L) = L:length(). % length is visible because listExt is opened
end implement myClass

Extension predicates can be qualified with namespace and class:

Example Using qualification
implement myClass
clauses
    ppp(L) = L:listExt::length(). % length is visible due to the qualification listExt::...
end implement myClass

Several suitable extension predicates may be visible in a certain context, and thus cause ambiguity. Qualification can resolve such ambiguity.

Example Given listExt::length above and a similar/identical extension predicate in listExt2:
class listExt2
predicates
    length : (A* List) -> integer Length.
end class listExt2

The following code have an ambiguous reference to length:

implement myClass
    open listExt, listExt2
clauses
    ppp(L) = L:length(). % length is ambiguous because it is visible both in listExt and listExt2
end implement myClass

Qualification can be used to resolve the ambiguity:

implement myClass
    open listExt, listExt2
clauses
    ppp(L) = L:listExt2::length(). % length is the one from listExt2
end implement myClass

Arity

A predicate that takes N arguments are said to be N-ary, or to have arity N. Predicates with different arity are always different predicates, even if they have the same name.

In most situations the arity of a predicate is obvious from the context in which the predicate is mentioned. But in, for example, predicatesFromInterface sections and resolve qualifications the arity is not obvious.

In order to distinguish between different arities of predicates in predicates from sections and in resolve qualifications, predicate names can (optionally) be stated with arity.

The following arities are possible:

  • Name/N meaning an ordinary predicate (i.e. not a function) Name of arity N.
  • Name/N-> meaning a function Name of arity N.
  • Name/N... meaning an ordinary predicate Name with N arguments followed by an Ellipsis argument (i.e. a varying number of arguments). (Ellipsis "..." can be used in predicate and predicate domain declarations as the last formal argument. In this case it means that the declared predicate (predicate domain) can have a variable number of arguments. Ellipsis flow must match an ellipsis argument and can therefore be only the last flow in the flow pattern.)
  • Name/N...-> meaning a function Name with N arguments followed by an ellipsis argument.
PredicateNameWithArity :
   PredicateName Arity-opt
Arity : one of
   / IntegerLiteral Ellipsis-opt
   / IntegerLiteral Ellipsis-opt ->

In Name/0... and Name/0...->. the zero is optional and can thus be written as Name/... and Name/...->, respectively.

See also

These attributes are specifically related to predicates

Properties

Properties are named values associated with classes and objects. Actually they are syntactic sugar for get/set predicates for the property value. And in that sense they are a language incarnation of a frequently used programming pattern.

Properties Sections

A properties section declares a set of object or class properties in the current scope.

PropertiesSection :
   class-opt properties PropertyDeclaration-dot-term-list-opt

The keyword class can be used only inside class implementations, since:

  • properties declared in an interface are always object properties and
  • properties declared in a class declaration are always class properties.

Property Declaration

PropertyDeclaration :
    PropertyName : PropertyType FlowPattern-list-opt
FlowPattern: one of
    (i)
    (o)

It is possible to get the value of a property that has the (o) flow, and it is possible to set the value of a property that has the (i) flow. If the flow patterns are not stated, both (i) and (o) are assumed, so it is possible bot to set and get the value of such properties.

Though it is legal to state (i) and (o) simultaneously, it is considered better practice to omit them in the get+set case.

Example Assume we declare them with an i/o pattern as:
properties
    durationO : real (o). % a get only property
    durationI : real (i). % a set only property
    durationIO : real (i) (o). % a "full" property, which can both be set and get.
    duration : real. % equivalent to the declaration above and preferred.

In the sequel we will use the use the following example:

Example
interface ip
properties
   duration : real.
   initialized : boolean (o).
   scale : real.
end interface
duration and scale are get+set properties, and initialized is a get-only property.

Properties are used like fact variables. It is possible to qualify properties for with a scope name or an object.

Example X is an object that supports the interface ip
X:duration := 5,
if true = X:initialized then ... else ... end if,
X:scale := 2.56,
....

Inside an implementation of a class that supports ip you access the properties as if they were facts.

duration := 5,
if true = initialized then ... else ... end if,
scale := 2.56,
....

Implementation

A property is implemented by defining a function for getting the value and a predicate to set it.

Example
clauses
    % implementation of the get function of the duration property
    duration() = duration_fact.
 
clauses
    % implementation of the set predicate of the duration property
    duration(D) :-
        duration_fact := D / scale.

Alternatively the property can be implemented as a fact variable with the same name as the property.

Example
facts
    % the initialized property is implemented by a fact variable
    initialized : boolean := false.
    % the scale property is implemented by a fact variable
    scale : real := 1.2

In this case the compiler will implicitly provide clauses that implement the get and set predicates.

Example For the two fact variable implementations above the compiler will provide clauses corresponding to this
clauses
    % implicit get clause for the initialized property
    initialized() = initialized.
 
clauses
    % implicit get clause for the scale property
    scale() = scale.
 
clauses
    % implicit set clause for the scale property
    scale(V) :-
        scale := V.
As mentioned below it would not be legal to state these clauses in a program.

It is illegal to have set and get predicates and a fact with the same name, meaning that a property is either implemented by programmer provided clauses or by a fact; mixed implementation is not possible.

Example We want to send a changed event when the duration property changes value. Therefore we have to implement the property by predicates, and use a fact variable with an other name for storing the value.
properties
    duration : integer.
facts
    duration_fact : integer.
clauses
    duration() = duration_fact.
clauses
    duration(D) :-
        OldDuration = duration_fact,
        duration_fact := D,
        OldDuration <> D,
        !,
        sendChanged().
    duration(_D).

It is not possible to use the duration predicates as predicates (they are not declared as predicates, but as a property; it is just the way the get and set of the property are implemented).

But in the predicate names are "used" - so you cannot declare predicates duration\1 or duration\0->.

As mentioned above properties are always implemented by get/set predicates even when the program implement them by a fact variable.

Properties from Interface

An interface can support a subset of another interface by stating the properties in a properties from section. The properties from section names the interface and all supported properties.

If an interface supports a subset of another interface it is neither subtype or super-type related to the other interface.

The important thing about the properties from section is that the mentioned properties retain their origin interface. Therefore:

  • there will be no support conflict with any properties from the origin interface;
  • they can be inherited as the properties from the origin interface.
PropertiesFromInterface :
    properties from InterfaceName PropertyName-comma-sep-list-opt

PropertiesFromInterface can only be used in interface definitions.

Example
interface aaa
   properties
       pp : integer.
       qq : boolean.
end interface aaa
 
interface bbb
   properties from aaa
       pp
   properties
       rr : string.
end interface bbb
 
interface ccc supports aaa, bbb
end interface ccc

Even though aaa and bbb both declare a property pp, ccc can support them both without any conflicts, because pp has aaa as an origin interface in all cases.

Example
interface aaa
   properties
       pp : integer.
       qq : boolean.
end interface aaa
 
interface bbb
   properties from aaa
       pp
   properties
       rr : string.
end interface bbb
 
class aaa_class : aaa
end class aaa_class
 
class bbb_class : bbb
end class bbb_class
 
implement aaa_class inherits bbb_class
   facts
       pp_fact(): integer.
   clauses
       pp()= pp_fact-3.
   clauses
       pp(D):- pp_fact:=D+3.
end implement aaa_class

aaa_class can inherit pp from bbb_class, because pp in both classes has aaa as origin interface.

Facts

Facts Sections

A facts section declares a fact database, consisting of a number of facts. The fact database and the facts belong to the current scope.

Fact databases can exist on a class level as well as on an object level.

Facts sections can be declared only in class implementations.

If the fact database is named, an additional compound domain is implicitly defined. This domain has the same name as the fact section and has functors corresponding to the facts in the fact section.

If the facts section is named, the name denotes a value of the build-in domain factDB. The save and consult predicates accept values of this domain.

FactsSection :
   class-opt facts FactsSectionName-opt FactDeclaration-dot-term-list-opt
FactsSectionName :
   - LowerCaseIdentifier

Fact Declarations

A fact declaration declares a fact of a fact database. A fact declaration is either a fact variable, or a functor fact.

FactDeclaration :
   FactVariableDeclaration
   FactFunctorDeclaration
FactFunctorDeclaration :
   FactName : ( Argument-comma-sep-list-opt ) FactMode-opt
FactName :
   LowerCaseIdentifier

A fact functor declaration has nondeterm fact mode by default.

A fact functor can have initialization via clauses section. In such case values in the clauses should be expressions, which can be evaluated at compile time.

FactMode : one of
   determ nondeterm single

If mode is single, then a fact always has one and only one value and the assert predicate overwrites old value with a new one. Predicate retract cannot be applied to single facts.

If mode is nondeterm, then the fact can have zero, one, or any other number of values. If mode is determ, then the fact can have zero or one value. If fact has zero values, then any read access to it gives fail.

Fact Variable Declarations

A fact variable is similar to a one-argument single functor fact. However, syntactically it is used as a mutable variable (i.e. with assignment).

FactVariableDeclaration :
   FactVariableName : Domain InitialValue-opt
InitialValue :
   := Term
   := erroneous
FactVariableName :
   LowerCaseIdentifier

The initialization expression InitialValue must evaluate to a value of Domain type.

The initialization expression can be omitted (only) if the fact variable is initialized in a constructor. Class fact variables should always have an initialization expression.

The keyword erroneous can be used as value to be assigned to fact variables. That is both lines below are valid:

facts
   thisWin : vpiDomains::windowHandle := erroneous.
clauses
   p() :- thisWin := erroneous.

The idea of assigning erroneous value is to give clear runtime error if some code uses uninitialized fact variable by mistake.

Visual Prolog has late initialization of fact variables, meaning that the initialization code for a fact variable is not execute before and unless it is needed.

Example

Consider this code:

facts
    current : integer := initializeCurrent().

The current is initialized by calling the function initializeCurrent.

Initially nothing happens. If the first access to current is a read access to its value as in this code:

...
stdio::writef("Current = %\n", current),
...

then before the write takes place current will be initialized by evaluating its initialization expression (i.e. by calling initializeCurrent).

If on the other hand the first access to current is a write access to its value as in this code:

...
current := 7,
stdio::writef("Current = %\n", current),
...

then the initialization expression will never be evaluated, since the code never needed the value.

The behavior of the code is very similar to this code:

facts
    current_fact : integer := erroneous.
 
properties
    current : integer.
 
clauses
    current() = current_fact :-
        if isErroneous(current_fact) then
            current_fact := <initialize>
        end if.
 
clauses
    current(P) :-
        current_fact := P.

When the current property is read the fact will be initialized if it is currently erroneous. Or to put it differently: the initialization is done on a by-need basis.

The main difference is that the fact variable is never erroneous when using the late fact initialization.

If the initialization expression can be evaluated to a constant at compile time then the fact is initialized immediately, rather than late.

Late initialization of facts is threadsafe in the following way: if two or more threads are reading a late fact simultaneously, they will/may potentially all execute the initialization code. But only one of the results will be used as the initial value, and all the threads will receive that value; all the other calculated initialization values will be discarded.

The attribute immediate can be used to enforce immediate initialization of a fact variable.

Example

This code will initialize current immediately:

facts
    current : integer := initializeCurrent() [immediate].

Facts

Facts can only be declared in a class implementation and subsequently they can only be referenced from this implementation. So the scope of facts is the implementation in which they are declared. But the lifetime of object facts is the lifetime of the object to which they belong. Likewise the lifetime of class facts are from program start to program termination.

Example The following class declares an object fact objectFact and a class fact classFact:
implement aaa_class
   facts
       objectFact : (integer Value) determ.
   class facts
       classFact : (integer Value) determ.
   ...
end implement aaa_class

Constant fact variable

A constant fact variable is a fact variable that never changes value after it has been initialized. It can for example be a global "table" that initialized at some point and then used for lookup afterwards. Or an "id" in an object identifying what the object represents.

A fact variable is a constant fact variable if it is market with the attribute [constant].

A constant class fact variable can only be assigned:

A constant object fact variable can only be assigned:

  • Directly in the declaration
  • Or in a constructor
Example Declare and initialize a table.
class facts
  translationTable : mapP{string, string} [constant].
 
 class predicates
    initialize : () [classInitializer].
clauses
    initialize() :-
        % create the table
        translationTable := Table.
Example Make sure that the id property of the object is never changed (after creation):
facts
    id : unsigned [constant].
 
clauses
   new(Id) :-
      id := Id.

Clauses

Clauses Sections

A clauses section consists of a set of clauses. The clauses section contains implementations of predicates or initial values of facts.

A single clause section can have clauses for several predicates and facts. On the other hand, all clauses for one predicate/fact (the same name and arity) must be grouped together in one clauses section and without intervening clauses of other predicates/facts.

ClausesSection :
   clauses Clause-dot-term-list-opt

See also Guards in Monitors.

Clauses

Clauses are used to define predicates. A single predicate is defined by a set of clauses. Each clause is executed in turn until one of them succeeds, or there is no more clauses left to execute. If no clause succeeds the predicate fails.

If a clause succeeds and there are more relevant clauses in a predicate left, the program control can later backtrack to the clauses of this predicate to search for other solutions.

Thus, a predicate can fail, succeed, and even succeed multiple times.

Each clause has a head and optionally a body.

When a predicate is called the clauses are tried in turn (from top to bottom). For each clause the head is unified with the arguments from the call. If this unification succeeds then the body of the clause (if such one exist) is executed. The clause succeeds if the match of the head succeeds and the body succeeds. Otherwise it fails.

A clause consists of a head and an optional body.

Clause :
   ClauseHead ReturnValue-opt ClauseBody-opt .
ClauseHead :
   LowercaseIdentifier ( Term-comma-sep-list-opt )
ReturnValue :
   = Term
ClauseBody :
   :- Term

See also Guards in Monitors.

Goal Section

The goal section is the entry to a program. When the program starts it executes the goal, when the goal is executed, the program exits.

GoalSection :
   goal Term.

The goal section consists of a clause body. The goal section defines its own scope, therefore all invocations should contain class qualifications.

The goal must have procedure mode.

Terms

This section describes terms and how execution/evaluation of terms and clauses proceeds.

Semantically, there are two kinds of terms: formulas and expressions.

  • Expressions represent values, like the number 7.
  • Formulas represent logical statements, like "the number 7 is greater than the number 3".

Syntactically the two kinds have a huge overlap and therefore the syntax unites the two kinds into terms.

The following definition of Term is simplified, in the sense that it includes syntactic constructions that are not legal. For example, one cannot legally write ! + !. We do however believe that using this simple syntax description in combination with intuitive understanding of language concepts, the type system, and the operator hierarchy described below is better for most purposes.

Term:
    ( Term )
    Literal
    Variable
    Identifier
    MemberAccess
    PredicateCall
    PredicateExpression
    UnaryOperator Term
    Term Operator Term
    Cut
    Ellipsis
    FactvariableAssignment

Backtracking

The evaluation of a Prolog program is a search for a "solution" to the goal. Each step in the search for a solution can either succeed or fail. At certain points in the program execution there are more than one possible choices for finding a solution. When such a choice point is met a so called backtrack point is created. A backtrack point is a recording of the program state plus a pointer to the choice that was not executed. If it turn out that the original choice could not provide the solution (i.e. if it fails), then the program will backtrack to the recorded backtrack point. Thereby restoring the program state and pursuing the other choice. The mechanism will be described and exemplified in details in the following sections.

Literals

Literals have universal type.

Literal:
   IntegerLiteral
   RealLiteral
   CharacterLiteral
   StringLiteral
   BinaryLiteral
   ListLiteral
   CompoundDomainLiteral

See also Literals (in Lexical Elements)

Variables

Variables in Visual Prolog are immutable: once they are bound to a value they retain that value, but backtracking can unbind the variable again during the process of restoring a previous program state.

A variable can thus be bound (during unification and matching), if it is already bound then it evaluates to the value that it is bound to.

Variables are names starting with an upper-case letter or with an underscore (_), followed by a sequence of letters (both uppercase and lowercase), digits, and underscore characters (all in all called an UppercaseIdentifier):

Variable:
    UppercaseIdentifer

The following are examples of valid variable names:

My_first_correct_variable_name
_
_Sales_10_11_86

while the next two are invalid:

1stattempt
second_attempt

The variable consisting of single underscore character (i.e. _) is known as the anonymous variable. The anonymous variable is used in patterns and bindings where the corresponding value is of no interest and should be ignored. Every occurrence of the anonymous variable is an independent anonymous variable, i.e. even though the anonymous variable is used several times in a single clause they have no relation to each other.

If variables that starts with an underscore are not anonymous, but they are still intended for values of no interest that should be ignored. The compiler will issue a warning if the value of such a warning is actually not ignored.

Prolog variables are local to the clause in which it occurs. That is, if two clauses each contain a variable called X, these X-s are two distinct variables.

A variable is said to be free when it is not yet associated with a term and to be bound or instantiated when it is unified with a term.

The Visual Prolog compiler does not make a distinction between upper and lower case letters in names, except for the first letter. This means that the two variables SourceCode and SOURCECODE are the same.

Identifier

Identifier: one of
    MemberName
    GlobalScopeMembername
    ScopeQualifiedMemberName
 
MemberName:
    LowerCaseIdentifier

Identifiers are used to refer to named entities (i.e. classes, interfaces, constants, domains, predicates, facts, ...).

An identifier can just be a lower case identifier (i.e. a lowercase letter followed by a sequence of letters, numbers and underscore characters).

Many entities can have the same name. So it may be necessary or desirable to qualify the lowercase identifier the name of the particular scope of interest, or to state that the name is in the global namespace.

Example These are examples of unqualified identifiers:
integer
mainExe
myPredicate

Global Entities Access

The only global entities, which exist in Visual Prolog, are built-in domains, predicates, and constants. Global names are directly accessible in any scope. There might however exist situations where a global name is shadowed by a local or imported name. In that case the global entity can be qualified with a double colon '::' (without a prefixed class/interface name). The double colon can be used everywhere, but the most important place is where an interface name is used as formal parameter type specifier.

GlobalScopeMemberName:
    :: MemberName
Example The built-in domain integer is defined in the global scope, to avoid ambiguity or stress that it is this particular domains you can use the global scope member name:
::integer

Class/Interface Member Access

Static members of classes and interfaces are accessed by means of qualification with the class name (and optionally a namespace prefix):

ScopeQualifiedMemberName
    NamespacePrefix-opt ScopeName :: MemberName
 
NamespacePrefix:
    NamespaceIdentifier-opt \
 
ScopeName:
    LowercaseIdentifier

The ScopeName is the name of the class or interface that defines/declares the name.

Namespace prefixing is explained in: Referencing names in namespaces.

Some names can be accessed without qualification, see scoping & visibility.

Predicate Call

A predicate call have the form

PredicateCall:
     Term ( Term-comma-sep-list-opt )

The first term must be an expression that evaluates to a value with predicate type. Typically, it is either the name of a predicate in a class, or an expression that evaluates to a predicate member of an object.

Notice that some predicates return values, whereas other predicates do not. A predicate that returns a value is an expression, and the predicate call is often referred to as a function call. A predicate that does return a value is a formula.

A predicate is invoked by applying arguments to the predicate. The predicate must have a flow-pattern that matches the free/bound state of the arguments.

Most predicates are defined by a set of clauses, but some predicates are built into the language and some are defined externally in a DLL (perhaps in a foreign programming language).

When a predicate is invoked by a predicate call, each clause is executed in turn until one of them succeeds, or there are no more clauses left to execute. If no clause succeeds the predicate fails.

If a clause succeeds and there are more relevant clauses left, a backtrackpoint is created to the next relevant clause.

Thus, a predicate can fail, succeed, and even succeed multiple times.

Each clause has a head and optionally a body.

When a predicate is called the clauses are tried in turn (from top to bottom). For each clause the arguments in the head is unified with the arguments from the call. If this unification succeeds then the body of the clause (if present) is executed. The clause succeeds, if the match of the head succeeds and the body succeeds. Otherwise it fails.

Example
clauses
   ppp() :- qqq(X), write(X), fail.
 
   qqq(1).
   qqq(2).
   qqq(3).

When ppp is called it in turn calls qqq. When qqq is called, it first creates a backtrack point pointing to the second clause. Then the first clause is executed. Hereby the free variable X from ppp is matched against the number 1, whereby X is bound to 1.

In ppp X (i.e. 1) is written and then fail cause backtracking to the backtrackpoint. Hereby program control is set to the second clause in qqq and the program state is set back to the state it was in when qqq was first entered, i.e. X in ppp is unbound again.

Before the actual execution of the second clause in qqq begins a backtrack point to the third clause is created. The execution then proceeds as it did for 1

Unification

When a predicate is called the arguments from the call is unified with the terms in the head of each clause.

Unification is the process of binding variables in such a way that two terms become equal, making as few bindings as possible (i.e. leaving as much as possible open for further binding).

Variables can be bound to any kind of terms, including variables or terms containing variables.

Unification is either possible or impossible, i.e. it can succeed or fail.

Variables and terms to which they are unified have types, a variable can only be bound to a term of the same type as the variable, or a subtype. When two variables are bound to each other they must therefore have exactly the same type.

Unification takes place (as mentioned) between a predicate call and the clause head. It also takes place when two terms are compared for equality.

Example Consider two terms (of the same type):
T1 = f1(g(), X, 17, Y, 17)
T2 = f1(Z, Z, V, U, 43)

We will attempt to unify these two terms from left to right (i.e. a left-to-right pre-traversal).

Both T1 and T2 are f1/5 terms, this match. Therefore we attempt to unify each of the arguments from T1 with each correspondent argument of T2. First we must unify Z and g(), this can be unified if we bind Z to g(). So far everything is fine and we have the first binding in our unifier:

Z = g()

The next two arguments are X and Z, which already has been bound to g(). These two arguments can also be unified if we also bind X to g(). So we now have the following contributions to our unifier:

X = Z = g()

Next we must bind V to 17 and then we must bind Y to U. So far everything unifies with the following unifier:

X = Z = g()
V = 17
Y = U

The two unified terms are now equivalent to these terms:

T1 = f1(g(), g(), 17, Y, 17)
T2 = f1(g(), g(), 17, Y, 43)

But we have not yet unified the two last arguments, which are 17 and 43. No variable binding can make these terms equal, so all in all the unification fails.

T1 and T2 cannot be unified.

In the example above T1 could have been a predicate call and T2 a clause head. But they could also have been two terms that were compared with equal "=".

Matching

Matching is the same as unification except that variables can only be bound to grounded terms. A grounded term is a term that does not contain any unbound variables.

It is the flow-patterns that are stated for predicates, that make it possible to use matching rather than full-blown unification.

Example
clauses
   ppp(Z, Z, 17).
   qqq() :-
      ppp(g(), X, 17).

Unification of the ppp-call with the ppp-clause is possible with the following unifier:

Z = X = g()

If ppp have the flow (i,o,i) then the unification is just a match:

  • g() is input as the first argument, this is bound to Z
  • The second argument in the clause is therefore bound and can thus be output to X, which therefore becomes bound to g().
  • finally the third argument is 17 used as input this number is simply compared to the third argument in the clause.

It is the flow-pattern that makes it possible to predict that the clause does not need real unification.

Nested Function Calls

Terms that have to be unified or matched with each other are allowed to contain sub-terms that are actually expressions or function calls that have to be evaluated before the unification/matching can be completed.

The evaluation of such sub-terms is done on a by-need basis.

In a predicate call all input arguments are evaluated before the predicate is called, all output arguments are variables, which does not need evaluation.

Clause heads can also contain terms that have to be evaluated, before matching/unification can be determined.

  • all matching/unification that does not require any evaluation is performed before any evaluation is performed;
  • then evaluation corresponding to input arguments is performed one by one left-to-right. Comparing each value to the corresponding input after each evaluation;
  • then the clause body is evaluated;
  • then the output arguments are evaluated (left-to-right);
  • then the return value (if the predicate is a function) is evaluated.

If any of these fail then the rest of the evaluation is not carried out.

All in all the base principles are:

  • input after other match, before body evaluation
  • output after body evaluation
  • left-to-right

Arguments

This section describes named, default, optional parameters and functor originals. Even though these notions are individual they also have a significant impact on each other and therefore they are described together.

In brief:

  • Named parameters: In a call the actual arguments can be supplied by formal parameter name rather than position.
  • Default parameters: A default parameter value can be stated together with a formal argument in a predicate declaration. This value is used when no actual parameter is supplied.
  • Optional parameters: An actual parameter is optional and can therefore be skipped.
  • Functor originals: Functor term which is used as/bound to the original of another functor term (in a functor term expression).

Named parameters

The formal parameter names from a declaration can be used to specify the actual arguments in a call by using the syntax :<Formal> = <Actual>.

Example Given the predicate addPerson:
class predicates
    addPerson : (string Name, integer Height, integer Weight).

You can call addPerson using positional arguments like this:

addPerson("Hans", 175, 75)

But you can also use named parameters like this

addPerson(:Name = "Hans", :Height = 175, :Weight = 75)

Where Name, Height and Weight are the names that is used in the declaration.

When using named parameters the order of the parameters are insignificant, so this call has the same meaning:

addPerson(:Weight = 75, :Name = "Hans", :Height = 175)

Poisitional and named parameters can be mixed such that the first arguments are given by position and the last by name. Here the Name is given by position and Weight and Height are given by name

addPerson("Hans", :Weight = 75, :Height = 175)

Notice that all positional arguments must be to the left of the first named argument.

Default parameters

A default parameter is defined by adding = <value> after a formal input parameter in a declaration (<value> can be a constant expression, a property or predicate call).

Example The predicate addPerson has three parameters Name, Height and Weight::
class predicates
    addPerson : (string Name, integer Height = 175, integer Weight = 75).

Height has default value 175 and Weight has default value 75.

Notice that it is illegal to provide default parameters for [out] parameters.

Optional parameters

If a parameter is [out] or if it has a default value, then the actual argument is optional and can be skipped provided that it is the last argument in the call. Skipping an [out] parameter corresponds to supplying an anonymous variable for that parameter. Skipping a parameter that has a default value corresponds to supplying the default value for the parameter.

Example Given this predicate
class predicates
    ppp : (integer A = 17, integer B [out]).

We can skip B because it is the last parameter and [out], so here we supply 12 for A and ignore the B output:

ppp(12) % corresponding to ppp(12, _)

In the call above 12 is the last argument, but there is a default value for that parameter so that argument can also be skipped:

ppp() % corresponding to ppp(17, _)

Using named arguments we can exchange the order of the parameters:

ppp(:B = Out, :A = 17)

In that call the last parameter has a default value so it can be skipped:

ppp(:B = Out) % corresponding to ppp(B: = Out, :A = 17) --> ppp(17, Out)

An optional out parameter can cause conflict with another predicate:

Example Conflicting predicates
predicates
    ppp : ().
    ppp : (integer X [out]). % conflict

These predicate declarations conflicts because a call without arguments p() could be to either of them.

The attribute [mandatoryOut] can be used to avoid such conflicts and/or if it doesn't seem appropriate that a predicate a has optional output parameters.

Example No conflict because the second predicate does not have optional output parameters:
predicates
    ppp : ().
    ppp : (integer X [out]) [mandatoryOut]. % no conflict

These predicate declarations conflicts because a call without arguments p() could be to either of them.

Functor originals

A functor original is a syntactic construction that describes an original for a functor term expression. Syntactically it takes the following form:

<functor>(<arguments> | <functor original> )

The functor original can either be a a functor value or a free variable. In both cases the construction indicates that the functor may have more arguments than those mentioned explicitly in front of the bar.

If the functor original is a functor value then it will be used as original for constructing a new functor value.

Example Consider this code:
domains
    person = person(string Name, integer Height, integer Weight).
 
class predicates
    updateName : (person Person, string NewName) -> person Updated.
clauses
    updateName(Person, NewName) = person(NewName | Person).

Here we use Person as original in the functor term expression person(NewName | Person). This expression will create a new person value which has NewName as the Name/first component. All the remaining functor components (i.e. Height and Weight) are taken from the original, i.e. Person.

The use of functor originals can be combined with named parameters:

domains
    person = person(string Name, integer Height, integer Weight).
 
class predicates
    updateWeight : (person Person, Integer NewWeight) -> person Updated.
clauses
    updateWeight(Person, NewWeight) = person(:Weight = NewWeight | Person).

Here NewWeight is used as Weight component. And again the remaining functor components (i.e. Name and Height) are taken from the original, i.e. Person.

The functor original can be any kind of term as long as it evaluates to an appropriate functor term.

Example Here the functor original is the result of calling a function:
clauses
    mkPerson(Name) = person(Name | getCurrentPerson()).

If a functor domain has more than one alternative, then the functor original must be of same kind as the term that is constructed.

Example Consider a functor domain with two alternatives:
domains
    transport =
        aircraft(string Name, integer Seats, integer Range);
        car(string Name, integer Doors).

The following is legal:

A1 = aircraft("Cruiser 1", 25, 300),
A2 = aircraft("Cruiser 2" | A1) % legal A1 is an aircraft

Because A1 is an aircraft, and it is an aircraft we are constructing (as A2).

This is illegal:

C = car("Taxi 23", 4),
A = aircraft(:Seats = 25, :Range = 173 | C)  % illegal C is a car

Because C is a car but we are constructing an aircraft, it does not matter/help that a car has a Name component, which is what we need for the aircraft we are constructing.

In a functor match the functor original can be an anonymous variable. And in that it simply indicates that the term can have more components which we don't care about.

Example Given the transport domain above, we can write a predicate that extract the Name component like this:
class predicates
    getName : (transport Transport) -> string Name
clauses
    getName(aircraft(Name | _)) = Name.
    getName(car(Name | _)) = Name.

Here we have used an anonymous variable as functor original indicating that the functor term has/may have more arguments (which we are not interested in).

In the car case the functor original only represents one additional argument, but using this form the code will be robust to adding additional components to car later. For the same reason, it can make sense to provide a functor original that doesn't represent any additional arguments (i.e. that represents zero extra arguments).

We could also have used named parameters:

class predicates
    getName : (transport Transport) -> string Name
clauses
    getName(aircraft(:Name = Name | _)) = Name.
    getName(car(:Name = Name | _)) = Name.


Here is a predicate that determines whether a transport is a car:

class predicates
    isCar : (transport Transport) determ.
clauses 
    isCar(car( | _)).

This example also shows that it is not necessary to provide any regular arguments at all besides the functor original.

In a functor match the functor original can be a named variable. If the variable is bound then it is used as an original for constructing a functor value and then that functor value is used in the match.

Example Consider this code
C = car("Taxi 23", 4),
car("Taxi 24" | C) = getCurrentCar()
In the second line C is used as original creating the term car("Taxi 24", 4). This term is then matched against the result of calling getCurrentCar.

If the functor original is a free variable (in a functor match) then that variable will be bound to the entire functor term:

Example Consider this code where Free is a free variable
car("Taxi 24" | Free) = getCurrentCar(),

This code is equivalent to this code:

Free = getCurrentCar(),
car("Taxi 24" | _) = Free,

I.e. Free is bound to the result of calling getCurrentCar and then it is matched to this functor pattern car("Taxi 24" | _).

Notice that the code will fail (and not raise an exception) if getCurrentCar returns an aircraft.

Also consider this code (where Name and Car are both free variables):

car(Name | Car) = getCurrentCar(),

it equivalent to this code

Car = getCurrentCar(),
car(Name | _) = Car


Fact Variable Assignment

Assign operator := is used to assign a new value for a fact variable FactVariable. The Term must be evaluated to a value of suitable type (i.e. the same type as the fact variable, or a subtype).

FactVariableAssignment:
    FactVariable := Term

Facts

A fact database contains a number of fully instantiated (grounded) predicate heads corresponding to the facts from the facts section declaration. The facts can be accessed by a predicate call, using the fact name as the predicate name. The predicate call is matched against each fact in turn; succeeding with a possible backtrack point to the next fact each time the predicate call match the fact. When there are no more facts in the fact database then the predicate call fails.

New facts can be asserted using the predicates assert/1, asserta/1, and assertz/1. assert/1 is the same as assertz/1 and it asserts a new fact to the end of the list of facts, whereas asserta/1 asserts a new fact to the start of the list.

Existing facts can be retracted with the predicate retract/1 and retractAll/1. retract/1 retracts the first fact that match the argument binding variables in the argument and leaving a backtrack point so that more facts will potentially be retracted when backtracking.

retractAll/1 retracts all facts that matches the arguments and succeeds without any binding.

Operators

Operators are organized in a precedence hierarchy. In the rule below operators in each group have same precedence, which is higher than those below. I.e. the power operator has higher precedence than unary minus and plus, which in turn has higher precedence than the multiplication operators, etc. Parenthesis can be used to circumvent the precedence (and for clarification).

Operator: one of
    PowerOperator
    UnaryOperator
    MultiplicationOperator
    AdditionOperator
    OtherwiseOperator
    RelationOperator
    MustUnifyOperator
    InOperator
    AndOperator
    OrOperator
UnaryOperator: one of
    - +

All operators except the UnaryOperator's are binary. The power operator is right associative, all other operators are left associative.

RelationOperator, MustUnifyOperator and InOperator have same precedence.

Notice that the placement UnaryOperator is not consistent with mathematics, where these operators are at the same level as the AdditionalOperator's. The difference has no influence of the calculated value, but it allows writing 2*-2, where mathematics would require a parenthesis around the second operator 2*(-2). It also means that -2*2 is mmeans (-2)*2 where it would be -(2*2) in mathematics (the resulting value is the same).

Example

-2^2 is the same as -(2^2) because ^ has higher precedence than unary minus.

Example

3^2^2 is the same as 3^(2^2) because ^ is right associative.

Example

-2*-3^-4+5 is the same as ((-2) * (-(3 ^ (-4)))) + 5.

Example The following term:
7 + 3 * 5 * 13 + 4 + 3 = X / 6 ; A < 7,  p(X)

has the same meaning as this term:

((((7 + ((3 * 5) * 13)) + 4) + 3) = (X / 6)) ; ((A < 7) , p(X))

I.e. at outermost level the term is an "or" of two terms, the first of these is a relational (=) term, the second is an "and" term, etc.

Arithmetic Operators

The arithmetic operators are used for arithmetic operations on numbers. They are expressions, which takes expressions as arguments. They have root types as arguments and return universal types as result. (See Universal and Root types.)

PowerOperator:
    ^
MultiplicationOperator: one of
    * / div mod quot rem
AdditionOperator: one of
    +  -

Relational Operators

The relational operators are formulas, which takes expressions as arguments. Given this nature they are non-associative.

RelationOperator: one of
  =   >   <   >=   <=   <>   ><

First the left term is evaluated, then the right term is evaluated and then the results are compared.

Notice that <> (different) is not the dual operation of = (equal). <> compares two values, whereas = tries to unify two terms (in the general case at least).

The dual to expression A = B is not (A = B).

Must Unify Operator

The must unify operator is a procedure, which takes expressions as arguments. It is non-associative.

MustUnifyOperator:
  ==

A == B unifies A and B; if the unification fails an exception is raised, otherwise the predicate succeeds. Therefore A == B always succeeds.

Example
clauses
    p(L) :-
        [H|T] == L,
        ...
p is a procedure. An exception will be raised if it is called with an empty list, because [H|T] and L cannot unify.

Bitwise and boolean operators

The following operators for bitwise operations on unsigned, unsigned64 and unsignedNative.

A ** B % A and B
A ++ B % A or B
A -- B % A and not B
A ^^ B % A exclusive or B
~~ A % not A
A << N % Shifts the bits in A N times to the left.
A >> N % Shifts the bits in A N times to the right.

The logical operations (**, ++, ^^ and ~~) can also be used on boolean values.

The shift operations discard bits that is shifted out of the number, and shift-in zero bits in the opposite end.

Logical Operators

The AndOperator(s) and OrOperator(s) are formulas, which takes formulas as arguments. They are all left associative. The , and and are synonyms and so are ; and or.

AndOperator: one of
 ,   and
OrOperator: one of
  ;  or orelse

and (,)

The evaluation of an and term A, B proceeds as follows. First the left sub-term A is evaluated. If this evaluation fails, the whole and term fails. If A succeeds then the right sub-term B is evaluated. If this evaluation fails, the whole and term fails, otherwise the and term succeeds.

Thus the second sub-term B is only evaluated, if the first sub-term A succeeds.

Example
clauses
   ppp() :-
       qqq(), rrr().

When ppp is called it will first call qqq and if qqq succeeds, then it will call rrr. If rrr succeeds, then the and term and subsequently the whole clause succeeds.

or (;)

The evaluation of an or term A; B proceeds as follows. First a backtrack point to the second term B is created and then the first term A is evaluated. If the evaluation of the first term succeeds, then the whole or term succeeds and is left with a backtrack to the second term B. If the evaluation of the first term fails, the backtrack point to the second term is activated.

If the backtrack point to the second term B is activated (either because the first term fails, or because something later in the execution invokes the backtrack point), then the second term B is evaluated and the whole or term will succeed if B succeeds.

Thus an or term can succeed with a backtrack point and the second sub-term B is only evaluated on backtrack.

Example
clauses
   ppp() :-
       (V = 3 or V = 7), write(V), fail.

Here we have used the keyword or, but you can also use semi-colon ;.

When ppp is called we first create a backtrack point to the term V = 7 and then we evaluate V = 3. Thereby V will be bound to 3 we then continue to the write(V) after 3 has been written fail is met. fail always fails so we effectuate the backtrack point leading us to the term V = 7.

Backtracking also undo all bindings made since the backtrack point was created. In this case it means that V is unbound.

Then V = 7 is evaluated and V becomes bound to 7 and er continue to the term write(V), and then fail is met again, this time there are no more backtrack points ppp fails.

Using parentheses or can be nested deeply in clauses.

clauses
   p(X) = Y :-
       (X = 1, !, Z = 3 or Z = 7), Y = 2*Z.

We recommend careful usage of or. It is mainly intended for usage in test-conditions:

clauses
   isOutside(X) :-
       (X < 10 or X > 90), !.

or is a nondeterministic construction, but orelse can be used as a deterministic pendant:

clauses
   isOutside(X) :-
       X < 10 orelse X > 90.

orelse

orelse is a deterministic pendant to the nondeterministic or. A orelse B will succeed if A succeeds or if B succeeds, but it will not leave a backtrack point to B if A succeeds.

The evaluation of an orelse term A orelse B proceeds as follows: First a backtrack point to the second term B is created and then the first term A is evaluated. If the evaluation of the first term succeeds then the backtrack to the second term (and any backtrack point within it) B are removed again and the whole orelse term succeeds. If the evaluation of the first term A fails, the backtrack point to the second term B is evaluated.

So an orelse term does not leave a backtrack point.

Example
clauses
   ppp(V) :-
       (V = 3 orelse V = 7), write(V).

Whenever ppp is called we first create a backtrack point to the term V = 7 and then we evaluate the term V = 3, if V = 3 succeeds we remove the backtrack point to V = 7 again and then continue to write(V). If V = 3 fails the backtrack point to V = 7 is effectuated. If V = 7 succeeds we continue to write(V), if V = 7 fails the entire ppp predicate will fail.

otherwise

otherwise is an expression operator; though it has control flow that makes it resemble the logical operators.

A otherwise B

is an expression (A and B must be expressions). If the evaluation of A succeeds by evaluating to the value VA then A otherwise B evaluates to VA, otherwise (i.e. if the evaluation of A fails) then A otherwise B will be the result of evaluating B.

otherwise is right associative:

A otherwise B otherwise C
=>
A otherwise (B otherwise C)

It has lower precedence than all other expression operators, but higher than relational operators:

V < A + tryGet() otherwise 9
=>
V < ((A + tryGet()) otherwise 9)

core have been enriched with a predicate isSome for providing default values for core::optional matching:

Example
V = isSome(Optional) otherwise 0
If Optional have the form some(X) then V will get the value X otherwise V will get the value 0.

not

The not/1 takes a term as the argument. The evaluation of not(A) first evaluates A. If A succeeds, then not(A) fails, if A fails, then not(A) succeeds.

Notice that not(A) will never bind any variables, because if not(A) succeeds then A has failed, and a failed term does not bind anything. If not(A) on the other hand fails, it cannot bind any variables either, because then the term itself failed.

Also notice that not(A) can never succeed with backtrack points, because if not(A) succeeds then A have failed, and a failed term cannot contain any backtrack points. This in turn means that all possibilities of success in A have been exhausted.

cut (!)

Cut "!" removes all backtrack points created since the entrance to the current predicate, this means all backtrack points to subsequent clauses, plus backtrack points in predicate calls made in the current clause before the "!".

Cut:
    !
Example
clauses
   ppp(X) :-
       X > 7,
       !,
       write("Greater than seven").
   ppp(_X) :-
       write("Not greater than seven").

When ppp is executed, there is first created a backtrack point to the second clause, and then the first clause is executed. If the test "X > 7" succeeds then the cut "!" is reached. This cut "!" will remove the backtrack point to the second clause.

Example
clauses
   ppp() :-
       qqq(X),
       X > 7,
       !,
       write("Found one").
   ppp() :-
       write("Did not find one").
clauses
   qqq(3).
   qqq(12).
   qqq(13).

When ppp is executed it first creates a backtrack point to the second ppp clause and then qqq is called. The qqq will create a backtrack point to the second qqq clause and execute the first clause, thereby returning the value 3. In ppp variable X is bound to this value and then compared to 7. This test fails and, therefore, the control backtracks to the second clause of qqq.

Before executing the second clause a new backtrack point to the third clause of qqq is created and then the second clause returns 12.

This time the test against 7 succeeds and, therefore, the cut is executed. This cut will remove both the backtrack point left in qqq as well as the backtrack point to the second clause of ppp.

cut scopes

A cut scope is a scope to which the effect of a cut is limited. Meaning that if a cut is met within a cut scope then only backtrack points within that scope are discarded, while backtrack points outside (i.e. prior to) the cut scope remains.

The clauses of a predicate is a cut scope. Meeting a cut will (at most) discard the backtrack points that was created after entrance to the predicate. Backtrack points created before entrance to the predicate will remain.

Example
clauses
   aaa() :- p1_nd(), qqq().
   qqq() :- p2_nd(), !.

aaa calls p1_nd, which leaves a backtrack point, and then it calls qqq. qqq calls p2_nd, which also leaves a backtrack point. Then we meet a cut. This cut is in the cut-scope of the qqq predicate, so it is only the backtrack point in p2_nd which is discarded, the one in p1_nd remains.

Several terms introduce cut scopes (see the respective terms: list comprehension, if-then-else, foreach). Here we will use if-then-else to illustrate the effect of cut scopes. Consider the schematic if-then-else term:

if Cond then T1 else T2 end if

The condition Cond is a cut-scope, meaning that a cut inside Cond will only have effect inside Cond. Cuts inside T1 and T2, on the other hand, have effect outside the if-then-else statement.

Consider this code fragment:

X = getMember_nd([3,1,2]),
if X = getMember_nd([3,3]), ! then
   write(X)
else
   !
end if,
fail

getMember_nd is a nondeterministic predicate. The evaluation of this code will go as follows. First X is bound to 3 and getMember_nd leaves a backtrack point (so that X can later become 1 and then even 2).

Then we evaluate the condition in the if-then-else term. The first part of this condition succeeds as 3 is a member of [3,3]. The first part also leaves a backtrack point, so that it can be examined whether X is a member several times.

Now we meet a cut. This cut is inside the condition part of an if-then-else statement, so it only has local effect, meaning that it only discards the backtrack point in the second getMember_nd, but leaves the backtrack point in the first getMember_nd predicate.

The whole condition succeeds and we enter the then-part and write out "3".

After the if-then-else we meet fail, which backtracks us to the first getMember_nd.

getMember_nd then binds X to 1, and leaves a backtrack point (so that X can later become 2).

Then we evaluate the condition in the if-then-else term. The first part of this condition fails as 1 is not a member of [3,3]. So we enter the else-part.

Here we meet a cut. This cut is in the else-part of a conditional term so it has effect outside the if-then-else term and subsequently it discards the backtrack point in the first getMember_nd.

When we meet the fail after the if-then-else term there are no more backtrack points in the code and it will fail. So all in all X never becomes 2.

fail/0 and succeed/0

fail/0 and succeed/0 are two built-in nullary predicates. fail/0 always fails and succeed/0 always succeeds, besides this the predicates have no effect.

in

InOperator:
  in

The in operator is used to test for member ship of a collection (e.g. a list) and to nondeterministically generate the members of a collection.

Example
predicates
    p : (Type X, Type* L).
clauses
    p(X, L) :-
        if X in L then
            write("X is in L\n")
        end if.

p is a procedure that takes a value X and a list L as arguments. If X is in the list L then it will write "X is in L". In this case in is used as an in-test (membership test).


Example
predicates
    q : (Type* L).
clauses
    q(L) :-
        foreach X in L do
            writef("% is in L\n", X)
        end foreach.
q is a procedure that takes a list L as argument. The "in" operator is used to nondeterministically return the members of L, so that they can be written.

The in operator can be defined for any domain and interface using the in_test and in_iterate attributes.

The in_test(<predicate name>) attribute defines the predicate that is used as in-test for a certain domain or interface. Likewise the in_iterate attribute defines the predicate that is used as in-iterator for the domain/interface.

Example
domains
    tree{E} = empty; node(tree{E} Left, E Value, tree{E} Right)
        [in_test(isMemberTree), in_iterate(getAll_nd)].

When the program contains A in B where A is bound B is a tree{E} then isMemberTree is actually called.

In that case A in B corresponds to isMemberTree(A, B).

If A is free the call corresponds to A = getAll_nd(B).

For a domain <collection> the predicate must have the type:

predicates
    <predicate> : (<some-type> Elem, <collection> Collection) determ.
Example
interface collection [in_test(contains), in_iterate(getAll_nd)]
...
end interface collection

When the program contains A in B where A is bound B is a collection then contains is actually called.

In that case A in B corresponds to B:contains(A).

If A is free the call corresponds to A = B:getAll_nd().

For a domain <collection> the in_test and in_iterate predicate must fulfill these schematic declarations:

domains
    <collection> = ... [in_test(<in_test>), in_iterate(<in_iterate>)].
class predicates
    <in_test> : (<some-type> Elem, <collection> Collection) determ.
    <in_iterate : (<collection> Collection) -> <some-type> Elem nondeterm.

For an interface <collection> the in_test and in_iterate predicate must fulfill these schematic declarations:

interface <collection> [in_test(<in_test>), in_iterate(<in_iterate>)]
predicates
    <in_test> : (<some-type> Elem) determ.
    <in_iterate : () -> <some-type> Elem nondeterm.
...
end interface <collection>

The in operator is predefined on list domains, and in PFC the collections have suitable attributes.

Example
clauses
    p() :-
        foreach X in [1, 2, 3, 4] do % in_iterate
            if X in [2, 4] then % in_test
                ...
            end if
        end foreach.

The first in is the predefined in_iterate for the list domain, and the second one is the predefined in_test.

clauses
    q() :-
        M1 = setM_redBlack::new(),
        M1:inset("a"),
        M1:inset("b"),
        M2 = setM_redBlack::new(),
        M2:inset("b"),
        foreach X in M1 do % in_iterate
            if X in M2 then % in_test
                ...
            end if
        end foreach.

For collections the in operators resolve to contains and getAll_nd:

interface collection{@Type}
    [in_test(contains), in_iterate(getAll_nd)]
 
predicates
    contains : (@Type Value) determ.
    % @short Succeeds if the collection contains the value @Type
    % @end
 
predicates
    getAll_nd : () -> @Type Value nondeterm.
    % @short @Type is nondeterministic iteration of the elements in the collection.
    % @end
 
...
 
end interface collection

List Comprehension

ListComprehensionTerm :
    [ Term || Term ]

The list comprehension term is a list expression. Consider this schematic term:

[ Exp || Gen ]

Gen is (typically) a nondeterm term. Exp is evaluated for each solution of Gen, and the resulting Exp's are collected in a list. The Exp corresponding to the first solution of Gen is the first element in the list, etc. This list is the result of the list comprehension term. Exp must be procedure (or erroneous). Both Exp and Gen are cut scopes.

The list comprehension (normally) reads: The list of Exp's such that Gen.

Example
[ X || X = getMember_nd(L), X mod 2 = 0 ]

This reads the list of X's such that X is in L and X is even. So this expression is the even numbers of L.

Example
[ X + 1 || X = getMember_nd(L), X mod 2 = 0 ]

Here the collected expression is more complex. This makes say the term more awkward:

"the list of (X+1)'s such that ..."

This expression again finds the even elements in L, but the resulting list contains all these values incremented.

This term is completely equivalent to this term:

[ Y || X = getMember_nd(L), X mod 2 = 0 , Y = X+1 ]

This term is easier to say:

"The list of Y's such that (there exists an) X which is member of L, and which is even, and Y is X+1."

Anonymous Predicates

Anonymous Predicates

An anonymous predicate is an expression that evaluates to a predicate value. The value can be bound to a variable, passed as an argument, or returned as a result, but it has no name in any class, interface, or implementation.

Anonymous predicates have the ability to capture values from the context in which the expression occurs; this is a powerful ability that can be used to avoid a rather excessive amount of strange/unpleasant code.

Syntax

Anonymous predicates are terms:

Term : one of
    ...
    AnonymousPredicate
    ...

An anonymous predicate is a nameless clause in curly brackets. Certain parts are optional, giving these forms:

AnonymousPredicate : one of
    { ( Arg-comma-sep-list ) = Term }
    { ( Arg-comma-sep-list ) = Term :- Term }
    { ( Arg-comma-sep-list ) :- Term }
    { = Term }
    { = Term :- Term }
    { :- Term }

Leaving out the argument list means "the required number of arguments" and can be used whenever the arguments are not used inside the predicate expression.

Semantics

An anonymous predicate expression evaluates to a predicate value. Consider this code:

clauses
    run() :-
        Inc = { (X) = X+1 },
        A = Inc(4),
        B = Inc(23),
        stdio::writef("A = %, B = %", A, B).

Inc becomes an increment predicate, so the program will write:

A = 5, B = 24

The code in this example corresponds to this code:

clauses
    run() :-
        Inc = inc,
        A = Inc(4),
        B = Inc(23),
        stdio::writef("A = %, B = %", A, B).
 
class predicates
    inc : (integer X) -> integer R.
clauses
    inc(X) = X+1.

Where the clause (X) = X+1 can be found in the last line; i.e., this time in a named predicate.

Variables that are bound outside (i.e., before the occurrence of) an anonymous predicate can be used inside the anonymous predicate. The value of the variable will be captured by the anonymous predicate.

Variables that are bound in an anonymous predicate are local variables in the anonymous predicate.

Capturing context

An anonymous predicate can capture context, which means that it can refer to things that are defined in its context, especially facts and variables from the clause.

Capturing variables

An anonymous predicate occurs in a clause, and this clause may contain variables. Those variables that are bound before the anonymous predicate is met can be used inside the anonymous predicate. This code illustrates how a variable is captured:

domains
    pred = (integer) -> integer.
 
class predicates
    createAdder : (integer A) -> pred Adder.
clauses
    createAdder(A) = { (X) = X+A }.
 
clauses
    run() :-
        Add17 = createAdder(17),
        A = Add17(4),
        B = Add17(20),
        stdio::writef("A = %, B = %", A, B).

We call createAdder with 17 as argument. So in the createAdder clause A is 17, and therefore the result is { (X) = X+17 }. We say that the anonymous predicate has captured the variable A.

Since Add17 is a predicate that adds 17 to its argument, the output of the code will be:

A = 21, B = 37
Capturing ellipsis (...)

An anonymous predicate can capture the ellipsis variable (i.e., ...):

clauses
    ppp(...)  :-
        W = { () :- stdio::write(...) },
        qqq(W).

W captures the ellipsis variable. qqq receives a nullary predicate; when this predicate is invoked the captured ellipsis variable will be written to the standard output device.

Capturing facts

An anonymous predicate can access facts. If it is created by a class predicate it can access class facts. If it is created by an object predicate it can access both object and class facts. Consider this code that captures a class fact:

class facts
    count : integer := 0.
clauses
    seq() = { () = count :- count := count+1 }.
clauses
    run() :-
        A = seq(),
        B = seq(),
        stdio::writef("A1 = %, ", A()),
        stdio::writef("B1 = %, ", B()),
        stdio::writef("A2 = %, ", A()),
        stdio::writef("B2 = %", B()).

Both A and B increment the class fact count, so the result is:

A1 = 1, B1 = 2, A2 = 3, B2 = 4

In object predicates we can capture object facts. So assuming that seq is an object predicate in myClass, this code illustrates the capture of an object fact:

facts
    count : integer := 0.
clauses
    seq() = { () = count :- count := count+1 }.
clauses
    run() :-
        A = myClass::new():seq(),
        B = myClass::new():seq(),
        stdio::writef("A1 = %, ", A()),
        stdio::writef("B1 = %, ", B()),
        stdio::writef("A2 = %, ", A()),
        stdio::writef("B2 = %", B()).

In this case A and B come from two different objects, which each have a count fact, so the output will be:

A1 = 1, B1 = 1, A2 = 2, B2 = 2

Technically, the class version actually does not capture anything; it merely has access to the fact. Likewise, the object version does not actually capture the fact; instead it captures This and through This it obtains access to the object facts.

Capturing This

As described above it is possible to capture This and thereby gain access to object facts. The same mechanism gives access to calling object predicates.

clauses
    seq() = { () = count :- inc() }.
 
clauses
    inc() :- count := count+1.

This can also be used directly:

clauses
    ppp() = { () = aaa::rrr(This) }.
Nesting

Anonymous predicates can be nested:

clauses
    run() :-
        P = { (A) = { (B) = A+B } },
        Q = P(3300),
        R = P(2200),
        stdio::writef("Q(11) = %, ", Q(11)),
        stdio::writef("R(11) = %", R(11)).

To obtain Q we call P with 3300, so A is 3300 and Q therefore becomes { (B) = 3300+B }; likewise R becomes { (B) = 2200+B }. So the output is:

Q(11) = 3311, R(11) = 2211
Syntactic Sugar

If you do not need the arguments they can be skipped. So this code fragment:

P = { (_) :- succeed },
Q = { (_, _) = 0 },
R = { (_, _, _) = _ :- fail }.

can be shortened to:

P = { :- succeed },
Q = { = 0 },
R = { = _ :- fail }.

Notice that the arguments are completely skipped. If you write () it means zero arguments, whereas skipping the arguments means "a suitable amount" of arguments.

Examples of practical usage

The examples assume that the PFC scopes core, std, stdio, list and string are open.

Dummy predicates

Anonymous predicates are good for creating dummy predicate values:

ppp( { = true } ),     % do not filter (boolean)
qqq( { :- succeed } ), % do not filter (determ)
rrr( { = 17 } ).       % all rows must have height 17
Adaptation

In cases where you need a predicate and have one that is almost suitable, you can make the adaptation using an anonymous predicate.

Index adaptation

Consider the predicate write3:

class predicates
    write3 : (function{integer, string} Indexer).
clauses
    write3(Indexer) :-
        foreach I = std::fromTo(0,2) do
            write(Indexer(I), "\n")
        end foreach.

Indexer implements an "array" of strings; write3 will write the three strings found at the indexes 0, 1 and 2. So write3 assumes that the "array" index is zero-based.

However, the "array" we have uses a one-based index:

class predicates
    myArray : (integer N) -> string Value.
clauses
    myArray(1) = "First" :- !.
    myArray(2) = "Second" :- !.
    myArray(3) = "Third" :- !.
    myArray(_) = _ :-
        raiseError().

Using an anonymous predicate we can easily adapt the one-based array to the zero-based usage:

% myArray is 1-based, write3 requires 0-based
Arr = { (N) = myArray(N+1) },
write3(Arr).

So we get the expected output:

First
Second
Third
Parameter adaptation

In this code listChildren will call a ChildWriter predicate for each "C is the child of P"-pair:

class predicates
    listChildren :
        (predicate{string,string} ChildWriter).
clauses
    listChildren(CW) :-
        CW("Son1", "Father"),
        CW("Son2", "Father").

We will however prefer to list the "P is the parent of C" using the predicate wParent:

class predicates
    wParent : (string Parent, string Child).
clauses
    wParent(P, C) :-
        writef("% is the parent of %\n", P, C).

wParent takes the arguments in the opposite order, but we can easily adapt using an anonymous predicate:

Swap = { (A,B) :- wParent(B,A) },
listChildren(Swap).

And then the output becomes the expected:

Father is the parent of Son1
Father is the parent of Son2

We can also throw away arguments, for example when calling this predicate that only needs a Child:

class predicates
    wKnowParent : (string Child).
clauses
    wKnowParent(C) :-
        writef("We know a parent of %\n", C).

The adaptation looks like this:

Fewer = { (C,P) :- wKnowParent(C) },
listChildren(Fewer).

The output will be:

We know a parent of Son1
We know a parent of Son2

We can also supply dummy arguments:

More = { (_,P) :- addChildren(P, 1) },
listChildren(More).

Here addChildren will "add a count of children to P". Since each invocation corresponds to one child we will call addChildren supplying 1 as a "dummy" argument. The More is thus an adaptor that both throws away an argument and supplies a dummy argument.

Filters

Assume this predicate:

class predicates
    writeFiltered : 
        (string L, predicate_dt{integer} Filter).
clauses
    writeFiltered(Label, Filter) :-
        List = [1,2,3,4,5,6,7,8,9],
        FilteredList = filter(List, Filter),
        writef("%\t%\n", Label, FilteredList).

Filter is used to filter the list [1,2,3,4,5,6,7,8,9]; the filtered list and the Label are written to the standard output.

First we use the allow-all filter:

All = { :- succeed },
writeFiltered("All", All).

This filter simply succeeds for any element, so the output is the entire list:

All     [1,2,3,4,5,6,7,8,9]

It is just as easy to create a filter that fails for all elements and thus allow-none:

None = { :- fail },
writeFiltered("None", None).

The output from this is the empty list:

None    []

We can also create filters for elements greater than 3 and elements divisible by 3:

GreaterThan3 = { (X) :- X > 3 },
writeFiltered("> 3", GreaterThan3),
Rem3 = { (X) :- 0 = X rem 3 },
writeFiltered("Rem3", Rem3).

The output from this is:

> 3     [4,5,6,7,8,9]
Rem3    [3,6,9]
Sorting

The list package has a sort predicate. But sometimes the default order is not what you need. Therefore the list package also has a predicate sortBy, which sorts the elements using a programmer-defined compare operation. Let us first consider string sorting, using this predicate:

class predicates
    writeStringsSorted :
        (string Label, comparator{string} Comp).
clauses
    writeStringsSorted(Label, C) :-
        List = ["John Wayne", "Uma Thurman",
            "Harrison Ford", "Nicolas Cage",
            "Elizabeth Taylor", "Cary Grant",
            "Jerry Lewis", "Robert De Niro"],
        Sorted = sortBy(C, List),
        write(Label, "\n"),
        foreach S = list::getMember_nd(Sorted) do
            writef("    %\n", S)
        end foreach.

We can call the predicate with the "normal" comparator, and using an anonymous predicate we can easily sort it descending as well:

Normal = compare,
writeStringsSorted("Normal", Normal),
Descending = { (A,B) = compare(B,A) },
writeStringsSorted("Descending", Descending).

The output looks like this:

Normal
    Cary Grant
    Elizabeth Taylor
    Harrison Ford
    Jerry Lewis
    John Wayne
    Nicolas Cage
    Robert De Niro
    Uma Thurman
Descending
    Uma Thurman
    Robert De Niro
    Nicolas Cage
    John Wayne
    Jerry Lewis
    Harrison Ford
    Elizabeth Taylor
    Cary Grant

Let us also sort some more complex elements. Here a person has a first name and a last name, using this domain:

domains
    person = p(string First, string Last).

For the demonstration we will use this test predicate:

class predicates
    writePersonsSorted : 
        (string Label, comparator{person} Comparator).
clauses
    writePersonsSorted(Label, C) :-
        List = [p("John","Wayne"),
            p("Uma","Thurman"),
            p("Harrison","Ford"),
            p("Nicolas","Cage"),
            p("Elizabeth","Taylor"),
            p("Cary","Grant"),
            p("Jerry","Lewis"),
            p("Robert","De Niro")],
        Sorted = sortBy(C, List),
        write(Label, "\n"),
        foreach p(F,L) = list::getMember_nd(Sorted) do
            writef("    % %\n", F, L)
        end foreach.

Again we can sort using the normal and a descending comparator:

Normal = compare,
writePersonsSorted("Normal", Normal),
Descending = { (A,B) = compare(B,A) },
writePersonsSorted("Descending", Descending).

Since the compare predicate uses left-to-right lexicographic order on the p-functor, the result is the same as before:

Normal
    Cary Grant
    Elizabeth Taylor
    Harrison Ford
    Jerry Lewis
    John Wayne
    Nicolas Cage
    Robert De Niro
    Uma Thurman
Descending
    Uma Thurman
    Robert De Niro
    Nicolas Cage
    John Wayne
    Jerry Lewis
    Harrison Ford
    Elizabeth Taylor
    Cary Grant

But with the more complex domain we can create a comparator that will sort on last name:

LN = { (p(_,L1), p(_, L2)) = compare(L1,L2) },
writePersonsSorted("LastName", LN).

The result is what we expect:

LastName
    Nicolas Cage
    Robert De Niro
    Harrison Ford
    Cary Grant
    Jerry Lewis
    Elizabeth Taylor
    Uma Thurman
    John Wayne
Capturing context (threads & callbacks)

As mentioned a very powerful feature of anonymous predicates is the ability to capture context. The examples in this section show some ways you can use this.

Background threads

The routine for starting a thread takes a nullary predicate and runs it in the new thread. But you nearly always need to pass some input data to the job in the new thread. This is possible in several ways, but the absolutely simplest way is to use anonymous predicates. The project bgDemo from the Visual Prolog example collection (that can be installed from the IDE) uses this method. The project has a form that can start a background job and display status information from the job in a jobControl that is added to the form. A background job is a predicate that will receive a jobLog, which it can use to report status and completion degree:

domains
    job = (jobLog Log).

A jobLog looks like this:

interface jobLog
 
properties
    completion : real (i).
 
properties
    status : string (i).
 
end interface jobLog

The job can report completion degree by setting the completion property (range 0 to 1). Likewise, the status property can be used to reflect the current status of the job.

The status and completion will be shown in the form together with a job name. A job is started by calling the form's addJob predicate:

clauses
    addJob(JobName, Job) :-
        JobCtrl = jobControl::new(This),
        JobCtrl:name := JobName,
        JobCtrl:show(),
        assert(jobCtrl_fact(JobCtrl)),
        arrange(),
        JobLog = jobLog::new(JobCtrl),
        Action = { :- Job(JobLog) },
        _ = thread::start(Action).

In this context it is the last three lines that are interesting. thread::start takes a nullary predicate as argument, but a job is a predicate that takes a jobLog as argument. Therefore we create an anonymous predicate Action, which takes no arguments but invokes Job on the JobLog. The anonymous predicate has captured both Job and JobLog from the context, and subsequently both these values are transferred to the new thread even though this thread only receives a nullary predicate.

The jobs in the bgDemo project are merely dummy jobs that only manipulate their jobLog. One of them looks like this:

clauses
    job(Log, From, To) :-
        Log:status := "Step 1",
        foreach N1 = std::fromTo(From, To) do
            Log:completion :=
                (N1-From) / (To-From) / 2,
            programControl::sleep(3)
        end foreach,
        Log:status := "Step 2",
        foreach N2 = std::fromTo(From, To) do
            Log:completion :=
                (N2-From) / (To-From) / 2 + 0.5,
            programControl::sleep(3)
        end foreach,
        Log:status := "finished".

It has two loops which run from From to To and calculates the completion and sets it on the Log. It also sets the status text before, between and after the loops.

You may notice that the job does not have the proper job type, because a proper job only has one argument (the jobLog); this job has three arguments. Again it is anonymous predicates that help us. The code that adds the jobs to the form looks like this:

predicates
    onFileNew : window::menuItemListener.
clauses
    onFileNew(_Source, _MenuTag) :-
        JF = jobForm::display(This),
        Job11 = {(L) :- job1::job(L, 1, 1000)},
        Job12 = {(L) :- job1::job(L, 200, 600)},
        Job13 = {(L) :- job1::job(L, 1200, 3000)},
        Job14 = {(L) :- job1::job(L, 1, 1000)},
        JF:addJob("job1.1", Job11),
        JF:addJob("job1.2", Job12),
        JF:addJob("job1.3", Job13),
        JF:addJob("job1.4", Job14),
        ...

In a more realistic program, it is most likely that From and To would not be constants, but rather parameters passed from some outer place. In that case these anonymous predicates would also capture variables from the context.

The jobLog in the bgDemo illustrates one more usage of anonymous predicates. The jobLog passes the completion and the status information to a jobControl. The jobControl is a GUI control on the jobForm capable of doing a suitable rendering of the information. This however gives a synchronization problem, because GUI controls are not thread safe and here we want to update some controls from a background thread. This can lead to conflicts, because it is the main thread that draws the controls.

The solution is to transfer the update of the control to the GUI thread. We do this by posting actions to the control. The implementation of the status update looks like this:

clauses
    status(Status) :-
        Action = { :- jobCtrl:status := Status },
        jobCtrl:postAction(Action).

Action is a nullary predicate that will set the status in the jobCtrl. We post this action to the jobCtrl. When the jobCtrl receives the action it invokes it and is thus updated. This way, the actual update of the control will be performed by the GUI thread. This anonymous predicate not only captures the Status variable it also captures the jobCtrl fact.

Asynchronous callbacks

Assume that we send commands to a remote service. The command execution is asynchronous, so when we execute a command we also give a callback action which will be invoked when the execution of the command is finished. To execute a command we must call this predicate:

predicates
    executeCommand :
        (command Cmd, predicate{} OnDone).

Based on this predicate we want to create a similar predicate that can execute a list of commands. A certain command should be executed when the previous command completes. We will also make our list executor asynchronous, so we supply an action that will be invoked when the entire script of commands is finished. Our script executor will have the form:

predicates
    executeScript :
        (command* Script, predicate{} OnDone).

If the script is empty we simply invoke the OnDone action. If the script has a command H and a rest script T, we must first execute H, and when it is finished we must execute the rest of the script T. So the OnDone action we supply when executing H must execute T. All in all, the implementation can look like this:

clauses
    executeScript([], OnDone) :-
        OnDone().
    executeScript([H|T], OnDone) :-
        DoneH = { :- executeScript(T, OnDone) },
        executeCommand(H, DoneH).

We have used an anonymous predicate to perform the execution of the rest of the script. This anonymous predicate captures T and OnDone.


Object Member Access

Whenever we have a reference to an object, we can access the object member predicates of that object.

MemberAccess:
    Term : Identifier

(Currently, the term must be a variable or a fact variable).

The identifier must have the type of the term.

Inside an implementation object member predicates can be invoked without reference to an object, because "This" is subsumed, see Scoping.

Object Expressions

An object expressions is an expressions that evaluates to an object. Like anonymous predicates it can capture values from and access facts in the context it appears in.

The syntax is like a regular class implementation without a name, but with a construction interface:

Example
Object = 
    implement : observer
      clauses
        onNext(A) :- F(toString(A)).
        onCompletion() :- F("\n").
    end implement

the implement ... end implement part is an object expression. To make object expressions a lightweight construction the keyword clauses is implicit/optional at the beginning of the scope (unless the scope has open, supports or inherits qualifications).

ObjectExpression: one of
    FullObjectExpression
    SimpleObjectExpression
 
FullObjectExpression:
    implement : ConstructionType
        ScopeQualifications
        Sections
    end implement
 
SimpleObjectExpression:
    implement : ConstructionType
        Clause-dot-term-list-opt
        Sections
    end implement

There will be exactly one constructor new\0. Like for other objects you don't need to supply an implementation if the constructor is 'trivial'.

inherits, supports, open, delegate and resolve works in the same way as in regular implementations.

Scoping

The predicates can refer to the context like anonymous predicates but can also refer to facts and inherited classes inside the object.

Object expressions are nested within other scopes, these scopes are all visible from the object expression. If a name is defined in more than one surrounding scope then the reference is to the closest level. Names from named scopes can be resolved with the scope name, but names from surrounding object expressions must be resolved by means of a variable as described in the "This" section.

This

In a predicate in an object expression the variable This represent the object of the object expression. There are no predefined names for surrounding This variables. So if you want to refer to an outer This you will have to put it in another variable e.g. Outer = This and then use that variable inside the object expression.

...
    Outer = This,
    Object = 
        implement : observer
            onNext(A) :- F(Outer, toString(A))).
            onCompletion() :- F(Outer, "\n")).
        end implement

Polymorphism (limitation)

Occasionally there will be situations where we will need a type variable. An example would be a predicate p : () -> observer{A} implemented using an object expression. Unfortunately, this is not possible until we get access to the type variables of polymorphic constructions.

clauses
    p(Value) = 
        implement : observer{A} % A is unknown/unbound
        facts
            v : A = Value. % A is unknown/unbound
        clauses
            onNext(V) :- v := V.
            onCompleted():- write(v).
        end implement.

Examples

The examples below will be based on iterator object.

interface iterator
predicates
   hasNext : () determ.
   next : () -> integer.
end interface iterator

Which we will write using this predicate:

class predicates
    writeAll : (iterator It).
clauses
    writeAll(It) :-
        if It:hasNext() then
            writef("%\n", It:next()),
            writeAll(It)
        else
            write("<<<end>>>\n")
        end if.


Simple object

Example We can write a simple "null" iterator that is finished immediately.
class predicates
    test1 : ().
clauses
    test1() :-
        It =
            implement : iterator
                hasNext() :-
                    fail.
                next() = _ :-
                    exception::raise_error().
            end implement,
        writeAll(It).

Calling test1 will produce

<<<end>>>

Own state

Example In this example we create an iterator object that har its own fact n which is used to count down from 3
class predicates
    test2 : ().
clauses
    test2() :-
        It =
            implement : iterator
                hasNext() :-
                    n > 0.
                next() = N :-
                    N = n,
                    n := n - 1.
            facts
                n : integer := 3.
            end implement,
        writeAll(It).

Calling test2 will produce

 3
 2
 1
<<<end>>>

Capturing values

Example The count down object from above can be placed in its own predicate, and we can capture the value to count down From in the context:
class predicates
    countDown : (integer From) -> iterator It.
clauses
    countDown(From) =
        implement : iterator
            hasNext() :-
                n > 0.
            next() = N :-
                N = n,
                n := n - 1.
        facts
            n : integer := From.
        end implement.
 
class predicates
    test3 : ().
clauses
    test3() :-
        It = countDown(2),
        writeAll(It).

Calling test3 will produce

 2
 1
<<<end>>>


Example Here map create an iterator that maps the values returned iterator just like it would have modified the values of a list. Notice how the object expression captures the variables F and It and accesses them in its member predicates.
class predicates
    map : (function{integer, integer} Function, iterator It) -> iterator Mapped.
clauses
    map(F, It) =
        implement : iterator
            hasNext() :-
                It:hasNext().
            next() = F(It:next()).
        end implement.
 
class predicates
    test4 : ().
clauses
    test4() :-
        It1 = countDown(2),
        It2 = map({ (V) = V + 7 }, It1),
        writeAll(It2).

Calling test4 will produce

 9
 8
<<<end>>>

Capturing a fact

Example Here the fact count from the context is captured and manipulated from within the object expression.
class facts
    count : integer := 3.
 
class predicates
    test5 : ().
clauses
    test5() :-
        It =
            implement : iterator
                hasNext() :-
                    count > 0.
                next() = N :-
                    N = count,
                    count := count - 1.
            end implement,
        writeAll(It).

Calling test5 will produce

 3
 2
 1
<<<end>>>

inherits

Example Suppose we have a class randomIterator which generates random numbers and supports the iterator iterator.

We can inherit from this iterator to create a iterator that "throws a dice":

class predicates
    test6 : ().
clauses
    test6() :-
        Dice =
            implement : iterator inherits randomIterator
            clauses
                next() = randomIterator::next() mod 6 + 1.
            end implement,
        foreach _ = std::cIterate(5) do
            writef("Dice : %\n", Dice:next())
        end foreach.

By inheriting randomIterator we get the implementation of hasNext and only need to implement next.

Notice that it is necessary to use the clauses keyword in this case because the class has an inherits qualification.

Assuming that randomIterator will never end, we just iterate 5 times.

Calling test5 will produce (something like):

Dice : 1
Dice : 2
Dice : 4
Dice : 2
Dice : 3

Domain, Functor, and Constant Access

Domains, functors, and constants are all accessed as if they are class members. Even if they are declared in an interface. This means that when they are qualified, then they are always qualified with class/interface name and a double colon.

foreach

ForeachTerm :
  foreach Term do Term end foreach

Consider the schematic foreach term:

foreach Gen do Body end foreach

Gen is (typically) a nondeterm term. Body is evaluated for each solution of Gen. If/when Gen fails the foreach-term succeeds without evaluating Body. Body must be procedure (or erroneous). Gen and Body are both cut scopes.

The schematic foreach term resembles a fail loop:

Gen,
    Body,
fail

The main (and important) difference is that a foreach-term succeeds after the iteration, whereas a fail loop fails. As a result foreach-terms can be followed by other terms and they can be properly nested.

Example
foreach L = list::getMember_nd(LL) do
   write("<< "),
   foreach  X = list::getMember_nd(L) do
       write(" ", X)
   end foreach,
   write(" >>\n")
end foreach.

LL is supposed to be a list of lists. The outer foreach-loop iterates L through this list, so each L is a list. The inner foreach-loop iterates X through the elements of L.

There are a number of things to notice:

  • There is no comma before the keywords "do" and "end foreach".
  • The Body of a foreach-term is a cut scope, so a cut meet in the body will not influence the iteration.
  • A foreach-term always succeeds (or raises an exception), and no extra variables are bound after the evaluation of a foreach-term. Therefore, a foreach-term can only be used for its side effects.
Example
clauses
   p(L) :-
       foreach X = list::getMember_nd(L) do
           stdio::write(X, "\n")
       end foreach,
       stdio::write("Finished\n").

Foreach can be used instead of traditional "fail-loops":

clauses
   p(L) :-
       X = list::getMember_nd(L),
           stdio::write(X, "\n"),
       fail.
   p(_L) :-
       stdio::write("Finished\n").

In this context it is advantageous that Body must be a procedure, because in a "fail-loop" the body may accidentally fail before reaching the fail in the loop. Another advantage is that a foreach loop succeeds when the loop is finished, whereas a fail loop fails, so that execution can continue in the same clause. Also notice that foreach can be properly nested:

clauses
   p(LL) :-
       foreach L = list::getMember_nd(LL) do
           foreach X = list::getMember_nd(L) do 
               stdio::write(X, "\n")
           end foreach, 
           stdio::write("Finished a list\n")
       end foreach,
       stdio::write("Finished all lists\n").

if-then-else

if-then-else can be used both as a statement and as an expression.

if-then-else (statement)

The if-then-eslse statement conditionally executes a group of statements.

IfThenElseTerm:
    if Condition then Term Elseif-list-opt Else-opt end if
 
Elseif:
    elseif Condition then Term
 
Else:
    else Term

The following two terms are equivalents.

if Cond1 then T1 elseif Cond2 then T2 else T3 end if
if Cond1 then T1 else
  if Cond2 then T2 else T3 end if
end if

Consider the schematic if then else term:

if Cond then T1 else T2 end if

First Cond is evaluated, if it succeeds then T1 is evaluated otherwise T2 is evaluated.

Cond is followed by an implicit cut, which turns:

  • a nondeterm condition into a determ condition and
  • a multi condition into a procedure.

Cond is a cut-scope (see Cut Scopes).

Example
clauses
    w(X) :-
        if X div 2 = 0 and X > 3 then 
            write("X is good")
        else
            write("X is bad"),
            nl
        end if,
        nl.

There are several things to notice about this example:

  • You can use "and" and "or" logical operators and other "complex" terms in all three sub-terms.
  • There is no comma before the keywords "then", "elseif", "else", and "end if".

For readability sake, we always recommend using "or" instead of ";". Likewise we also recommend using "and" (instead of ",") when it (as in the condition above) represents a logical "condition" rather than a "sequentation".

Leaving out the else-part is just shorthand for writing that else succeed, i.e.

if Cond then Term end if

is short-hand for

if Cond then Term else succeed end if

if-then-else (expression)

The if-then-else expression conditionally evaluates expressions.

Syntactically it is same as the if-then-else statement, but and the terms in the branches must be expressions and the entire if-then-else expression will itself evaluate to a value.

The shorthand writings that leave out the else-part does not make sense for the expression.

Example
clauses
    w(X, Y) :-
        Min = if X < Y then X else Y end if,
        writef("The minimum is : %\n", Min).
The if-then-else expression above evaluates to X if X is less than Y else it evaluates to Y. Min is bound to the resulting value.


try-catch-finally

The try-catch-finally statement provides means for dealing with exceptions that may occur in a given block of code.

TryCatchTerm:
    try Term CatchFinally-list end try
 
CatchFinally: one of
    catch Variable do Trap-Handler
    finally Finally-Handler
 
Handler:
    Term

A try-construction thus have a Term and a list of catch and finally handlers.

The Term and the handlers are not allowed to leave backtrack points (i.e. they cannot have mode multi or nondeterm).

A try-construction with more than one handler is equivalent to nesting several try-constructions with one handler each. I.e. the following term:

try
   Body
catch Var1 do
   Handler1
finally
   Handler2
catch Var2 do
    Handler3
end try

Is equivalent to these nested terms:

try
    try
        try
            Body
        catch Var1 do
            Handler1
        end try
    finally
        Handler2
    end try
catch Var2 do
    Handler3
end try

try-catch

Consider the try-catch construction

try
    Body
catch Var do
    Handler
end try

First Body is evaluated.

If Body fails or succeeds the whole try construction fails or succeeds, respectively. I.e. if Body does not terminate with an exception the try construction corresponds to evaluating Body.

If Body terminates with an exception, then the exception is caught by the catch handler. Meaning that first Var is bound to the exception (in PFC context the exception will be a traceId) and then Handler is evaluated. In this case the construction behaves as if Handler is evaluated with Var bound to the caught exception.

Notice, that no bindings are made by Body if it terminates with an exception.

Example Handle the situation where a file cannot be read:
clauses
    read(Filename) = Contents :-
        try
            Contents = file::readFile(Filename)
        catch TraceId do
            stdio::writef("Could not read the file: %\n", Filename),
            exceptionDump::dumpToStdio(TraceId),
            Contents = ""
        end try.

First Contents = file::readFile(Filename) is evaluated, if that does not terminate with an exception read returns the contents of the file.

If it raises an exception the handler is evaluated with TraceId bound to the exception. So in this case a message is written to stdio and then the exception is dumped to stdio, and finally Contents is set to the empty string which is returned as result.

try-finally

Consider the try-finally construction:

try
    Body
finally
    Handler
end try

The purpose of the construction is to evaluate the Handler after the Body no matter how the Body terminates, i.e. whether it succeeds, fails or terminates with an exception (it cannot leave backtrack points).

The evaluation is like this

First Body is evaluated.

  • If Body succeeds: Handler is executed and the try-finally construction succeeds.
  • If Body fails: Handler is executed and the try-finally construction fails.
  • If Body terminates with an exception Exn: Handler is executed and the try-finally construction terminates with the exception Exn.
Example Ensure that an odbcStatement is free'd after use:
clauses
    tryGetName(Connection, PersonId) = Name :-
        Stmt = odbcStatement::new(Connection),
        try
            Stmt:setParameterValue(1, core::integer(PersonId)),
            Stmt:execDirect("select name from person where id=?"),
            Stmt:fetch(),
            Name = Stmt:getParameterValue_string(1)
        finally
            Stmt:free()
        end try.

The Stmt is free'd also if fetch fails, or if something terminates with an exception.

Conversion

View and Construction Types

An interface defines a type of objects, all objects that supports the interface have that type. In the sequel we shall use the term the object type as synonym for the term the type defined by the interface.

Since interfaces define types, these types can be used as formal type specifiers in predicate and fact declarations and in domain definitions.

Since an object have the object type of any interface it supports, it can be used as an object of any of these types. I.e. the type of objects is converted to any supported object type. As described below the conversion is in many cases performed automatically.

So the same object can be viewed as having different types in different contexts. The type with which an object is viewed is called its view type, whereas the type of the class that constructed the object is called the construction type or definition type. The construction type is also a view type.

Type Conversion

As mentioned above objects can be used as having the type of any supported interface. This section describes how conversions between various supported types is handled.

Conversion Upwards

If some term is statically typed to some type T1 and T1 is declared to support T2 then it is obvious that any object referenced by the variable will indeed support T2. So upward support information is statically known. Subsequently all conversions upwards in the support hierarchy is performed automatically.

Example Assume the existence of the interface bb which supports an interface aa and the class bb_class with construction type bb. Consider the following code:
implement ...
   predicates
       ppp : (aa AA).
   clauses
       ... :-
           BB = bb_class::new(), % (1)
         ppp(B). % (2)
   clauses
       ppp(AA) :- % (3)
           ...
           BB = convert(bb,AA),    % Conversion possible since definition type of AA is bb
           ...

In the line marked (1) we create a bb_class object: the object has construction type bb. The variable BB is a reference to this new object. BB provides the view type bb on the object. In the line marked (2) the object is passed to ppp as an aa object. The conversion from view type bb to view type aa is performed implicitly. When the object reaches the line marked (3) it has view-type aa, though the construction type is still bb.

Explicit Conversion

Explicit conversion is performed by calling a conversion predicate.

Several conversion predicates are available.

Checked Conversion

The predicates convert/2-> and tryConvert/2-> are used to perform safe conversion from one type to another type.

Neither predicate can be given a real declaration, but here are pseudo declarations for them

predicates
   convert : ("type" Type, _ Value) -> Type ConvertedValue.
   tryConvert : ("type" Type, _ Value) -> Type ConvertedValue determ.

Both convert/2-> and tryConvert/2-> take a "type" as the first argument and a value of any type as the second argument and will then return the converted value as the result.

convert/2-> will raise an exception if the conversion is impossible, while tryConvert/2-> simply fails in that case.

Notice that the use of convert/2-> and tryConvert/2-> is always superfluous, if the source type is a subtype of the target type, because then the conversion will be performed implicitly.

convert/2-> and tryConvert/2-> can be used in the following situations:

  • converting from one number domain to another number domain
  • converting an object to another type

The compiler may complain (but does not have to) if it can determine that a conversion can never succeed, for example if attempting to convert between number domains that does not have overlapping ranges.

Conversion Downwards

When an object is converted to a super type (i.e. to a supported interface), then information about the object is "forgotten". Notice that the capabilities are not really lost they are just not visible in the context where the object is seen with a less capable interface.

In many situations it is necessary to restore the actual capabilities of the objects. Therefore, we need to be able to convert them downward as well as upwards.

Downward conversion cannot (in general) be validated statically. Therefore, it is necessary to use explicit conversion when restoring "lost" interfaces.

Example

While it is extremely simple to make sensible illustration of type conversions up in the supports-hierarchy, it requires a "real" example to illustrate sensible use of downward conversion. Therefore we shall present a more "real" example here.

Assume that we want to implement "sets of homogeneously typed objects". I.e. sets of objects which all supports a certain view type. We know that we will need such sets for several types of objects. Therefore we want to make our implementation in a way, which can easily be adopted to many different types of objects, but yet preserve the homogeneity of the contained objects.

Our approach is fairly standard: we make the actual implementation of the "set" based on the object type, which any object supports. And then construct the more specific versions of "sets" by means of a thin layer, which will convert between the actual type and object. We shall not show the actual implementation of object sets, we shall merely assume that it exists in the shape of the following class and interface:

interface objectSet
   predicates
       insert : (object Elem).
       getSomeElem : () -> object determ.
   ... 
end interface
class objectSet_class : objectSet
end class

Now assume that we have some object type myObject and that we want to create the corresponding "set" class myObjectSet_class. We declare myObjectSet_class as following:

interface myObjectSet
   predicates
       insert : (myObject Elem).
       getSomeElem : () -> myObject determ.
   ... 
end interface
class myObjectSet_class : myObjectSet
end class

I.e. myObjectSet has all the predicates of objectSet but every occurrence of object is replaced with myObject. The implementation of myObjectSet_class inherits from objectSet_class, this embedded/inherited objectSet will carry the members of the set. The implementation will fulfill the following invariant: The embedded objectSet will only contain objects of type myObject (even though they "technically" have type object).

The implementation looks as follows:

implement myObjectSet_class
    inherit objectSet_class
   clauses
       insert(Elem) :-
           objectSet_class::insert(Elem). % (1)
       getSomeElem() = Some :-
           SomeObject = objectSet_class::getSomeElem(), % (2)
           Some = convert(myObject, SomeObject). % (3)
   ...
end implement

In the line marked (1) Elem is automatically converted from type myObject to object. In the line marked (2) we retrieve an object from the embedded object set. Technically this object has type object. But from our invariant we know that the object also supports myObject. Subsequently, we know that we can safely restore the myObject interface. This is explicitly done in the line marked (3).

Private and Public Types

When an object is created with a constructor it is returned with the construction type. Such an object can automatically be converted to any supported interface and explicitly back again.

Even if the class that implements the object have stated further supported interfaces privately it is impossible to convert the "public" object to any of these private types.

In the implementation however the object can be accessed with any privately supported type. Furthermore "This" can be handed outside the implementation with any of these privately supported types.

Such a "private" version of an object can also be converted implicitly upwards in its hierarchy and explicitly downwards again. In fact such a "private" object can be converted explicitly to any publicly or privately supported interface.

So an object have two views the public view and the private view. The private view includes the public type. The object cannot be converted from one view to another, but since the private view includes the public type, the private view can be converted to any supported type whatsoever.

Unchecked Conversion

The predicate uncheckedConvert/2-> is used to perform unsafe conversions based on memory representation. The predicate does not modify memory in any way, it simply forces the compiler to interpret that piece of storage with another type.

Notice this predicate is highly unsafe and should be used with maximum precautions.

The predicate is intended to be used when interfacing to foreign languages, in order to interpret the memory images these foreign languages uses.

uncheckedConvert/2-> can only be used on pieces of memory that have exactly the same bit-size. However many kinds of data are represented by a pointer and such data have the same bit-size.

predicates
   uncheckedConvert : ("type" Type, _ Value) -> Type ConvertedValue.
Example
predicates
   interpretBufferAsString : (pointer BufferPointer) -> string Value.
clauses
   interpretBufferAsString(BufferPointer) = uncheckedConvert(string, BufferPointer).

This predicate will interpret (convert) a buffer represented by a pointer as a string.

This is only sound if the memory block has the correct representation to be a string.

Exception Handling

This section describes the low level constructions for dealing with exceptions in Visual Prolog. PFC does however put a higher level layer on top of this low level mechanisms (see the tutorial Exception Handling).

The basic part of the exception handling system is based on the built-in predicate errorExit/1 and the try-catch language construction.

When errorExit/1 is called the currently active exception handler is invoked. This exception handler is executed in its original context, i.e. in the context where it was set rather than in the context where the exception is raised.

The argument that errorExit/1 is invoked on is transferred to the exception handler. This argument must somehow provide the needed description of the exception.

Together with additional runtime routines, it is possible to build high-level exception mechanisms on top of this system.

It is however out of the scope of this document to describe runtime system access routines.

It is likewise out of the scope of this document to describe how the runtime system deals with exceptions occurring inside the runtime system.

The first argument of try-catch is the term to execute with new exception handler. The second argument must be a variable. This variable will be bound to the value errorExit/1 is invoked on, if it is invoked while this exception handler is active. The third argument is the exception handler, which will be invoked if errorExit/1 is called while this exception handler is active.

The exception handler can access the variable stated in the second argument thereby examining the exception that was raised.

Example

clauses
    p(X) :-
        try
            dangerous(X)
        catch Exception do
            handleDangerous(Exception)
        end try.

If an exception is raised while executing dangerous, then Exception will be bound to the exception value, and control will be transferred to the third argument of try-catch. In this case Exception is passed to handleDangerous.

Built-in entities

Visual Prolog contains an embedded hidden class, which provides declarations and implementations to all built-in constants, domains, and predicates.

These built-in constants, domains, and predicates can be used both during compilation (for example, in #if ... constructions) and in implementations (which are supported for runtime).

Each compilation unit implicitly contains the declaration of this embedded hidden class. To disambiguate from other entities with the same name you can use "::" before names of built-in items.

Notice that the clause variable This is automatically defined in the clauses for object predicates.

Operators

See also Operators.

Operator Description Remark
^ Power operation Not defined for 64 bit integral numbers
- (unary) Unary minus
*, / Multiplication and division
div, mod The quotient and remainder of an integral division rounded towards minus infinity Not defined for real's
quot, rem The quotient and remainder of an integral division rounded towards zero Not defined for real's
+, - Addition and subtraction
otherwise Otherwise expression
  • The operators are listed from highest to lowest precedence
  • All division and multiplication operators have same precedence.
  • The power operator ^ and otherwise are right associative.
  • All other operators are left associative.

All binary operators takes two arguments of same base type and returns a value of that base type. Operands and result may be converted using ordinary subtype rules.

Integral division

div and quot are different integral division operators.

  • div truncates towards minus infinite. mod is the remainder corresponding to div.
  • quot truncates towards zero. rem is the remainder corresponding to quot.

For positive results div and quot have same functionality.

The difference can be seen in this table:

A B A div B A mod B A quot B A rem B
15 7 2 1 2 1
-15 7 -3 6 -2 -1
15 -7 -3 -6 -2 1
-15 -7 2 -1 2 -1

Constants

compilation_date Compilation date
compilation_time Compilation time
compiler_buildDate Build date of the compiler
compiler_version Compiler version number
maxFloatDigits Maximum supported digits for real domains
null The default NULL pointer
nullHandle A constant of type handle with value 0
invalidHandle A constant of type handle with value −1 (invalid)
platform_bits Bitness of the compilation platform (32 or 64)
platform_name Target platform name

compilation_date

Compilation date in the format YYYY-MM-DD.

compilation_date : string = "YYYY-MM-DD".

compilation_time

Compilation time in the format HH:MM:SS (24-hour clock).

compilation_time : string = "HH:MM:SS".

compiler_buildDate

Build date of the compiler in the format YYYY-MM-DD HH:MM.

compiler_buildDate : string = "YYYY-MM-DD HH:MM".

compiler_version

Compiler version number (value depends on the compiler).

compiler_version = 1100.

maxFloatDigits

Maximum supported value of digits for real domains.

maxFloatDigits = 16.

null

A constant of type pointer with the value 0.

null : pointer = uncheckedConvert(pointer, 0).

null is also implicitly defined on all interfaces as a null pointer of the interface type. If it were defined explicitly, it would look like this:

interface xxx
...
constants
    null : xxx = uncheckedConvert(xxx, null).  % already implicitly defined
...
end interface xxx
Example This example shows how the constant can be used in a clause.
interface xxx
end interface xxx
 
...
clauses
    isNullXxx(X) :-
        xxx::null = X.

nullHandle

A constant of type handle with the value 0.

nullHandle : handle = uncheckedConvert(handle, 0).

invalidHandle

A constant of type handle with the value -1 (invalid for a handle).

invalidHandle : handle = uncheckedConvert(handle, -1).

platform_bits

Bitness of the compilation platform.

platform_bits = 32.
or
platform_bits = 64.

platform_name

Target platform name.

platform_name : string = "Windows 32bits".
or
platform_name : string = "Windows 64bits".

Domains

any Universal term type
char Unicode character (16-bit)
string UTF-16 zero-terminated string
string8 Zero-terminated 8-bit string typically in UTF-8 encoding
symbol Interned UTF-16 string (global symbol table)
binary Byte sequence (non-scanned)
binaryNonAtomic Byte sequence (GC-scanned; may contain pointers)
integer 32-bit signed integer
integer64 64-bit signed integer
integerNative Platform-sized signed integer (32/64-bit)
unsigned 32-bit unsigned integer
unsigned64 64-bit unsigned integer
unsignedNative Platform-sized unsigned integer (32/64-bit)
real Floating-point number (64-bit)
real32 Floating-point number (32-bit)
pointer Pointer value
pointerTo Pointer to a value of a given type
handle Operating system handle (e.g., Windows)
boolean Boolean values
factDB Descriptor of a named internal database
compareResult Result of a comparison

any

Universal term type.

any

Values of this domain can hold any term. Such a value contains a reference to the type library of the term and the term itself.

char

Unicode character.

char

Values of this domain are Unicode characters implemented as two unsigned bytes.

Only assignment and comparison (lexicographical) are defined. The image of a character has the following syntax:

Char_image :
      ' Char_value '
Char_value :
      Letter
      Digit
      Graphical_symbol
      Escape_seq
Escape_seq:
      \t
      \n
      \r
      \\
      \'
      \"
      \u<HHHH>

In the syntax above HHHH corresponds to four hexadecimal digits. The backslash and single quote can only be represented by escape sequences.

compareResult

The result domain for comparisons (e.g., compare/2->).

domains
   compareResult = less; equal; greater.

string

UTF-16 strings.

string

A string is a pointer to a zero-terminated sequence of UTF-16 code units. Elements are 16-bit values; certain characters are encoded using surrogate pairs. Strings are immutable.

In source code a string literal is one or more parts surrounded by double quotes:

StringLiteral:
   StringLiteralPart-list
StringLiteralPart :
   @" AnyCharacter-list-opt "
   " CharacterValue-list-opt "

Parts starting with @ do not use escape sequences; parts without @ use the following escapes:

  • \\ representing \
  • \t representing a tab character
  • \n representing a newline character
  • \r representing a carriage return
  • \' representing a single quote
  • \" representing a double quote
  • \u followed by exactly four HexadecimalDigit values representing the Unicode character

Double quotes in strings must be written using the escape sequence (single quotes may be written directly or escaped).

string8

A built-in domain whose elements are sequences of one-byte characters (bytes). Implemented as a pointer to a zero-terminated array of bytes.

Literals. The same string literal syntax (`"..."`) can be used both as a string literal and as a string8 literal, depending on context:

  • When a string8 value is expected, the literal is compiled as UTF-8 bytes with a trailing zero
  • When a string value is expected, the literal is compiled as UTF-16 code units with a trailing zero

If the context is ambiguous, disambiguate by using a typed context (e.g., a predicate parameter of type string8) or by explicit conversion.

Example
predicates
    use8  : (string8 S8).
    use16 : (string  S).
 
clauses
    demo() :-
        use8("Hello"),   % literal used as string8 (UTF-8)
        use16("Hello").  % the same literal used as string (UTF-16)

symbol

UTF-16 strings with the same representation as string, but also stored in a global symbol table.

symbol

A symbol is interned in a global symbol table; identical symbols share the same pointer value. Symbols are never reclaimed, so they should not be used for large, short-lived text.

symbol is a subtype of string, so a symbol can be used wherever a string is expected. The opposite is not automatic; to obtain a symbol from a string, explicitly convert to the symbol domain (or a subtype).

Equality is efficient for symbol values (pointer equality). Other comparisons behave like the corresponding string operations.

binary

Sequence of bytes.

binary

Used for holding binary data. A value is a pointer to the byte sequence that represents the contents of the binary term.

The length of a binary term is stored in the four bytes immediately preceding the sequence:

TotalNumberOfBytesOccupiedByBinary = ByteLen + 4

where ByteLen is the length of the sequence and 4 is the size field.

Only assignment and comparison are defined.

Two binaries are compared as follows:

  • If sizes differ, the larger size is greater
  • Otherwise, compare bytes (as unsigned) until a difference is found; equal if sizes match and all bytes are equal

The text syntax for binary images is determined by Binary:

Binary :
       $ [ Byte_value-comma-sep-list-opt ]
Byte_value :
      Expression

Each expression must be computable at compile time and have a value in the range 0.. 255.

binaryNonAtomic

Sequence of bytes.

binaryNonAtomic

Same as binary, but may contain pointers and is scanned by the garbage collector.

integer

32-bit signed integer.

integer

Values occupy 4 bytes. Arithmetic (+, -, /, *, ^), comparison, assignment, div/2->, mod/2->, quot/2->, and rem/2-> are defined.

Range: -2147483648 .. 2147483647.

Literals follow Integer:

Integer :
      Add_operation-opt 0o Oct_number
      Add_operation-opt Dec_number
      Add_operation-opt 0x Hex_number
Add_operation :
      +
      -
Oct_number :
      Oct_digit-list
Oct_digit : one of
      0 1 2 3 4 5 6 7
Dec_number :
      Dec_digit-list
Dec_digit : one of
      Oct_digit 8 9
Hex_number :
      Hex_digit-list
Hex_digit : one of
      Dec_digit a b c d e f A B C D E F

integer64

64-bit signed integer.

integer64

Values occupy 8 bytes.

Range: -2^63 = -9223372036854775808 .. 2^63-1 = 9223372036854775807.

Literals use the same syntax as Integer. The available operations mirror those for Integer.

integerNative

Platform-sized signed integer (32-bit in 32-bit programs; 64-bit in 64-bit programs).

integerNative

unsigned

32-bit unsigned integer.

unsigned

Values occupy 4 bytes. Arithmetic (+, -, /, *, ^), comparison, assignment, div/2->, mod/2->, rem/2->, and quot/2-> are defined.

Range: 0 .. 4294967295.

Literals use the same syntax as integer numbers. A leading minus (UnaryMinus) is not allowed for an unsigned literal.

unsigned64

64-bit unsigned integer.

unsigned64

Values occupy 8 bytes.

Range: 0 .. 2^64-1 = 18,446,744,073,709,551,615.

Literals use the same syntax as integer64 numbers. A leading minus (UnaryMinus) is not allowed for an unsigned64 literal.

Operations mirror those for Unsigned.

unsignedNative

Platform-sized unsigned integer (32-bit in 32-bit programs; 64-bit in 64-bit programs).

unsignedNative

real

Floating-point number.

real

Values occupy 8 bytes. All arithmetic, comparison, and assignment operations are defined.

Range: approximately -1.7e+308 .. 1.7e+308. Integral values are implicitly converted to real when needed.

Floating-point literals follow Real:

Real :
      Add_operation-opt Fraction Exponent-opt
Fraction :
      Dec_number Fractional_part-opt
Fractional_part :
      . Dec_number
Exponent :
      Exp Add_operation-opt Dec_number
Exp :
      e
      E
Add_operation :
      +
      -
Dec_number :
      Dec_digit-list
Dec_digit : one of
      0 1 2 3 4 5 6 7 8 9

real32

Floating-point number.

real32

Values occupy 4 bytes. All arithmetic, comparison, and assignment operations are defined.

Range: approximately -3.4e+38 .. 3.4e+38.

The syntax of real32 literals is the same as for real literals.

pointer

A pointer to a memory address.

pointer

Corresponds directly to memory addresses. Only equality comparison is defined. There is a built-in null constant for this type.

pointerTo

pointerTo{Type} represents a pointer to a value of type Type. Conceptually (it is built-in), it can be viewed as:

domains
    pointerTo{Type} = pointerTo(Type Value).

handle

Used for Windows API calls. Values have the same size as a pointer (4 bytes on 32-bit, 8 bytes on 64-bit platforms).

No operations are defined for this domain, and values cannot be converted to/from other domains (except via uncheckedConvert).

There are built-in constants: nullHandle and invalidHandle.

boolean

Boolean values.

boolean

This domain is provided for convenience and is treated as a normal compound domain:

domains
   boolean = false; true.

factDB

Descriptors of named internal databases.

factDB

This domain has the following hidden meta-declaration:

domains
   factDB = struct @factdb( named_internal_database_domain, object ).

All user-defined names of facts sections are constants of this domain. The compiler automatically builds the corresponding compound terms when needed. At runtime, the first field holds the address of the corresponding domain descriptor, and the second holds either zero (for class facts sections) or a pointer to an object (e.g., This for object facts sections).

Predicates

and/2
,/2
Term "and"
assert/1 Insert the specified fact at the end of the matched internal facts database.
asserta/1 Insert a fact at the beginning of the matched internal facts database.
assertz/1 Insert a fact at the end of the matched internal facts database.
bound/1 determ Test whether the specified variable is bound to a value.
class_name/0-> This compile time predicate returns the string ClassName that represents the name of the current interface or class.
compare/2-> Returns the result of the variables' comparison.
constant_name/0-> This compile time predicate returns the string ConstantName that represents the name of the current constant. Typically used in execepion definitions.
convert/2-> Checked term conversion.
digitsOf/1-> Returns precision of the specified floating-point domain.
errorExit/1 erroneous Performs a run-time error with the specified return code ErrorNumber and sets the internal error information.
fact_address/1-> Returns the address of a fact variable.
fail/0 failure Invoke backtracking.
free/1 determ Check whether a variable is free.
fromEllipsis/1-> Creates the list of terms of the universal type any from the EllipsisBlock.
hasDomain/2
hasDomain/2->
Declares/restricts the type of a variable or value.
in/2 determ
in/2 nondeterm
Infix operator "in" (in-test and in-iterator).
isErroneous/1 determ Returns the lower bound value of the specified numeric domain.
lowerBound/1-> Returns the lower bound value of the specified numeric domain.
maxDigits/1-> Retrieves the value of digits (precision) of the basic domain corresponding to the specified floating-point domain domainName.
not/1 determ Negate the result (success/fail) of subgoal.
otherwise/2 Infix expression operator providing a value when a determ expression fails
or/2
;/2
Nondeterministic term "or"
orelse Deterministic term "or"
predicate_fullname/1-> This compile time predicate returns the string PredicateFullName that represent the name of the predicate in which clause body predicate_name is called. The returned predicate name is qualified with a scope name.
predicate_name/1-> This compile time predicate returns the string PredicateName that represent the name of the predicate in which clause body predicate_name is called. The returned predicate name is not qualified with a scope name.
programPoint/0-> This compile time predicate returns the programPoint corresponding to the place where it is called.
retract/1 nondeterm Remove a matched fact from the matched internal facts database.
retractall/1 Remove all matching facts from the matched internal facts database.
retractFactDb/1 Remove all facts from the specified named internal facts database.
sizeBitsOf/1-> Retrieves the number of bits occupied in memory by an entity of the specified domain DomainName.
sizeOf/1-> Retrieves the number of bytes occupied in memory by the specified term.
sizeOfDomain/1-> Retrieves the number of bytes occupied in memory by the entity of the specified domain DomainName.
sourcefile_lineno/0-> Returns the current line number in the source file processed by the compiler .
sourcefile_name/0-> Returns the name of the source file processed by the compiler.
sourcefile_timestamp/0-> Returns the string representing the date and time of the source file processed by the compiler.
succeed/0 The predicate succeed/0 will always succeed.
toAny/1-> Converts the specified Term to the value of the universal term type any.
toBinary/1-> Converts the specified Term to the binary representation.
toBoolean/1-> The purpose of this meta-predicate is to convert the deterministic call (to a predicate or fact) to the procedure that returns the value of boolean domain.
toEllipsis/1-> Creates the EllipsisBlock from the list of any type values.
toString/1-> Converts the specified Term to the string representation.
toTerm/1->
toTerm/2->
Converts the string/binary representation of the specified term SrcTerm into representation corresponding to the domain of PrologTerm variable of the return value.
tryToTerm/1-> determ
tryToTerm/2-> determ
Converts the string/binary representation of the specified term SrcTerm into representation corresponding to the domain of PrologTerm variable of the return value.
tryConvert/2-> determ Checks whether the input term InputTerm can be strictly converted into the specified domain returnDomain and returns the converted term ReturnTerm.
typeDescriptorOf/1-> Returns the typeDescriptor of a value.
typeLibraryOf/1-> Returns the typeLibrary of a value.
uncheckedConvert/2-> Unchecked conversion of domains.
upperBound/1-> Returns the upper bound value of the specified numeric domain.

The following predicates are deprecated:

finally/2 Use try-finally constuction instead.
findall/3 Use list comprehension [ ... || ...  ] instead
trap/3 determ Use try-catch constuction instead.

and

See and (,).

assert

assert : (<fact-term> FactTerm).

Insert the specified fact at the end of the matched internal facts database

assert(Fact) inserts Fact in the matched internal facts database after any other stored facts for the corresponding database predicate. Fact must be a term belonging to the domain of an internal facts database. assert/1 applied to a single fact changes the existing instance of a fact to the specified one. assert/1 has the same effect as assertz/1. See also asserta/1.

Notice that the combination of retract/1 and assert/1 like the following can lead to endless loop:

loop() :-
  retract(fct(X)),
     ...           % creating Y from X
     assert(fct(Y)),
  fail.

The problem is that the retract in first line will eventually retract the fact asserted in the last line, because that fact is inserted last in the fact chain.

Exceptions:

  • Attempt to assert a second instance to a fact declared as determ.

asserta

asserta : (<fact-term> FactTerm).

Insert a fact at the beginning of the matched internal facts database.

The asserta(Fact) predicate inserts a Fact in the matched internal facts database before any other stored facts for the corresponding predicate. The Fact must be a term belonging to the domain of an internal facts database. The asserta/1 applied to a single fact changes the existing instance of a fact to the specified one. See also assert/1 and assertz/1.

Exceptions:

  • Attempt to a fact declared as determ, but the fact instance already exists.

assertz

assertz : (<fact-term> FactTerm).

assertz does exactly the same as the assert/1 predicate.

bound

bound : (<variable> Variable) determ.

Test whether the specified variable is bound to a value.

The bound(Variable) succeeds if Variable is bound and fails if it is free. The bound predicate is used to control flow patterns and to check the binding of reference variables. The bound predicate treats the specified Variable as bound if any of it's part is instantiated.

See also free/1.

class_name

class_Name : () -> string ClassName.

This compile time predicate returns the string ClassName that represents the name of the current interface or class.

compare

compare : (A Left, A Right) -> compareResult CompareResult.

Comparison of two terms of the same domain, resturns the value of compareResult domain.

CompareResult = compare("bar", "foo")

constant_name

constant_name : () -> string ConstantName.

This compile time predicate returns the string ConstantName that represents the name of the current constant. It is typically used in exception definitions.

convert

convert : (<type> Type, Term) -> <type> Converted.

Checked term conversion.

Call-template for this function is:

ReturnTerm = convert(returnDomain, InputTerm)

  • returnDomain: Specifies a domain to which function convert/2-> converts InputTerm. Here returnDomain must be a name of built-in Visual Prolog domain, an interface domain, a name of such user defined domain that is synonym to one of built-in Visual Prolog domains, a numeric domain, binary and pointer domains. The domain name returnDomain must be specified at compile-time, i.e. it cannot come from a variable.
  • InputTerm: Specifies the value that must be converted. InputTerm may be any Prolog term or an expression. If InputTerm is an expression, then it will be evaluated before the conversion.
  • ReturnTerm: Returned parameter ReturnTerm will be of returnDomain type.

The convert predicate performs a clean and genuine conversion of the given InputTerm, returning a new term ReturnTerm of the specified new domain returnDomain. If convert cannot perform the required conversion, it rises errors. The similar functionality is provided by the tryConvert/2-> predicate, but tryConvert-> fails and does not produce any runtime errors if it cannot perform the conversion.

Allowed conversions
  • Between numerical domains.
  • Between interface types.
  • Between string and symbol domains.
  • From binary to pointer.
  • For synonyms of mentioned domains.
  • Between reference domains and corresponding non-reference domains.

The contrast to these is uncheckedConvert/2-> predicate, which performs an unchecked conversion between terms from any domains, which have the same bit-size.

The convert/2-> (or tryConvert/2->) predicate accomplishes a checked explicit conversion, when the source and target domains are statically known during the compilation. The result of an explicit conversion can be one of the following:

  • ok the successful conversion to the target domain;
  • run-time-check the conversion to the target domain with generation of run-time checking for compatibility;
  • error the conversion is impossible, error output.
Rules of Checked Explicit Conversions
  • Synonyms of domains are converted using the same rules that are applied to the domains themselves.
  • Numerical domains can be converted to the numerical domains only.
  • Integral constants are the representatives of the anonymous integral domain: [const .. const].
  • Real constants are the representatives of the anonymous real domain: digits dig [const .. const], where dig is the number of the digits in mantissa without insignificant zeroes.
  • A value of the symbol domain can be converted to the string domain and vice versa.
  • A value of binary domain can be converted to the pointer domain.
  • The domains that are implicitly introduced for interfaces can be converted only to the interface domains according to the rules specified below.
  • All other domains cannot be converted.
Conversions of Numerical Domains
  • The range is considered first during such conversion. If the ranges of source and target do not intersect, then an error is produced. If the ranges of source and target only partially intersect, then run-time checking is generated. Also, if one of domains is real and another is an integral one, then the integer range is converted to the real range before the comparison.
  • When input term in real and output is integer, then convert/2-> and tryConvert/2-> predicates truncate the input value to the nearest integer value, which is nearer to zero.
Conversions of Interface Types

Predicate convert/2-> allow to convert any object to any interface type. The actual correctness of such conversion is checked at runtime. When object is created, its type is internally stored, therefore when the object is passed as argument it still remember about its original type. This original type is used for checking allowed conversions. The example:

interface x
      supports a, b
end interface x

If object is created by class, which implements x interface, and then object is passed as parameter of type a to some predicate, then it is allowed to convert the object to b type.

Exceptions:

  • Check range error.
  • Unsupported interface type.

digitsOf

digitsOf : (<real-domain> Domain) -> unsigned.

Returns precision of the specified floating-point domain.

Call-template for this function is:

Precision = digitsof(domainName)

The input parameter domainName of this compiling-time predicate is a floating-point domain, it should be explicitly specified at compile-time (that is, domainName cannot come from a variable). The predicate returns the number Precision that was determined by the digits attribute in the domain declaration.

The compiler guarantees that values of the domain domainName will have at least Precision number of significant decimal digits.

errorExit

errorExit : (unsigned ErrorNumber) erroneous.

Performs a run-time error with the specified return code ErrorNumber, which can be used in the try-catch-finally.

fact_address

fact_address : (FactType FactVariable) -> pointerTo{FactType} PointerToFactVariable.

The fact_address predicate returns the address (as a pointerTo{FactType}) of a fact variable FactVariable of type FactType.

FactVariable must be a fact variable.

fail

fail : () failure.

The fail predicate forces failure and, hence, always causes backtracking. A clause that fails (with fail or for some other reason) cannot bind output arguments.

free

free : (<variableName> Variable) determ.

Check whether a variable is free.

Call-template for this predicate is:

free(Variable)

The free predicate succeeds if the specified Variable is free and fails if Variable is bound. The free predicate treats the specified Variable as bound if any of it's part are instantiated.

See also bound/1.

fromEllipsis

fromEllipsis : (...) -> any* AnyTermList.

This predicate creates the list of terms of the universal type any from the EllipsisBlock ... (i.e. from the special varying parameters block).

Call-template for this function is:

AnyTermList = fromEllipsis(EllipsisBlock )

See also toEllipsis/1->.

hasDomain

hasDomain is not really a predicate, but more a type declaration/restriction. It has two forms a non-function for declaring/restricting the type of a variable and a function form for declaring/restricting the type of a value.

The non-function form is called with a type as first parmeter and a variable as second parameter.

hasDomain : (<type> Type, Type Variable).

The only effect of the call is that the Variable will be restricted to the type Type.

The variable can be free, bound or of some mixed flow and the binding of the variable will not change in any way.

The function form is called with a type as first argument and a value as second argument, and it returns the same value.

hasDomain : (<type> Type, Type Value) -> Type Value.

The only effect of the call is to ensure that the Value will be restricted to the type Type.

lowerBound

lowerBound : (<numeric-domain> NumericDomain) -> <numeric-domain> LowerBound.

Returns the lower bound of the specified NumericDomain.

Call-template for this function is:

LowerBoundValue = lowerBound(domainName)

The lowerBound is a compiling-time predicate. The lowerBound returns the lower bound value LowerBoundValue of the specified numeric domain domainName. The return value LowerBoundValue belongs to the same domain domainName. The domainName parameter should be the name of any numerical domain; this domain name should be explicitly specified at compile-time (that is, domainName cannot come from a variable). See also upperBound/1->.

It will give a compile time error if the specified domain domainName is not numeric domain.

in

See in/2.

isErroneous

isErroneous : (<fact-variable> FactVariable) determ.

The predicate succeeds if the specified fact variable is erroneous.

Call-template for this predicate is:

isErroneous(factVariableName)

The predicate succeeds if the specified fact variable factVariableName has the erroneous value, otherwise it fails.

See also notErroneous.

maxDigits

maxDigits : (<real-domain> RealDomain) -> unsigned MaxDigits

Retrieves the value of digits (precision) of the basic domain corresponding to the specified floating-point domain RealDomain.

Call-template for this function is:

MaxDigitsNumber = maxdigits(domainName)

The return maximal number of digits MaxDigitsNumber for the domainName parameter, which should be the name of a real domain.

not

See not.

notErroneous

The notErroneous/1-> predicate will succeed with the value of a fact if the fact is not erroneous. The main purpose of the predicate is to get an atomic view of the fact in a multi-threaded application.

Example
facts
    theFact : integer := erroneous.
clauses
    ppp() :-
        if F = notErroneous(theFact) then
            % theFact was not erroneous, its value was F
        end if.

The related code using isErroneous/1 is not threadsafe:

clauses
    ppp() :-
        if not(isErroneous(theFact)) then
            % theFact was not erroneous, but it can be in the next line
            F = theFact              
        end if.

See also isErroneous.

otherwise

See otherwise.

or

See or (;).

orelse

See orelse.

predicate_fullname

predicate_fullname : () -> string PredicateFullName.

This predicate returns the name PredicateFullName of the predicate in which it is invoked. The returned predicate name is qualified with a scope name.

predicate_fullname can only be used inside a clause. Use of predicate_fullname in other places causes a compile time error. See also predicate_name.

predicate_name

predicate_name : () -> string PredicateName.

This predicate returns the name PredicateName of the predicate in which it is invoked.

predicate_name can only be used inside a clause. Use of predicate_name in other places causes a compile time error. See also predicate_fullname

programPoint

programPoint : () -> core::programPoint ProgramPoint.

This predicate returns the name programPoint corresponding to the place where it is invoked.

retract

retract : (<fact-term> FactTerm) nondeterm anyflow.

Successively removes the first matching fact from the facts database. Fails when no more facts match.

Call-template for this predicate is:

retract(FactTemplate)

Here FactTemplate should be a fact term. The retract/1 predicate deletes the first fact that matches the FactTemplate in the appropriated facts database. During backtracking, the rest of the matching facts will be deleted.

Notice that FactTemplate can have any level of instantiation. The FactTemplate is matched with the facts in the facts database, which means that any free variables will be bound in the call to retract/1.

The FactTemplate can contain any anonymous variables. That is, variables with names consisting from the single underscore _ or a variable with a name starting with an underscore _AnyValue if the variable occurs only once in the clause. For example.

retract(person("Hans", _Age)),

will retract the first matched person fact that has "Hans" as the first argument and anything as the second argument.

When retracting a fact, which is declared to be determ, the call to retract/1 will be deterministic.

See also retractall/1 and retractFactDb.

The retract/1 predicate cannot be applied to single facts or fact variables.

Be careful calling retract/1 with free FactTemplate variable if any single fact is declared in the project current scope. If you retract a single fact, then the run-time error is generated. The retract/1 predicate fails when there are no more matches.

retractall

retractall : (<fact-term> FactTerm) .

Remove all matching facts from the facts database.

Call-template for this predicate is:

retractall(FactTemplate)

Here FactTemplate should be a fact term.

The retractall/1 retracts all facts which match the given FactTemplate. It always succeeds, even if no facts were retracted.

Attempting to retract a single fact will cause a compile time error.

It is not possible to obtain any output values from retractall/1. For this reason, the variables in the call must be bound or be a single underscores (anonymous). Notice that FactTemplate can have any level of instantiation, but free variables must be single underscores ("unconditionally anonymous"). In difference to retract/1 "conditionally" anonymous variables with names starting from the underscore (like _AnyValue) cannot be used in retractall/1.

See also retract/1 and retractFactDb/1.

retractFactDb

retractFactDb : (factDB FactDB).

Remove all facts from the named internal facts database FactDB.

Call-template for this predicate is:

retractFactDb(FactDB)

The retractFactDb/1 removes all facts from the named facts database FactDB.

Notice, it is impossible to retract single facts and fact variables, so the predicate leaves such ones as they are.

See also retractall/1 and retract/1.

retractAll/2

Obsolete predicate! Use retractFactDb/1 instead.

sizeBitsOf

sizeBitsOf : (<domain> DomainName) -> unsigned BitSize.

Retrieves the number of bits occupied in memory by an entity of the specified domain DomainName.

Call-template for this function is:

BitSize = sizeBitsOf(DomainName)

This compiling-time predicate receives the domain DomainName as input parameter and return the size of memory that is occupied by the entity of the given domain. The result is measured in bits. For the integer domains sizeBitsOf/1-> predicate returns the value that was defined for the size-field in a domain's declaration.

The following is always true for the integral domains:

sizeOfDomain(domain)*8 - 7 <= sizeBitsOf(domain) <= sizeOfDomain(domain)*8

See also sizeOfDomain/1->.

sizeOf

sizeOf : (Type Term) -> integer ByteSize.

Retrieves the number of bytes occupied in memory by the specified term Term.

Call-template for this function is:

ByteSize = sizeOf(Term)

The sizeOf/1-> function receives a term as input parameter and returns value ByteSize that specifies the number of bytes occupied in memory by this term Term.

sizeOfDomain

sizeOfDomain : (<domain> Domain) -> integer ByteSize.

Retrieves the number of bytes occupied in memory by the entity of the specified domain DomainName.

Call-template for this function is:

ByteSize = sizeOfDomain(DomainName)

This compiling-time predicate receives the domain DomainName as input parameter and return the size of memory that is occupied by the entity of the given domain. The result is measured in bytes. The returned value ByteSize belongs to the integer domain. Compare with sizeBitsOf/1->, which returns size of a domain measured in bits.

sourcefile_lineno

sourcefile_lineno : () -> unsigned LineNumber.

Returns the current line number in the source file processed by the compiler.

sourcefile_name

sourcefile_name : () -> string FileName.

Returns the name of the source file processed by the compiler.

sourcefile_timestamp

sourcefile_timestamp : () -> string TimeStamp..

Returns a string that represents the date and time of the currently compiled source file in format YYYY-MM-DD HH:mm:ss. Where:

  • YYYY - Year.
  • MM - Month.
  • DD - Day.
  • HH - Hour.
  • mm - Minute.
  • ss - Second.

succeed

succeed : ().

The predicate succeed/0 will always succeed.

toAny

toAny : (Term) -> any UniversalTypeValue.

Converts the specified Term to the value of universal term type any.

Call-template for this function is:

UniversalTypeValue = toAny(Term)

A term of the any domain can be converted back to its original type using the toTerm predicates (see toTerm).

toBinary

toBinary : (Term) -> binary Serialized.

Converts the specified Term to binary representation.

Call-template for this function is:

Serialized = toBinary(Term)

When a Term (of some domain domainName) is converted into a binary, it can safely be stored in a file or sent over a network to another program. Later the obtained binary value Serialized can be converted back to a Visual Prolog term, using toTerm/1-> function (the domain for the reversed term should be adequate to domainName) for the reverse conversion.

toBoolean

toBoolean : (<deterministic_expression> SubGoal) -> boolean Succeed.

The purpose of this meta-predicate is to convert an expression to the value of boolean domain.

Call-template for this meta-predicate is:

True_or_False = toBoolean(deterministic_expression)

this is equivalent to

True_or_False = if deterministic_expression then true else false end if

The toBoolean/1-> meta-predicate returns boolean value. The result is true if deterministic_call succeeds. The result is false if deterministic_call fails.

toEllipsis

toEllipsis : (any* AnyTermList) -> ....

This predicate creates EllipsisBlock ... (i.e. the special varying parameters block) from the list of terms of the universal type any. Such EllipsisBlock can be later passed to a predicate which expects the varying number of arguments (i.e. is declared with the ellipsis (...)), like write/..., at the position of the ellipsis (...).

Call-template for this function is:

EllipsisBlock = toEllipsis(<any_term_list>), write(EllipsisBlock)

See also fromEllipsis/1->.

toString

toString : (Term) -> string Serialized.

Converts the specified Term to string representation.

Call-template for this function is:

Serialized = toString(Term)

When a Term (of some domain domainName) is converted into a string, it can safely be stored in a file or sent over a network to another program. Later the obtained string value can be converted back to a Visual Prolog term, using toTerm/1-> function (the domain of the return value should be adequate to domainName) for the reverse conversion.

toTerm

toTerm : (string Serialized) -> Term.
toTerm : (binary Serialized) -> Term.
toTerm : (any Serialized) -> Term.
toTerm : (<domain> Type, string Serialized) -> Term.
toTerm : (<domain> Type, binary Serialized) -> Term.
toTerm : (<domain> Type, any Serialized) -> Term.

Converts the string/binary/any representation of the specified term Serialized into representation corresponding to the domain of Term variable of the return value. The domain can be stated explicitly or it can be left to the compiler to determine a suitable domain.

Call-template for this function is:

Term = toTerm(Serialized) % with implicit domain
Term = toTerm(domainName, Serialized) % with explicit domain, domainName

If the domain is not specified the compiler must be able to determine the domain for the returned value Term at compile-time. Notice that binary version of toTerm predicate performs almost byte to byte conversion and only checking general compatibility of Serialized data with the domain required to the return value Term. The programmer is wholly responsible for providing binary data of Serialized that can be correctly converted to the term of the desired domain. The toTerm predicates are counterparts to predicates toBinary/1-> and toString/1->. When a Term (of some domain domainName) is converted into a binary or string representation Serialized (by toBinary/1-> or toString/1-> or toAny/1-> correspondingly), it can safely be stored in a file or sent over a network to another program. Later the corresponding toTerm/1-> function can convert the obtained string/binary value Serialized back to a Visual Prolog term Term. For correctness of the reverse conversion the domain of the clause variable Term should be adequate to the initial domain domainName.

See also tryToTerm.

It gives a compile time error if the compiler cannot determine the return domain.

Exceptions

  • Run time errors are generated when the toTerm predicate cannot convert the string or binary into a term of the specified domain.

tryToTerm

tryToTerm : (string Serialized) -> Term.
tryToTerm : (binary Serialized) -> Term.
tryToTerm : (any Serialized) -> Term.
tryToTerm : (<domain> Type, string Serialized) -> Term.
tryToTerm : (<domain> Type, binary Serialized) -> Term.
tryToTerm : (<domain> Type, any Serialized) -> Term.


Converts the string/binary/any representation Serialized into a term Term like toTerm. The only difference between the predicates is that tryToTerm fails if it cannot convert the string or binary or any into a term of the specified domain whereas toTerm raises an exception.

See also toTerm.

tryConvert

tryConvert : (<type> Type, Value) -> <type> Converted determ.

Checks whether the input term Value can be strictly converted into the specified domain Type and returns the converted term Converted.

Call-template for this function is:

ReturnTerm = tryConvert(returnDomain, InputTerm)

Arguments:

  • returnDomain: Specifies a domain to which tryConvert/2-> predicate tries to convert the specified InputTerm. Here returnDomain can be any domain accessible in the current scope. The domain name returnDomain must be specified at compile-time, i.e. it cannot come from a variable.
  • InputTerm: Specifies the term that must be converted. InputTerm may be any Prolog term or an expression. If InputTerm is an expression, then it will be evaluated before conversion.
  • ReturnTerm: Returned term ReturnTerm will be of returnDomain domain.

The conversion rules are the same as of the embedded predicate convert/2->, but tryConvert/2-> fails when convert/2-> generates conversion errors.

This predicate succeeds if the corresponding conversion succeeds. Otherwise it fails. The tryConvert/2-> predicate tries to perform a clean and genuine conversion of the given InputTerm into a value of the specified domain returnDomain. The tryConvert/2-> predicate will fail if the required conversion cannot be performed. When tryConvert/2-> predicate succeeds, it returns the term ReturnTerm converted to the specified domain returnDomain.

For allowed conversions and rules of checked explicit conversions see convert/2-> predicate.

See also uncheckedConvert/2->.

typeDescriptorOf

typeDescriptorOf : (<type> Type) -> typeDescriptor TypeDescriptor.
typeDescriptorOf : (Type Value) -> typeDescriptor TypeDescriptor.

Reflection predicate that returns the typeDescriptor of a type or a value.

A typeDescriptor is the reflection descriptor of an uninstantiated type/domain.

typeLibraryOf

typeLibraryOf : (<type> Type) -> typeLibrary TypeLibrary.
typeLibraryOf : (Type Value) -> typeLibrary TypeLibrary.

Reflection predicate that returns the typeLibrary of a type or a value.

A typeLibrary is the reflection descriptor of an instantiated type/domain.

uncheckedConvert

uncheckedConvert : (<type> Type, Value) -> <type> Converted.

Unchecked conversion of a value to another type.

Call-template for this function is:

ReturnTerm = uncheckedConvert(returnDomain, InputTerm)

Arguments:

  • returnDomain: Specifies a domain to which uncheckedConvert predicate unsafely converts the specified InputTerm. Here returnDomain can be any domain accessible in the current scope, the ReturnTerm should has the same bit-size as the InputTerm. The domain name returnDomain must be specified at compile-time, i.e. it cannot come from a variable.
  • InputTerm: Specifies the value that must be converted. InputTerm may be any Prolog term or an expression. If InputTerm is an expression, then it will be evaluated before conversion.
  • ReturnTerm: Returned parameter ReturnTerm will be of returnDomain type.

uncheckedConvert evaluates InputTerm, change the type to returnDomain without any modification of the memory pattern and unifies with ReturnTerm. The uncheckedConvert predicate performs no runtime checks. It makes only compile time checking of bit-size equality of the converted domains. So almost any term may be quite recklessly converted to any other term. So quite disastrous results may occur if you try to use variables incorrectly converted by uncheckedConvert. Be extremely careful implementing uncheckedConvert; we strongly recommend you always, when it is possible, using of convert/2-> and tryConvert/2->. But notice that, when an object is returned by COM system it is necessary to convert it by uncheckedConvert, as Prolog program does not have information about its actual type.

upperBound

upperBound : (<numeric-domain> NumericDomain) -> <numeric-domain> UpperBound.

Returns the upper bound value of the specified numeric domain.

Call-template for this function is:

UpperBound = upperBound(domainName)

The upperBound is a compiling-time predicate. The upperBound returns the upper bound value of the specified numeric domain domainName. The return value UpperBound belongs to the same domain domainName. The domainName parameter should be the name of any numerical domain; this domain name should be explicitly specified at compile-time (that is, domainName cannot come from a variable).

See also lowerBound/1->.

Will cause a compile time error if the specified domain domainName is not numeric domain.

Directives

Each compiler directive starts from the # character. The following directives are supported:

  • #include, #bininclude, #stringinclude - file inclusion.
  • #if, #then, #else, #elseif, #endif - conditional statements.
  • #export, #externally - exporting and importing classes.
  • #message, #error, #requires, #orrequires - compilation time information.
  • #options - compiler options.


Source File Inclusion

The #include compiler directive is used to include the contents of another file into your program source code during compilation. It has the following syntax:

Pp_dir_include :
   #include String_literal

The String_literal should specify an existing filename.

#include "pfc\\exception\\exception.ph" % Includes pfc\exception\exception.ph file
#include @"pfc\vpi\vpimessage\vpimessage.ph" % Includes pfc\vpi\vpimessage\vpimessage.ph

This compiler directive uses "include the first file occurrence only" semantics. That is, if a compilation unit contains several include directives for the same file, it will be included only one time with the first include directive.

Each included file must contain several accomplished scopes; an included file cannot contain uncompleted scopes. That is, it should contain several accomplished interface declarations, class declarations, class implementations or/and several compiler directives.

The compiler tries to find the specified include source file in the following way:

  1. If the filename contains an absolute path, then this file should be included.
  2. Otherwise, the compiler searches for the specified include filename among the paths that had been defined by the /Include command line option. These paths are handled consequently as they are specified in the option. In the IDE you can set these paths in the Include Directories in the Directories tab of the Project Settings dialog.

If the compiler does not find the specified file a compiling time error is generated.

Text File Inclusion

The #stringinclude compiler directive is used to include (during compilation) the contents of a file (specified by the string_literal string) as a ::string constant into your program source code. It has the following syntax:

Pp_dir_bininclude :
   #stringinclude( String_literal )

This directive can be used in any places where string constants are allowed. The string_literal should specify an existing filename. The syntax is the same as in the #include compiler directive described in the previous paragraph Source File Inclusions. The compiler tries to find the specified file in the same way as for #include compiler directive. If the file has a byte-order-mark it will be treated accordingly, if the file does not have byte order mark and does not appear to be in utf-16 it will be read with the current codepage (it is recommended to use files with byte-order-mark utf-8 or utf-16).

Example A typical usage is like this:
constants
    myText : string = #stringinclude("text.txt").
    % String constant from contents of the file "text.txt".

Binary File Inclusion

The #bininclude compiler directive is used to include (during compilation) the contents of a file (specified by the string_literal string) as a ::binary constant into your program source code. It has the following syntax:

Pp_dir_bininclude :
   #bininclude( String_literal )

This directive can be used in any places where binary constants are allowed. The string_literal should specify an existing filename. The syntax is the same as in the #include compiler directive described in the previous paragraph Source File Inclusions. The compiler tries to find the specified file in the same way as for #include compiler directive.

Example A typical usage is like this:
constants
    myBin : binary = #bininclude("Bin.bin").
    % Binary constant from contents of the file "Bin.bin".

When creating a binary constant the compiler adds the EOS symbol immediately after this constant.

Exporting and Importing Classes

Compiler directives #export and #externally are used to determine lists of exported and imported classes, respectively. They have the following syntax:

Pp_dir_export :
   #export ClassNames-comma-sep-list
Pp_dir_export :
   #externally ClassNames-comma-sep-list

These compiler directives are applied only to classes classNames, which do not construct objects.

They can be used only outside scopes; that is, they cannot be used inside declarations of interfaces and classes and they cannot be used inside implementations of classes.

By default, predicates within one executed module are hidden at runtime for all other executed modules. An #export compiler directive makes names of specified classes public outside the module in which they are declared (and implemented). Therefore, all predicates from this module declared in the classes (specified in an #export directive) become accessible while runtime from other executed modules.

Usually, an #export compiler directives can be used in projects, which target modules are DLLs. It enumerates classes declared in a DLL, which should be accessible to other modules that use this DLL.

If a compilation unit export some class, then this compilation unit should contain this class implementation.

Also an #export compiler directives can be used to specify condition expressions for #if compiler directives.

For example, let us suppose that somewhere in the beginning of a compilation unit the compiler has met the #export compiler directive like this:

#export className

Then the compiler, if in the subsequent code it meets an #if compiler directive with the same #export compiler directive used as the condition expression, for example like this:

#if #export className #then  ...  #endif

Then the compiler evaluates the #export condition expression as true and, hence, the compiler executes the #then branch of the conditional compilation directive.

For example, the following #export compiler directive with the subsequent #if conditional compilation compiler directive:

#export className
...
#if #export className #then #requires "some.pack" #endif

guaranty that the "some.pack" package will be included into the compilation unit.

From the other hand, if an #export compiler directive is not met by the compiler (somewhere in the compilation unit before the #if compiler directive, which uses the same #export compiler directive as the conditional expression), then the compiler evaluates this #export condition expression as false. Hence, the compiler will not execute the #then branch of the #if conditional compilation directive. That is, the single #if compiler directive without previous #export directive

#if #export className #then #requires "some.pack" #endif

does not requires to include the "some.pack" package.

An #externally compiler directive is counterpart to an #export compiler directive. An #externally compiler directive can be used instead of (and concurrently with) an IMPORTS directive in definition files. An #externally compiler directive enumerates classes, which are declared in a module but implemented in other modules. Therefore, the compiler will not produce errors when it detects such classes. The referenced classes can be implemented (and exported) in DLLs, which can be linked to the module at runtime.

The #export and #externally compiler directives can be used as Condition boolean expressions in Conditional Compilation.

For example, like this:

#if #export className #then #include "Some package.pack" #endif

Compile Time Information

Compiler directives #message, #requires, #orrequires, and #error can be used to issue user-defined messages into a listing file while compilation of project modules and to interrupt compilation.

These directives can be used either outside scopes (interface declaration, class declaration or class implementation), or inside scopes but outside sections. They have the following syntax:

Pp_dir_message: one of
    #message String_literal
    #error String_literal
    #requires String_literal Pp_dir_orrequires-list-opt
    #orrequires String_literal

When the compiler meets any of these directives, it generates the correspondent warning message and place the directive text into a listing file.

A listing file name can be specified with the compiler directive:

/listingfile:"FileName"

Notice that no empty spaces can be used between the colon : (after /listinglile) and "FileName".

By default the compiler does NOT generate informative messages for the #message, #requires, and #orrequires directives. You can switch generation of these informative messages ON specifying the compiler options:

/listing:message
/listing:requires
/listing:ALL
Example In this case, when the compiler meets a directive like:
#message "Some message"

it will place the following text into the listing file:

C:\Tests\test\test.pro(14,10) : information c062: #message "Some message"

The directive #requires (#orrequires) issues arbitrary user-defined messages about the needed source (object) files into a listing file. The #orrequires directive cannot be used alone: the #requires directive should immediately (separated with white spaces or comments only) precede it.

The directive #error always terminates the compilation and issues the user-defined error message like the following into a listing file:

C:\Tests\test\test.pro(14,10) : error c080: #error "Compilation is interrupted"

You can parse and analyze these messages and accept the required actions. For example, the VDE analyzes information printed by the #requires and #orrequires directives and automatically adds all needed PFC packages and standard libraries to the compiled project (See also the Handling Project Modules topic).

Example The directives #requires and #orrequires can be used like this:
#requires @"\Common\Sources\CommonTypes.pack"
#orrequires @"\Common\Lib\CommonTypes.lib"
#orrequires @"\Common\Obj\Foreign.obj"
#if someClass::debugLevel > 0 #then
   #requires @"\Sources\Debug\Tools.pack"
   #orrequires @"\Lib\Debug\Tools.lib"
#else
   #requires @"\Sources\Release\Tools.pack"
   #orrequires @"\Lib\Release\Tools.lib"
#endif
#orrequires "SomeLibrary.lib"
#requires "SomePackage.pack"
#if someClass::debugLevel > 0 #then
   #orrequires @"\Debug\SomePackage.lib"
#else
   #orrequires @"\Release\SomePackage.lib"
#endif
Example The #message directive can be used like this:
#message "Some text"
#if someClass::someConstant > 0 #then
   #message "someClass::someConstant > 0"
#else
   #message "someClass::someConstant <= 0"
#endif
class someClass
   #if ::compiler_version > 600 #then
       #message  "New compiler"
       constants
           someConstant = 1.
   #else
       #message "Old compiler"
       constants
           someConstant = 0.
   #endif
end class someClass
Example The #error can be used like this:
#if someClass::debugLevel > 0 #then
   #error "Debug version is not yet implemented"
#endif

Compiler options directive

Compiler directive #options <string_literal> affects the whole compilation unit. This directive should be used outside scopes and conditional compilation statements in the main source file for a compilation unit (i.e. in the source file which is passed to the compiler). Otherwise the compiler generates a warning message and ignores the directive.

The <string_literal> can only contain the following compiler options:

"/Warning"
"/Check"
"/NOCheck"
"/Optimize"
"/DEBug"
"/GOAL"
"/MAXErrors"
"/MAXWarnings"
"/profile"

Otherwise the compiler generates the error message for invalid option. If there are several #options directives they are handled in the textual order.

Conditional Compilation

The conditional programming constructions are part of the Visual Prolog language. Only other compiler directives, Compilation Units, and Program Sections (including empty) can be conditional. The following syntax is used:

ConditionalItem :
   #if Condition #then CompilationItem-list-opt ElseIfItem-list-opt ElseItem-opt #endif
ElseIfItem :
   #elseif Condition #then CompilationItem
ElseItem :
   #else CompilationItem

Here Condition can be any expression, which can be evaluated to fail or succeed during compilation time.

Each one conditional compilation statement must be in one file, that is, the compiler directives #if, #then, #elseif and #else (if present), #endif of the same level of nesting must be in one file.

During compilation the compiler evaluates the conditions, in order to determine which parts to include in the final program. Parts that are excluded from the final program are called the dead branches.

All branches of conditional compilation items are syntax checked and must be syntactically correct. That is, also the dead branches must be syntactically correct.

The compiler only calculates conditions on a need to know basis, i.e. it does not calculate conditions in dead branches.

A condition may not depend on any code, which is located textually inside the conditional statement.

The example below is illegal because the condition depends on the scope (and constant) which is declared inside the condition branch.

#if aaa::x > 7 #then % ERROR!
class aaa
    constants
        x = 3
end class aaa
#else
class aaa
    constants
        x = 23
end class aaa
#endif

Attributes

Various definitions and declarations can be annotated with attributes. This section describes the general syntax of attributes and where they can be placed. It also describes the meaning of the specific attributes.

Syntax

Attributes :
    [ Attribute-comma-sep-list ]
Attribute : one of
    LowerCaseIdentifier
    LowerCaseIdentifier ( Literal-comma-sep-list )

where the literals must either be numbers or string literals.

Insertion Points

The attributes of interfaces, classes and implementations are right after the scope qualifications.

InterfaceDeclaration :
    interface IinterfaceName
        ScopeQualifications
        Attributes-opt
    Sections
end interface IinterfaceName-opt
ClassDeclaration :
    class ClassName ConstructionType-opt
        ScopeQualifications
        Attributes-opt
    Sections
    end class ClassName-opt
ClassImplementation :
   implement ClassName
        ScopeQualifications
        Attributes-opt
    Sections
    end implement ClassName-opt

The attributes of constants, domains, predicates, properties and facts are at the end (i.e. right before the terminating dot).

ConstantDefinition: one of
    ConstantName = ConstantValue Attributes-opt
    ConstantName : TypeName = ConstantValue Attributes-opt
DomainDefinition:
    DomainName FormalTypeParameterList-opt = TypeExpression Attributes-opt
PredicateDeclaration :
    PredicateName : PredicateDomain LinkName-opt Attributes-opt
    PredicateName : PredicateDomainName LinkName-opt Attributes-opt
PropertyDeclaration :
    PropertyName : PropertyType FlowPattern-list-opt Attributes-opt
FactDeclaration :
    FactVariableDeclaration Attributes-opt
    FactFunctorDeclaration Attributes-opt

The attributes of formal arguments are at the end.

FormalArgument :
    TypeExpression ArgumentName-opt Attributes-opt

Specific Attributes

attribute

This attribute is used on a functor domain to indicate that the functors in the domain can be used as attributes elsewhere in the program.

Example
domains
    meta =
        meta;
        metaDisplayAs(string DisplayAs) [attribute].

See Program Defined Attributes.

byVal

An argument is transferred directly on the stack rather than using a pointer. Valid for formal predicate arguments provided the language is stdcall, apicall or c.

Example
domains
    point = point(integer X, integer Y).
predicates
    externalP : (point Point [byVal]) language apicall.

The attribute can also be used in combination with the out attribute:

Example
predicates
    externalP2 : (point Point [byVal, out]) language apicall.

In that case a point structure will be allocated before the call then a pointer to that structure is transferred handed to the external predicate which can then fill the structure with relevant data.

classInitializer

This attribute indicates that a predicate should be invoked as a class initializer. It can be applied to a class predicate that does not take any arguments. The predicate will be invoked when the initialization code invokes the runtime_api::runProgramInitialization. A class can have any number of class initializer which will be invoked in an undetermined order. Notice that other classes may not have been initialized.

The predicate xxx::initialize is registered as a class initializer:

implement xxx
 
class predicates
    initialize : () [classInitializer].
clauses
    initialize() :-
        …
 
end class xxx

constant

The constant attribute is used to declare fact variables that cannot be changed once they have been initialized.

See Constant fact variable.

compiletimeSetting

The compiletimeSetting attribute indicates that a constant should be considered a compiletime setting. As a result the compiler will suppress warnings about always failing/succeding code and about unreachable code that may be caused by this constant. The warning suppession is an approximation, because it a may be impossible/difficult to determine the cause of a warning.

implement xxx
 
constants
    debugOutput : boolean = false [compiletimeSetting].
 
clauses
    pppp(...) :-
        ...
        if true = debugOutput then
            % do not give a warning about unreachable code
            log::write(...)
         end if,
         ...
 
end implement xxx

default

It is problematic to update functor domains, if terms have been persisted in serialized form. Because new programs cannot deal with old serializations.

The two attributes default/1 and retiredFunctor/1 can help dealing with this problem.

The last arguments of a functor can have default values:

domains
    ppp =
        fct(
            integer A,
            real B,
            ddd C,
            integer* New [default([])],
            real New2 [default(0)]
        ).

The default attribute does not change anything within the program; it only affects the deserialization. If during deserialization we meet the closing parenthesis too soon we supply default values for the remaining arguments.

Notice that this will only work for text deserialization.

See also Functor Domain Versioning.

deprecated

The declared entity is deprecated. The string literal describes how to migrate from it. The entity still exists, but usage will cause a warning. The entity will not exist in future versions of Visual Prolog. Valid for member declarations and scopes.

Example
predicates
    oldFashioned : (string Arg) [deprecated("Use newFashion instead")].

explicitTag

This predicate can be used on a functor domain to ensure that the memory representation of all terms have a functor. Without this attribute the compiler optimizes the representation such that some alternatives doesn't have a functor in the term, and such that functors with arguments are represented as a pointer value. The main purpose of this attribute is to ensure compatibility with foreign code.

Example
domains
    menu =
        resMenu(resid Resid);
        dynMenu(menuItem* SubMenu);
        noMenu
        [explicitTag].

formatString

The argument is a format string for a subsequent ellipsis argument (i.e. ...). Valid for one string argument of a predicate with an ellipsis argument. The use of formatString will make the compiler check the validity of actual arguments with respect to actual format strings (where possible).

Example
predicates
    writef : (string Format [formatString], ...).

The format string can contain ordinary characters which are printed without modification, and format fields, that begins with the percent % sign. If the percent sign is followed by some unknown character (not the format specifier) - then this character will be printed without modifications. To output a % character you must write %% in the format string.

predicates
     writef : (string Format [formatstring], ...).

The format fields specification is:

[-][0][width][.precision][type]

All fields are optional.

[-] Hyphen indicates that the field is to be left justified; right justified is the default. Having no effect when width value is not set, or the number of characters in the actual value is greater than width value.

[0] Zero before width means for values that zeros will be added until the minimum width is reached. If 0(zero) and -(hyphen) appear, the 0 is ignored

[width] Positive decimal number specifying a minimum field size. If the number of characters in the actual value is less than width value - then the required number of space ' ' characters will be added before the value (or after it, if '-' field was set). No changes occurs if number of characters in the actual value is greater than the width value.

[.precision] The point '.' with the following unsigned decimal number can specify either the precision of a floating-point image or the maximum number of characters to be printed from a string.

[type] Specifies other format then the default for the given. For example, in the type field, you can give a specifier that says an integer will be formatted as an unsigned. The possible values are:

f Format real's in fixed-decimal notation (such as 123.4 or 0.004321). This is the default for real's.
e Format real's in exponential notation (such as 1.234e+002 or 4.321e-003).
g Format real's in the shortest of f and e format, but always in e format if exponent of the value is less than -4 or greater than or equal to the precision. Trailing zeros are truncated.
d or D Format as a signed decimal number.
u or U Format as an unsigned integer.
x or X Format as a hexadecimal number.
o or O Format as an octal number.
c Format as a char.
B Format as the Visual Prolog binary type.
R Format as a database reference number.
p Format as the presented value.
P Format as a procedure parameter.
s Format as a string.

generated

This attribute can be placed on interfaces, classes and implementation to indicate that the code is generated by some tool. As result the compiler will issue less warnings about the code.

Example
interface iSomething supports iUnknown
    [generated]
...

immediate

The attribute immediate enforces immediate (i.e. non-late) initialization of a fact variable:

Example
facts
    current : integer := initializeCurrent() [immediate].

See also Fact Variable Declarations.

in

The argument is an input argument. Valid for a formal predicate argument.

Example
predicates
    pred : (string InputArg [in]).

in_iterate

Defines an in-iterator predicate for a domain or interface. See the description of the in operator.

in_test

Defines an in-test for a domain or interface. See the description of the in operator.

inline

inline alters the memory layout of a struct (i.e. a single alternative functor domain with an align qualification). The purpose of the attribute is to ease interfacing to foreign languages and should normally not be used for pure Visual Prolog.

inline can be used in three cases:

  • inlining a struct rather than having a pointer to the struct
  • inlining a fixed size string
  • inlining a fixed number of bytes
  • inlining a prolog predicate type (as a struct with two fields)

When using inline on struct field in another struct its data will be inlined instead of having a pointer to the struct

Example
domains
    point =p(integer X, integer Y).
 
domains
    rectangle =
       r(
            point UpperLeft [inline],
            point LowerRight [inline]
        ).

Since UpperLeft and LowerRight are inlined the struct have the same memory layout as this one:

domains
    rectangle2 =
        r2(
            integer UpperLeft_X,
            integer UpperLeft_Y,
            integer LowerRight_X,
            integer LowerRight_Y
        ).


When using inline(<size>) on a string or a string8 field in a struct, the struct will contain a fixed size string with <size> characters (i.e. char or char8, respectively). The strings will be zero terminated if they are shorter than <size>, but not if they have <size> characters.

Example
domains
    device =
        device(
            integer Id,
            string DeviceName [inline(12)]
        ).

DeviceName is an inlined Unicode string of length 12. The struct have the same layout as:

domains
    device =
        device(
            integer Id,
            char DeviceName_01,
            char DeviceName_02,
            char DeviceName_03,
            char DeviceName_04,
            char DeviceName_05,
            char DeviceName_06,
            char DeviceName_07,
            char DeviceName_08,
            char DeviceName_09,
            char DeviceName_10,
            char DeviceName_11,
            char DeviceName_12
        ).

When using inline(<size>) on the pointer type the struct will contain <size> bytes, and the pointer will become a pointer to that field:

Example
domains
    mark =
        mark(
            integer Position,
            pointer Data [inline(8)]
        ).

Data is pointer to 8 inlined bytes The struct have the same layout as:

domains
    mark2 =
        mark2(
            integer Position,
            byte Data_1,
            byte Data_2,
            byte Data_3,
            byte Data_4,
            byte Data_5,
            byte Data_6,
            byte Data_7,
            byte Data_8
        ).

And Data will point to Data_1.

intrinsic

A declaration which has special meaning and handling in the compiler (semi-built-in).

mandatoryOut

Used to prevent a predicate from having optional output parameters (see Optional parameters).

Example This predicate does not have optional output paramters
predicates
    ppp : (integer X [out]) [mandatoryOut]. % The output parameter is mandatory

noDefaultConstructor

Used for a class to indicate that it should not have an implicit default constructor, and can thus be used to a class that does not have any public constructors at all. Valid for an object creating class declaration.

Example
class classWithoutPublicConstructors : myInterface
    open core
    [noDefaultConstructor]
...
end class classWithoutPublicConstructors

out

The argument is an output argument. Valid for a formal predicate argument.

Example
predicates
    pred : (string OutputArg [out]).

pack

The [pack(n)] attribute (where n is a number) instructs the compiler to use n as packing size for a functor domains. By default the packing size is 4 in 32 bit programs and 8 in 64 bit programs. This attribute is mainly intended for compatibility with C/C++ api's.

Example
domains
    packed = packed(integer8, pointer) [pack(2)].

The attribute can used on a class declaration to cover all domains in that class.

Example The domains used with the RichEdit control must all be packed with 4:
class richEdit_native
    open core, gui_native
    [pack(4)]
 
% pack all domains with packing size 4
 
end class richEdit_native

programPoint

programPoint's are used by the exception mechanism to indicate where exceptions are raised and continued, but the usage is not limited to that purpose.

The programPoint attribute is used predicate or constructor declaration to indicate that it receives an extra input argument which describes the place in a program (program point) where this predicate was called. This additional argument has programPoint type which is declared in the PFC core class like:

domains
    programPoint = programPoint(hScopeDescriptor ClassDescriptor, string PredicateName, sourceCursor Cursor).

The programPoint attribute can be added to a predicate declaration like this:

predicates
    raiseAnException : (integer X) erroneous [programPoint].

Adding this attribute actually means that two predicates are declared, the one you have mentioned and an another one with name raiseAnException_explicit which in addition to the arguments of raiseAnException takes a programPoint as first argument:

predicates
    raiseAnException : (integer X) erroneous.
 
predicates
    raiseAnException_explicit : (programPoint ProgramPoint, integer X) erroneous.

When you call raiseAnException the compiler will create a program point and call raiseAnException_explicit instead.

Example
clauses
    test() :-
        raiseAnException(17).

will actually correspond to:

clauses
    test() :-
        raiseAnException_explicit(programPoint(...), 17).
where the program point corresponds to the point where raiseAnException is called in the test predicate.

If you have a programPoint you can directly call the explicit predicate with it.

Example
clauses
    raiseAnExceptio17_explicit(ProgramPoint) :-
        raiseAnException_explicit(ProgramPoint, 17).
Typically, as in this example, explicit predicates will call other explicit predicates with the programPoint they receive in order to use an "original" call point in a nested explicit predicate.

Such code is treated in the usual way. I.e. when calling raiseAnException or raiseAnException_explicit will in both cases result in calling raiseAnException_explicit, so this is the only predicate that needs an implementation. In fact, it is illegal to state clauses for the non-explicit predicate that will never be called.

There is also a built-in predicate, programPoint/0->, which returns a programPoint corresponding to the place where it is called.

To summarize:

  • A predicate declaration with programPoint attribute actually declares two predicates. A non-explicit and an explicit predicate.
  • Calling the non-explicit predicate actually results in calling the explicit predicate with the call point as additional argument.
  • Only the explicit predicate should be implemented.

presenter

Used to specify the presenter of a domain.

Example
domains
    someDomain = ... [presenter(presenter_someDomain)].

Also used without argument to specify that an interface has a presenter.

Example
interface something [presenter]
...
end interface something

See Presenters.

queryable

Makes an entity 'queryable', so that it is available for reflextion using the class predicateExtractor.

retired

The declared entity is retired. The string literal describes how to migrate from it. The entity does not exist anymore.

Example
predicates
    veryOldFashioned : (string Arg) [retired("Use newFashion instead")].

retiredFunctor

Functor alternatives can be retired.

domains
    ppp =
        fct(integer A, real B, ddd C) [retiredFunctor(aaa::fct_ppp)];
        fct2(integer A, ddd C, integer* New).

aaa::fct_ppp must be a predicate with this type (it can be an anonymous predicate):

predicates
    fct_ppp : (integer A, real B, ddd C) -> ppp NewValue.

I.e. it takes the arguments of the old functor and returns a value in the functor domain.

In the program fct is does not exist at all, it is retired. But in the deserialization fct terms can still be handled: The arguments are parsed according to the types, and then the value is created by invoking aaa::fct_ppp.

This method will also work for binary serializations, provided:

  • The old domain had more than one alternative (so there are functor numbers in the serialization)
  • New alternatives are added last (to retain functor numbers)

It is however not recommend using binary serialization for inter-session persistence.

See also Functor Domain Versioning.

sealed

Used for an interface to indicate that it cannot be supported by any other interface. This allows to create more efficient codes, because the compiler provides some optimization when using the objects of such type. Valid for an object creating class declaration as a construction interface.

Example
interface myInterface
    [sealed]
...
end interface myInterface
 
class myClass : myInterface
...
end class myClass

this

Used for declaring extension predicates.

Example
class predicates
    extension : (unsigned V [this]).

union

Used for creating functor domains with several alternatives but no real functors. This should only be used to mimic C/C++ union structs in low-level interfacing. Valid for functor domain with several alternatives and alignment.

Example
domains
    u64var = align 4
        u64(unsigned64 Value64);
        u64_struct(unsigned Low32, unsigned High32)
        [union].

used

An unused local member can be marked used to prevent the compiler to issue a warning and remove the corresponding code. Valid for members.

Example
predicates
    seeminglyUnused : () [used].