Language Reference

Quantum Prolog is a full ISO Prolog implementation running natively on x86_64 or ARM64 machines, or in web browsers (with limitations).
Note this language reference is not an introductory text on Prolog; see any online Prolog tutorial instead.

Quantum Prolog implements the ISO Prolog language as specified in

Part 2 of the ISO Prolog specification

(the Prolog Module specification) is not implemented by Quantum Prolog, nor does Quantum Prolog implement proposed specifications for threads and globals.

For support of the ongoing effort to standardize Definite Clause Grammars (DCGs) according to

(any version or most other third-party DCG expansion library), see Using the initialization directive for DCG expansion.

Except as stated otherwise, Quantum Prolog implements ISO Prolog as described in the above specifications. This language reference and the accompanying library reference details implementation-specific choices and limitations in reference to the above specifications.

Limits

Processor character set

ISO 10646 (Unicode) Basic Multilingual Plane with UTF-8 encoding

Integer rounding function

down

Smallest integer

-2,147,483,648 (the minimum for a signed 32-bit integer)

Largest integer

2,147,483,647 (the maximum for a signed 32-bit integer)

Floating point numbers

range and precision as representable by IEEE 754 64-bit binary floating point values

Maximum arity of compound terms

63

Numbers

Apart from regular decimal integers and IEE 754 floating point values, Quantum Prolog recognizes the following forms of character code constants:

0'\n, 0'\t, 0'\r, 0'\b, 0'\f, representing the numbers 10, 0, 13, 8, and 12, respectively

'' ' representing 32, the character code for space

''' representing 39, the charactor code for a single quote (U+0027 APOSTROPHE)

0'x representing any character code for a character x in the processor character set

0oNNNN... with up to 10 N digits representing an integer in octal notation

0xNNNN... with up to 8 N digits representing the integer in hexadecimal notation

0bNNNN... with up to 32 N digits representing the integer in binary notation

Notably, uXX syntax for ISO 10644 (Unicode) code points is not supported Non-ISO extension

Language-Independent Arithmetic

While numbers are represented in accordance with IEEE 754, arithmetic is carried out with respect to ISO/IEC 10967 Language Independent Arithmetic (LIA). LIA, as used in ISO 13211, since ISO Prolog lacks lexical representations for exceptional values (NaN, +Inf, and +Inf) essentially requires that exceptional values are notified by exceptions.

In particular, exceptions are reported with the following terms:

Integer overflow errors are reported as evaluation_error(int_overflow).

Zero devision errors are reported as evaluation_error(zero_divisor).

Floating point or mixed arithmetic operations carried out in accordance with IEEE 754 resulting in NaN are reported via evaluation_error(undefined).

Those resulting in infinities (-Inf or +Inf) are reported via evaluation_error(float_overflow).

Those resulting in subnormal values (other than +0.0d) are reported via evaluation_error(underflow).

As a clarification to ISO/IEC 13211 (2012) TC 2, in exponentiation of integer base and exponents, if the base isn't 1 and the exponent is less than -1, evaluation_error(undefined) is reported.

Directives

:- dynamic(Predicate/Arity)

allows a predicate to have dynamic clauses to be added (via assert/2) or removed (via retract/2), or have its definition removed enitrely via abolish/1

note ISO Prolog requires that a dynamic/2 directive is present in every file containing clauses for the predicate having the respective Predicate/Arity predicate specifier, but this isn't enforced by Quantum Prolog

:- discontiguous(Predicate/Arity)

allows a predicate to have clauses that appear non-consecutive in Prolog source text files

by default, Prolog requires multiple clauses for the same predicate in Prolog source text to follow one after another, with no clauses for other predicates in between

:- multifile(Predicate/Arity)

allows a predicate to have clauses in more than a single Prolog text file

by default (if no multifile/1 directive is placed on a predicate), all clauses for a predicate must reside in the same file; this is useful for ensuring that names of predicates used in a file aren't inadvertently used elsewhere in Prolog text files, potentially extending or otherwise altering solutions for the predicate

however, when multifile/1 is defined for a predicate identifier, queries against the respective predicates are satisfied by collecting all clauses
for the predicate in all Prolog source files

note ISO Prolog requires that a multifile/2 directive is present in every file containing clauses for the predicate having the respective Predicate/Arity predicate specifier, but this isn't enforced by Quantum Prolog

:- set_prolog_flag(debug, on|off)

switches on or off 4-port goal debugging

:- set_prolog_flag(unknown, error|warning|fail)

sets action to perform on an attempt to invoke a callable that isn't defined

error (the default) raises a existence_error(Atom/Arity) exception

warning prints a warning, and cause the invocation to fail fail silently fails an attempt to call an undefined procedure

note that a predicate can be defined, yet have no clauses (for example, by being defined in a dynamic/2 directive); if a predicate has no clauses, or has all its clauses retracted via retract/2, then the unknwon action is not performed; rather, the goal fails instead

:- ensure_loaded(Filename_atom)

loads the specified file name as Prolog text as if it were syntactically part of the Prolog text file being processed at the place where the ensure_loaded/1 occurs

however, if the filename to load was already loaded in an earlier ensure_loaded/1 directive, then the directive has no effect

note third-party Prolog implementations may make use of special term notations such as library('filename') for expressing filenames, but Quantum Prolog does not support such syntax and requires Filename_atom to be an atom, the naem of which is interpreted as filename and resolved relative to the current working directory

:- initialization(callable)

specifies a callable to be invoked once the Prolog source file containing the directive is completely loaded

note the callable invoked must be defined in the file containing the initialization/1 directive, or any file loaded from it via ensure_loaded/1

note Quantum Prolog supports at most one initialization/1 directive per Prolog source file; if more than a single goal must be invoked for initialization, these goals can be placed into a compound goal, so there's no loss of expressivity/generality

:- index(Predicate/Arity, ArgumentNumber) Non-ISO extension

specifies which argument to index for predicate Predicate with Arity in addition to the standard first-argument index maintained by Quantum Prolog, or switches off term indexing alltogether

by default, or if :- index(somePredicate/someArity, 1) is specified, Quantum Prolog indexes the first argument of the respective predicate, provided all its clauses contain atoms in the first argument position

if :- index(somePredicate/someArity, 2) is specified, an additional index will be maintained on the 2nd argument, and likewise for all other argument numbers > 1, respectively

an additional index is only maintained if all clauses of the respective predicate are presented as syntactical facts, and (like with default indexing), only if all arguments at the position to be indexed are atoms; note that, OTOH, default first-argument indexing indexes both syntactical facts and rules

:- index(somePredicate/someArity, 0) disables any index on the respective predicate

there must be at most one index/2 directive specified for a given predicate

indexes can be placed on both static and dynamic predicates

Note an include/1 directive is not supported.

Note Quantum Prolog doesn't support directives with list or multiple args for applying the dynamic/1, multifile/1, or discontiguous/1 directive to more than a single predicate identifier. Instead, multiple directive, each for a single predicate, must be used.

Portability notes on using non-standard directives

Many existing Prolog code bases and third-party Prolog implementations make use of and allow arbitrary callable terms to appear in top-level ':-'/1 clauses as custom directives in either top-level Prolog code text, or code text loaded via a historic consult/1 directive/predicate (that isn't part of ISO Prolog). For example, assuming one or more clauses for a predicate my_directive/3 are part of the database, it's common to immediately call into a predicate during loading Prolog text containing

:- my_directive(x, y, z).

Gratuitious use of custom directive makes Prolog become procedural and script-like in nature. For example, Prolog code such as the following isn't uncommon:

:- if(in_metadata_section).
:- do_this.
:- else.
:- do_that.

While Quantum Prolog rejects usage of non-standard directives in top-level Prolog code text, or in code text loaded via the ensure_loaded/1 directive, customized loading and executing custom directives can be easily implemented using Prolog itself, such as in the following consult/1 implementation:

% implementation of consult/1: read all terms, call
% into "directive-like" terms (= those having ':-'/1
% as principal functor) immediately, and assertz/1 others
consult(File) :-
	open(File, read, Stream),
	repeat,
		read(Stream, Term),
		(Term = end_of_file ->
			close(Stream), !;
			(Term = ':-'(Body) ->
				call(Body);
				assertz(Term)),
			fail).

Using the initialization/1 directive for DCG expansion

Quantum Prolog supports automatic translation of definite clause grammar rules into Prolog clauses such as the one provided via dcgs_expand.pl, the reference implementation for ISO DCGs according to ISO/IEC 13211-3:2006 (2014) Definite clause grammar rules, or alternative Prolog programs for DCG term expansion.

Unlike most third-party Prolog implementations having a fixed built-in package for DCG translation triggered via DEC-10 Prolog-like expand_term/2 or similar mechanisms not part of ISO Prolog, Quantum Prolog uses the initialization/1 directve hook into the Prolog runtime and other standard directives and predicates to perform automatic term expansion upon loading DCG rules.

For simplicity, the following example code demonstrates using Clocksin & Mellish's self-contained DCG translation variant (stored in dctg_trans.pl) for parsing a traditional simplistic English grammar example (also from Clocksin & Mellish). Upon initialization, all grammar rules (that is, terms having --> as principal functor) are queried, and each rule is converted to the regular clause implementing it using the translate/2 predicate, and then appended to the database using assertz/1:

% file boy-eats-apple-example.dcg %

:- ensure_loaded('dcgs_trans.pl').
:- initialization(
 ( clause( (DCG_head --> DCG_body), _),
   translate( (DCG_head --> DCG_body),
     (Clause_head :- Clause_body) ),
   assertz( (Clause_head :- Clause_body) ) ) ).

sentence --> sentence(X).

sentence(X) --> nominalphrase(X), verbalphrase(X).

nominalphrase(X) --> determiner(X), noun(X).

verbalphrase(X) --> verb(X).
verbalphrase(X) --> verb(X), nominalphrase(Y).

noun(singular) --> [boy].
noun(plural) --> [boys].

determiner(_) --> [the].

verb(singular) --> [eats].
verb(plural) --> [eat].



% main program %

:- ensure_loaded('boy-eats-apple-example.dcg')

?- sentence([the,boy,eats,the,apple],Z)

Likewise, to use ISO DCGs instead:

% girl-likes-boy-example.pl %
 
:- ensure_loaded('prologue.pl').
:- ensure_loaded('dcgs_trans.pl').
:- initialization(
 ( clause( (DCG_head --> DCG_body), _),
   dcg_rule( (DCG_head --> DCG_body),
     (Clause_head :- Clause_body) ),
   assertz( (Clause_head :- Clause_body) ) ) ).

determiner --> [the].
determiner --> [a].
noun --> [boy].
noun --> [girl].
verb --> [likes].
verb --> [scares].
noun_phrase --> determiner, noun.
noun_phrase --> noun.
verb_phrase --> verb.
verb_phrase --> verb, noun_phrase.
sentence --> noun_phrase, verb_phrase.



% main program (using ISO DCGs) %

:- ensure_loaded('girl-likes-boy-example.dcg').

% the common definition for phrase/2
% (which isn't defined in ISO/IEC 12211-3:2006)
phrase(P, L) :- Goal =.. [P, L, R], R = [], call(Goal).

?- sentence([the, girl, likes, the, boy], Z)

where prologue.pl is defined as in ISO/IEC JTC1 SC22 WG17 N235 A Prologue for Prolog and is supposed to provide the common append/3 procedure.

Vardb feature extension Non-ISO extension Experimental

?-(DB, Callable)

Description

Quantum Prolog's vardb feature is a principled extension to ISO Prolog introducing an '?-'/2 operator and predicate as a callable term, but not otherwise introducing new Prolog syntax.

'?-'/2 can be used, among other things

For example, the following Prolog goal

call( (p(a). p(b).) ?- p(X) )

evaluates to

X=a;
X=b

Limitations

Until implementation concerns are more fully understood and feedback from the Prolog community is received, the vardb feature is deliberately introduced with these limitations for forward-compatibility of vardb- programs with possible further extensions:

Parallel extension Non-ISO extension Experimental

maplist(Callable, FirstArgs, SecondArgs, ...)

maplist/N, for N >= 1, calls the Callable arg with arguments taken from the FirstArgs, SecondArgs, ... lists, potentially extending it with additional args using call/N semantics.

The second and subsequent arguments to maplist/N, if any, must be either lists or variables. At least one argument must be a list. Multiple list arguments must be equal in size.

An argument given as a variable is instantiated to a list of fresh variables before invoking Callable.

Callable is called with as many concurrent invocations as physical hardware threads are available on the system, provided the argument list size is larger than one. If the argument list size is larger than the number of available hardware threads, Quantum Prolog keeps invoking new executions as threads complete Callable evaluations, keeping the number of concurrent executions equal to, but never larger than, the number of hardware threads at all times.

Limitations

Note that maplist/N, as a concurrent variant of the common maplist/N predicate, can't implement any of the uses requiring individual calls to Callable to be performed in any particular order, and to meaningfully share bound variables. In fact, the order in which individual calls to Callable are performed is undefined.