Library Reference

This is a reference for the built-in predicates supported by Quantum Prolog. Since Quantum Prolog implements ISO/IEC 13211-1, this library reference is thus almost entirely an ISO Prolog predicate library reference, except where noted otherwise.
Note this library reference is not an introduction to Prolog; see Planning container shipping using Prolog instead.

Clause insertion, removal, and retrieval

asserta(+Clause)

Adds a new rule or fact to the database. The added rule or fact will appear to subsequent queries as if it were inserted before all existing facts and rules for the predicate of the respective arity in Prolog code text source order.

Only dynamic predicates can be inserted. Dynamic predicates are those declared dynamic explicitly via the dynamic/1 directive, or those that don't have clauses parsed from static Prolog code text at all but may have clauses inserted via prior asserta/1 or assertz/1 invocations in which case they will be declared dynamic implicitly.

Attempting to insert or otherwise modify clauses for control constructs or built-ins interpreted by Prolog at the top-level is rejected as permission error (see below).

Exceptions

instantiation_error

thrown on an attempt to call asserta/1 with a variable as argument

type_error(callable, null)

thrown on an attempt to call asserta/1 with an argument that neither unifies with Head :- Body nor with a valid clause head

permission_error(modify, static_procedure, PredicateSpecification)

thrown on an attempt to assert new clauses for a built-in or static procedure

ISO/IEC 13211 portability note

Note a term with principal functor ':-'/2 can only fail to unify with Head :- Body if either Head or Body, or both, are missing or if it has arity > 2. Hence, the second argument in the exception term type_error(callable, X) can not contain meaningful information (it is either a valid Head, in which case inclusion of Head in the exception term is irrelevant since Body is what's in error, or is null which could apply to either Head or Body). For this reason, Quantum Prolog always reports null as second argument of the exception term.

assertz(+Clause)

Adds a new rule or fact to the database. The added rule or fact will appear to subsequent queries as if it were appended after all existing facts and rules for the predicate of the respective arity in Prolog code text source order.

Only dynamic predicates can be inserted. Dynamic predicates are those declared dynamic explicitly via the dynamic/1 directive, or those that don't have clauses parsed from static Prolog code text at all but may have clauses inserted via prior asserta/1 or assertz/1 invocations in which case they will be declared dynamic implicitly.

Attempting to insert or otherwise modify clauses for control constructs or built-ins interpreted by Prolog at the top-level is rejected as permission error (see below).

Exceptions

instantiation_error

thrown on an attempt to call assertz/1 with a variable as argument

type_error(callable, null)

thrown on an attempt to call assertz/1 with an argument that neither unifies with Head :- Body nor with a valid clause head

permission_error(modify, static_procedure, PredicateSpecification)

thrown on an attempt to assert new clauses for a built-in or static procedure

ISO/IEC 13211 portability note

Note a term with principal functor ':-'/2 can only fail to unify with Head :- Body if either Head or Body, or both, are missing or if it has arity > 2. Hence, the second argument in the exception term type_error(callable, X) can not contain meaningful information (it is either a valid Head, in which case inclusion of Head in the exception term is irrelevant since Body is what's in error, or is null which could apply to either Head or Body). For this reason, Quantum Prolog always reports null as second argument of the exception term.

retract(+Term)

Succeeds while removing a single rule or fact from the database. On backtracking, additional rules or facts can be removed. The argument term is unified with the removed rule's or fact's definition. Fails if no clause having an unifying head can be retrieved.

retract/1 takes a single argument term interpreted as either a clause head (if it has a principal predicate other than ':-'/2), or a complete clause-like term Head :- Body (if it has principal functor ':-'/2). In the latter case, the argument term is matched against a complete stored clause with clause body, whereas in the former case, it is unified against the head of stored clause only. As a special rule, clause arguments taking the form Head :- true match both clauses with true as body, and clauses with an empty body (facts).

Note if using the Head :- Body argument form in Prolog code text, if Body contains syntactical conjuncts separated by commas (as non-trivial bodies tend to), the argument must be enclosed in grouping parentheses to ensure intended parsing. In the following example, the parentheses around the clause to retract are required:

retract( (p(X, Y) :- X = a, Y = b) )

Exceptions

instantiation_error

thrown on an attempt to call retract/1 with a variable as argument

type_error(callable, null)

thrown on an attempt to call retract/1 with an argument that neither unifies with Head :- Body nor with a valid clause head

permission_error(modify, static_procedure, PredicateSpecification)

thrown on an attempt to retract a built-in or static procedure

ISO/IEC 13211 portability note

Note a term with principal functor ':-'/2 can only fail to unify with Head :- Body if either Head or Body, or both, are missing or if it has arity > 2. Hence, the second argument in the exception term type_error(callable, X) can not contain meaningful information (it is either a valid Head, in which case inclusion of Head in the exception term is irrelevant since Body is what's in error, or is null which could apply to either Head or Body). For this reason, Quantum Prolog always reports null as second argument of the exception term.

retractall(+head)

Succeeds as all clauses having clause heads unifying with head are retracted. Note, unlike retract/1, retractall/1 does not support the variant where the argument is interpreted as full Head :- Body clause. retractall/1 doesn't bind variables.

retractall/2 behaves as if it were defined as follows:

retractall(Head) :-
retretract((Head :- _)),
	fail.
retractall(_).

Exceptions

instantiation_error

thrown on an attempt to call retractall/1 with a variable as argument

type_error(callable, null)

thrown on an attempt to call retractall/1 with an argument term having principal functor ':-'/{1,2}, or a term that doesn't represent a valid clause head

permission_error(modify, static_procedure, PredicateSpecification)

thrown on an attempt to retract a built-in or static procedure

abolish(@predicate_indicator)

Succeeds and retracts every clause matching the given predicate indicator of the form Predicate/Arity, also removing the predicate's definition.

Unlike retractall/2 which can only retract clauses, abolish/1 not only removes all clauses, but erases the definition of the predicate with the given arity from Prolog runtime info such that it won't be reported in subsequent invocations of current_predicate/1.

Exceptions

instantiation_error

thrown on an attempt to call retract/1 with either a variable as argument, or

with a term Predicate/Arity as argument, where either Predicate or Arity, or both, are variable

type_error(predicate_indicator, PredicateSpecification)

thrown if the principal predicate of predicate_indicator isn't '/'/2, or

if it is '/'/2 but Arity is neither a number nor variable

type_error(atom, Pred)

thrown if the Pred argument in predicate_indicator is neither variable nor an atom

domain_error(not_less_than_zero, Arity)

thrown if the Arity argument in predicate_indicator represents a negative integer

permission_error(modify, static_procedure, atom/N)

thrown on an attempt to retract a built-in or static procedure

clause(+head, ?callable_term)

Succeeds backtracking over all clauses currently in the database that unify with the argument head as head and callable_term as body. If callable_term is true, then facts (clauses with an empty body) are also matched.

Exceptions

instantiation_error

thrown if head is variable

type_error(callable, Head)

thrown if head is neither variable nor a callable term

type_error(callable, Callable_term)

thrown if callable_term is neither variable nor a callable term

permission_error(access, private_procedure, Predicate)

thrown on an attempt to list clauses for a built-in predicate, where Predicate is the predicate specifier for the built-in predicate

current_predicate(?predicate_indicator)

Unifies the argument predicator_indicator with current user-defined predicates in the database, backtracking over multiple predicate indicators.

Note current_predicate/1 iterates over distinct predicates (pairs of predicate names and arity) in the database, rather than clauses for a given predicate. If all clauses for a predicate/arity combination have been removed from the database using retract/1, the predicate's definition is still contained in the database. Once a predicate has been dynamically created, only abolish/1 can remove its definition such that it isn't reported by current_predicate/1.

Exceptions

type_error(predicate_indicator, Predicate_indicator)

thrown if Predicate_indicator isn't a valid predicate indicator of the form predicate/arity

that is, thrown if Predicate_indicator is neither a variable, nor a term with principal functor '/'/2 that has variables as arguments or that has an atom name as first argument and a number as second argument, or that has a number as second argument that is less than 0 or greater than 63 (the maximum arity allowed)

note these error conditions are reported by more granular exceptions in other builtins

current_op(?integer, ?operator_specifier, ?atom)

Backtracks over all currently defined operators matching/unifying with the given integer priority, operator_specifier operator specifier (such as xfy), and atom name/token.

Exceptions

domain_error(operator_priority, ?Integer)

thrown if the integer argument is neither variable nor a priority value

domain_error(operator_specifier, ?Operator_specifier)

thrown if the operator_specifier argument is neither variable nor an operator specifier

type_error(atom, Atom)

thrown if the atom argument is neither variable nor an atom

Multiple solution predicates

findall(+template, +goal, ?instances)

Queries all solutions to a goal and reports resolved variable bindings as a list of expanded template term.

findall/3 executes call(Goal), X = Template (where X is a fresh variable neither in Goal nor Template) and reports all values bound to X in the Instances list. If no variable is bound, then Instances contains an anonymous variable for the respective goal execution.

findall/3 reports an empty list in Instances if no solutions can be found.

findall/3 fails if Instances doesn't unify with the retrieved list of solutions.

Exceptions

instantiation_error

thrown on an attempt to call findall/3 with a variable as Goal

type_error(callable, Goal)

thrown if Goal is neither variable nor a callable goal

type_error(callable, Instances)

thrown if Instances is neither variable nor a list or partial list

bagof(+template, +goal, ?instances)

Queries all solutions to a goal and binds requested result variables into a list, while also backtracking over result lists for the different values bound by the goal to the free variables that aren't requested to be collected into the list.

bagof/3 collects solutions for goal into a list instances of values for template, a term containing variables appearing in goal. Variables in goal not contained in template (free variables) are used to group returned bindings to variables appearing in template.

bagof/3 groups and orders results reported in Instances according to free variables (that aren't existentially quantified) such that the order of results of bagof/3 doesn't necessarily reflect Prolog goal execution order. The order of results reported for a given set of free variables in Instances, however, preserve Prolog execution order.

Variables appearing in Goal to the left or as first argument of one or more '^'/2 operators (such as in bagof(Z, X ^ goal(X, Y, Z), L)) will be treated as existentially quantified and not reported in L, nor serve to group overall bagof/3 solutions.

bagof/3 (unlike findall/3) fails if no solutions at all can be found.

bagof/3 only reports solutions if Instances unifies with the retrieved list of solutions for a given set of free variables.

Exceptions

instantiation_error

thrown on an attempt to call bagof/3 with a variable as Goal

type_error(callable, Goal)

thrown if Goal is neither variable nor a callable goal

type_error(callable, Instances)

thrown if Instances is neither variable nor a list or partial list

setof(+template, +goal, ?instances)

Queries all solutions to a goal and binds requested result variables into a list, while also backtracking over result lists for the different values bound by the goal to the free variables that aren't requested to be collected into the list.

Unlike bagof/3, setof/3 reports unique values in Instances, whereas bagof/3 repeats multiple occurences of value combinations in Instances.

setof/3 collects unique solutions for goal into a list Instances of values for template, a term containing variables appearing in goal. Variables in goal not contained in template (free variables) are used to group returned bindings to variables appearing in template.

Variables appearing in Goal to the left or as first argument of one or more '^'/2 operators (such as in setof(Z, X ^ goal(X, Y, Z), L)) will be treated as existentially quantified and not reported in L, nor serve to group overall setof/3 solutions.

setof/3 groups, orders, and makes unique results reported in Instances according to free variables (that aren't existentially quantified) such that the order of results of setof/3 doesn't necessarily reflect Prolog goal execution order.

setof/3 (unlike findall/3) fails if no solutions at all could be found.

setof/3 only reports solutions if Instances unifies with the retrieved list of solutions for a given set of free variables.

Exceptions

instantiation_error

thrown on an attempt to call setof/3 with a variable as Goal

type_error(callable, Goal)

thrown if Goal is neither variable nor a callable goal

type_error(callable, Instances)

thrown if Instances is neither variable nor a list or partial list

Core I/O No web support

open(@source_sink, @io_mode, -descriptor, @stream_options)

Opens a file according to the specified arguments as follows:

@source_sink

specifies the name of the file to open, as an atom

@io_mode

specifies the mode in which to open

valid modes are read, write, or append, as atoms

-descriptor

specifies a variable used to bind a (POSIX-like) file descriptor number to, which can be used to reference the opened file in subsequent file operations

@stream_options

specifies a list of stream options; the following options are recognized:

type(text) specifies that the file should be opened in text mode

type(binary) specifies that the file should be opened in binary mode,

reposition(true) specifies that the stream's current read or write position should by repositionable using set_stream_position/2

reposition(false) specifies that the current file read or write position shouldn't be repositionable

eof_action(error) specifies that an attempt to read past the end of the stream shall cause a permission_error to be thrown

eof_action(eof_code) specifies that an attempt to read past the end of the stream is presented by an end-of-file character being returned in response to read procedures

eof_action(reset) specifies that the stream should be treated as having no concept of being "past the end", and shouldn't have an end-of-file condition reported; rather, the stream continues to be readable at all times, and an attempt to read from it will block until new input data is available

the respective option values for type, reposition, and eof_action are mutually exclusive

furthermore, the reposition(true) stream option and append mode are incompatble, and their use in combination is reported as domain_error(stream_option, Option) Non-ISO extension

furthermore, the reposition(true) stream option is incompatible with the type(text) stream option, and their use in combination is reported as domain_error(stream_option, Option) exception Non-ISO extension

Quantum Prolog doesn't support the alias(X) option in stream properties Non-ISO restriction

Exceptions

instantiation_error

thrown if one of the Source_sink or Mode arguments is variable

type_error(atom, Option)

thrown if stream_options isn't a list

type_error(variable, Descriptor)

thrown if the Descriptor argument isn't variable

type_error(atom, Mode)

thrown if the io_mode argument isn't an atom

domain_error(io_mode, Mode)

thrown on an invalid value for io_mode

domain_error(stream_option, Option)

thrown on invalid combination of stream optinons, as explained above

existence_error(open, SourceSink)

thrown if a file to open in read mode doesn't exist

permission_error(opem, SourceSink/Filename)

thrown if access in the resuested mode to a file isn't permitted

system_error(Message)

thrown on system I/O errors

ISO/IEC 13211-1 portability note

Note stream-terms in Quantum Prolog are atoms, in violation of ISO 13211-1 section 7.10.2.1. However, that requirement is provided only to ensure stream-terms are distinguishable from aliases (see footnote on page 55), and Quantum Prolog doesn't support aliases other than user_input and user_output anyway.

open(@source_sink, @io_mode, -stream)

open(Source_sink, Io_mode, Stream) is equivalent to

open(Source_sink, Io_mode, Strema,
	[ type(text), eof_action(eof_code) ])

Portability note: ISO/IEC 31211-1 doesn't mandate particular default stream options; the default stream options used by Quantum Prolog might not be portable to other systems.

close(@stream_or_alias, @close_options)

Closes a stream previously opened using open/4 or open/3.

If the stream to close is the current input stream, the current input stream is reset to user_input on completion.

If the stream to close is the current output stream, the current output stream is reset to user_output on completion.

@stream_or_alias

specifies the stream to close; this is a value previously obtained via open/3, open/4, current_input/1, or current_output/1

attempting to close the user_input or user_output stream (as the only supported aliases by Quantum Prolog) has no effect

@close_options

specifies a list of atoms representing close-options; only a single close-option is recognized:

force(false)

specifies that closing the stream should be performed normally

force(true)

specifies that after closing, the stream is guaranteed to be closed and no longer accessible, even in the presence of I/O errors; when an output stream is closed with force(true), no guarantee is made with respect to whether outstanding write operations have been carried out on disk or other stable storage, unless flush_output/0 or flush_output/1 had been called before on the respective stream

Exceptions

instantiation_error

thrown if @stream_or_alias is variable, or

thrown if close_options is variable or partial list

domain_error(stream_or_alias, Stream_or_alias)

thrown if stream_or_alias is something other than a descriptor of the form obtained via current_output/2

type_error(list, Close_options)

thrown if @close_options is neither variable nor a list

domain_error(close_option, Option)

thrown if an element (bound to Option in the exception term) of @close_options isn't recognized

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

current_input(?stream)

Retrieves or checks the descriptor term for the stream opened for current input.

Succeeds or fails depending on whether the argument unifies with the term descriptor for the current input stream,

Exceptions

domain_error(stream, Stream)

thrown if ?stream is neither variable nor a stream term as obtained by open/4

current_output(?stream)

Retrieves or checks the descriptor term for the stream opened for current output.

Succeeds or fails depending on whether the argument unifies with the term descriptor for the current output stream,

set_input(@stream_or_alias)

Sets the current input stream.

@stream_or_alias

specifies a stream to set as current input, as a stream term previously obtained via open/3, open/4, or current_input/1, or as the alias user_input to reset the current input stream to its initial default

Exceptions

instantiation_error

thrown if stream_or_alias is variable,

domain_error(stream_or_alias, Stream_or_alias)

thrown if ?Stream_or_alias is neither variable nor a stream term

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a read stream

set_output(@stream_or_alias)

Sets the current output stream.

@stream_or_alias

specifies a stream to set as current output, as a stream term previously obtained via open/3, open/4, or current_input/1, or as the alias user_output to reset the current output stream to its initial default

Exceptions

instantiation_error

thrown if @stream_or_alias is variable,

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream term

existence_error(stream, Stream_or_alias)

thrown if stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(output, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a write or append stream

flush_output(@stream_or_alias)

Succeeds while flushing outstanding I/O write operations for an output stream.

Exceptions

instantiation_error

thrown if @stream_or_alias is variable,

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term or stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(output, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to an output stream

flush_output

flush_output is equivalent to

current_output(S),
flush_output(S)

Term I/O No web support

write_term(@stream_or_alias, @term, @write_options)

Writes terms to a stream.

@stream_or_alias

specifies the stream to write to; this is a value previously obtained via open/3, open/4, or current_output/1, or the atom current_output

@term

the term to write

@write_options

list of write-options with the recognized elements listed in the following sections; by default, all options have value false, which means that terms will be printed in a casual way without quoting, and in operator notation if applicable

ignore_ops(false) or ignore_ops(true)

by default, or if ignore_ops(false) is specified, terms will be written in operator syntax for functors in term and every subterm of term having operator priorities and associativity defined, and their use in the respective term fits their defined fixity and arity (ie. have at at most 2 arguments/operands)

otherwise, or if ignore_ops(true) is among the list of write-options, terms are written in functional/canonical syntax; canonical syntax is primarily useful for unambiguosly serializing terms in a way that can be read-in by any Prolog system even in the presence of operator priority and associativity customization

ignore_ops(false) is useful for obtaining readable terms in operator syntax that reflect operator priorities and associativity at the time of serialization, thus must not be changed for reading-in serialized terms

quoted(false) or quoted(true)

by default, or if quoted(false) is specified, single-quote characters around atom names and double-quote characters around strings aren't written, even if required they were required for re-parsing; moreover, control characters in atom names and strings (such as newline characters and tabs) aren't escaped

otherwise (if quoted(true) is specified), atoms that need single-quotes to be unambigously parsed will be serialized with single-quote characters, double-quoted strings will be properly delimited, and control characters in single-quoted atoms and strings will be escaped

quoted(false) is primarily useful for printing user messages using write_term/3, while quoted(true) is useful for obtaining term serializations that can be read-in again using read_term/3

numbervars(false) or numbervars(true)

numbervars(true) is an option to print terms of the form '$VAR(n)' (where n is an integer) as variables Ij where I is a letter and j is a number, assigned used consistently for multiple occurences of the repsective variable number n across the term to write

note numbervars(true) is provided for ISO/IEC 13211-1 compatibility, but isn't of much use with Quantum Prolog

Exceptions

instantiation_error

thrown if @stream_or_alias is variable, or

thrown if Write_options is variable or partial list

domain_error(stream_or_alias, Stream_or_alias)

thrown if stream_or_alias is something other than a descriptor of the form obtained via current_output/2

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(output, binary_stream, Stream_or_alias)

thrown if @stream_or_alias refers to a binary or repositionable stream (when it must be a character stream)

permission_error(output, stream, Stream_or_alias)

thrown if @stream_or_alias refers to an input stream (when it must be an output stream)

domain_error(list, Write_options)

thrown if Write_options is neither a list nor variable

domain_error(write_option, Write_Options_Elmt)

thrown if Write_options contains an element that doesn't represent one of the above-stated recognized ISO/IEC 13211-1 write-option list elements

system_error(Message)

thrown on I/O errors

write_term(@term, -stream)

write_term(Term, Stream) is equivalent to

current_output(Stream),
write_term(Stream, Term, Stream)

write(@term, -stream)

write(Term, Stream) is equivalent to

write_term(Stream, Term, [ numbervars(true) ])

write(@term)

write(Term) is equivalent to

current_output(Stream),
write_term(Stream, Term, [ numbervars(true) ])

writeq(@term, -stream)

writeq(Term, Stream) is equivalent to

writeq_term(Stream, Term, [ quoted(true), numbervars(true) ])

writeq(@term)

writeq(Term) is equivalent to

current_output(Stream),
writeq_term(Stream, Term, [ quoted(true), numbervars(true) ])

write_canonical(@term, -stream)

write_canonical(Term, Stream) is equivalent to

write_canonical_term(Stream, Term, [ quoted(true), ignore_ops(true) ])

write_canonical(@term)

write_canonical(Term) is equivalent to

current_output(Stream),
write_canonical_term(Stream, Term, [ quoted(true), ignore_ops(true) ])

read_term(@stream_or_alias, ?term, +read_options)

Reads a term ending in a dot (.) character from a stream, reading further terms on backtracking, and failing if no (more) terms can be read at the end of the stream.

The term is parsed according to the operator priorities, fixities, and associativies currently in effect at the time of invocation.

If the stream to read is opened using the eof_action(eof_code) stream-option, at the end of the stream, or if only whitespace or Prolog source comments can be read from the stream until its end, the term end_of_file is bound to or unified with the Term argument. end_of_file is only reported on initial execution of read_term/4, but not on backtracking. end_of_file continues to be reported on new initial executions of read_term/4 if the end of stream has been reached for the respective stream.

Terms to read must be ended by dot characters followed by layout characters (whitespace characters or Prolog source comments), unless at the end of the stream to read.

@stream_or_alias

specifies the stream to read; this is a value previously obtained via open/5, open/3, current_input/1, or the atom current_output.

?term

is unified with the read term

+read_options

list of read-options with the recognized elements listed in the following sections; by default, all options have value false

variables(List)

the list List is unified with the list of variables in the unification of Term with the read-in term, listed as they occur in Term from left to right, without duplicates, including anonymous variables

variableNames(List)

the list List is unified with the list of terms containing, for each non-anonymous variable in the unification of term with the read-in term, an element V = N where V is a variable and N is an atom constructed from the characters making up the name of V

singletons(List)

like variableNames(List), but containing only elements for variables that occur exactly once in term

Exceptions

instantiation_error

thrown if @stream_or_alias is variable, or

thrown if read_options is variable or a partial list

domain_error(stream_or_alias, Stream_or_alias)

thrown if stream_or_alias is something other than a descriptor of the form obtained via open/4, open/3 or current_output/2, or the atom current_output

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, binary_stream, Stream_or_alias)

thrown if @stream_or_alias refers to a binary or repositionable stream (when it must be a character stream)

permission_error(input, stream, Stream_or_alias)

thrown if @stream_or_alias refers to an output stream (when it must be an input stream)

domain_error(list, read_options)

thrown if Read_options is neither a list nor variable

system_error(Message)

thrown on I/O errors

syntax_error(Message)

thrown if a sequence of characters was read that doesn't represent a syntactically valid term, or

thrown if a stream is opened with eof_action(error) and the end of the stream is encountered before reading a valid term, including when the stream is in the end-of-stream condition at invocation time

thrown only on initial execution of read_term/4 but not on backtracking

Portability Notes

Implementations of the ISO/IEC 13211-1 read_term/4 builtin differ accross major third-party Prolog systems in how end-of-stream conditions are handled and reported. For example, SICStus Prolog simply fails if a stream is read to exhaustion via backtracking, whereas SWI Prolog throws a syntax error exception instead.

The ISO/IEC 13211-1 read-option eof_action(...) supposed to unify end-of-stream handling across Prolog implementations is honored by SICStus Prolog and SWI Prolog only on initial entry, but not if an end-of-stream condition is reached via backtracking over read_term/4 and its variants.

The read-option eof_action(error), even when not relying on backtracking and instead always calling into read_term/4 as freshly instantiated goal, leaves details for the exception thrown on end of a stream as opposed to exception(s) thrown on syntax errors implementation-defined, hence control flow via exceptions can't be used to implement portable Prolog programs.

The recommended best practice for creating portable Prolog code across Quantum Prolog and the aforementioned third-party Prolog implementations is to open streams using eof_action(eof_code) as read-option, and then rely on Prolog reporting the end_of_file atom (when initially called as goal, but not on backtracking):

% best practice for portably reading all terms from
% a file, collecting the read terms into a list

call_read_term(S, X) :-
read_term(S, X, []), !,
X \= 'end_of_file'.

read_terms(S, [X|L]) :-
call_read_term(S, X),
read_terms(S, L).

read_terms(S, []).

?- open('some-read-terms.dat', read, S,
 [ eof_action(eof_code) ]),
   read_terms(S, Terms)

With Quantum Prolog and SICStus Prolog, but not SWI Prolog, assuming that read_term/4 can be iterated over via backtracking and relying on fail being returned on the last read_term/4 execution is also recommended since it's the most natural and least verbose solution:

% reading all terms from a file, binding/unifying terms
% with the "Terms" variable on backtracking

?- open('some-read-terms.dat', read, S,
 [ eof_action(eof_code) ]),
   read_term(S, Terms, [])

Note this solution shouldn't be used wile supplying a non-variable as Terms argument (such as in read_term(S, a(term), [])) since execution will fail both if the end of a stream is reached, and also if a term couldn't be unified with a(term), leaving unclear if the stream has been read to its end.

Note a common idiom to read all terms from a stream is to query at_end_of_stream/2, and on failure branch into calling read_term/4. However, this practice is not recommended, since read_term/4, after a term is read, explicitly doesn't read-ahead further characters from the stream. Hence, after read_term/4 has reported a term, a stream may still contain any number of whitespace characters or comments, and at_end_of_stream/2 will fail to guard further read attempts. SICStus Prolog has the consume_layout(true) option to handle this, but neither is consume_layout(true) part of ISO/IEC 13211-1, nor is it necessary as a read-option since it can be implemented using the regular read_char/2 and peek_char/2 predicates.

Note however, even though the description of ISO/IEC 13211-1's read_term/4 makes specific guarantees with respect to the stream position following read_term/4 (namely, that it is pointing to the next character following a read term), this is still an incomplete description and can't be relied on, since read_term/4 must leave a stream position that can be picked up by subsequent read_term/4 invocations. Since read_term/4 reads dot-terms, and a dot as end-token is required to be followed by layout characters (ie. whitespace or comments), in the case of a regular end-of-line comment, Prolog must consume all characters of that comment (and not just the % character starting the comment) until the next end-of-line character is encountered in order to be able to leave a stream position that can be picked up by further read_term/4 executions.

read_term(?term, +read_options)

read_term(Term, Read_options) is equivalent to

current_input(S),
read_term(S, Term, Read_Options)

read(@stream_or_alias, ?term)

read(Stream_or_alias, Term) is equivalent to

read_term(Stream_or_alias, Term, [])

read(Term)

read(Term) is equivalent to

current_input(S),
read_term(S, Term, Read_Options)

stream_property(@stream, ?property)

Reports a property value, or, on backtracking if ?property is variable, multiple properties of an open stream.

The following properties are reported:

file_name(F)

file name associated with a stream, if any

file_name(f) is only reported if the stream has an associated file name in the first place

mode(M)

mode in which the stream is opened; one of read, append, or 'write`

input(Bool)

true if @Stream is an input stream, false otherwise

output(Bool)

true if @Stream is an output stream, false otherwise

alias(A)

alias name of the stream, if any

alias(A) is only reported if the stream has an alias

note Quantum Prolog only supports the fixed aliases user_input and user_output

position(P)

P is the current file read/write position

position(P) is only reported if the stream has the reposition(true) property

end_of_stream(X)

X is either the atom at if the stream has been read to its end, or not otherwise

the additional value past described in ISO/IEC 13211-1 isn't reported by Quantum Prolog Non-ISO restriction

eof_action(Action)

ation to perform on the end-of-stream condition as specified on open/4 or open/3 for the stream

reposition(Bool)

whether the stream is repositonable, as specified on open/3 for the stream

type(T)

T is either the atom binary if the stream has been opened using the type(binary) option, or text otherwise

Exceptions

domain_error(stream, Stream)

thrown if Stream is neither variable nor a stream term as obtained by open/4 or open/3

existence_error(stream, Stream)

thrown if Stream doesn't refer to a currently open stream

domain_error(stream_property, Property)

thrown if Property isn't a term with princpal functor matching one of the above-stated recognized stream properties

system_error(Message)

thrown on I/O errors

at_end_of_stream(@stream_or_aluas)

Succeeds if a given stream has been read to the end or has otherwise no more data to read.

@stream_or_alias

a stream-term as obtained by open/4 or the stream-alias user_input or user_output for which to report the end-of-stream status

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream, Stream)

thrown if Stream_or_alias is neither variable nor a stream-term or stream-alias

existence_error(stream, Stream)

thrown if Stream_or_alias doesn't refer to a currently open stream

at_end_of_stream

at_end_of_stream/0 is equivalent to

at_end_of_stream(user_input)

Character I/O No web support

get_char(@stream_or_alias, ?in_character)

Succeeds while reading a character from a stream, representing read data as single-character atom.

@stream_or_alias

stream to read from

?in_character

variable or single-character atom representing the character that is read, or the atom end_of_file

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term or stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a read stream

permission_error(input, binary_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a binary stream

representation_error(character)

thrown if the data read from the input stream is an invalid sequence of code units for ISO/IEC 10646 (Unicode), or

thrown if the data read from the input stream represents a code point outside the Basic Multilingual Plane (BMP) and can't be represented as single-character atom

to read character data outside the BMP, use get_code/2 or get_code/1 instead of get_char/2 and get_char/1, respectively

note a code unit sequence representing U+FFFD REPLACEMENT CHARACTER (which is used by Unicode applications to represent unmappable or otherwise invalid character data) is considered an invalid sequence of code units by get_char/2; to read character data containing U+FFFD, use get_byte/2 instead

permission_error(input, past_end_of_stream, Stream_or_alias)

thrown on an attempt to read past the end of the stream when the stream was opened using the eof_action(error) stream-option

if, on the other hand, eof_action(eof_code) is in use as effective read-option, then the atom end_of_stream is bound to or unified with in_character instead

type_error(in_character, In_character)

thrown if the in_character argument is neither variable, nor a single-character atom or the end_of_file atom

peek_char(@stream_or_alias, ?in_character)

Succeeds while reading-ahead a character from a stream, representing read data as single-character atom, and leaving the stream's current file position unchanged.

peek_char/2 works identical to get_char/2, except that the stream to read is left unchanged. Subsequent read_char/2 or peek_char/2 invocations will read the same character value from the stream that is read by peek_char/2.

@stream_or_alias

stream to read from

?in_character

variable or single-character atom representing the character that is read, or the atom end_of_file

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term nor stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a read stream

permission_error(input, binary_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a binary stream

representation_error(character)

thrown if the data read from the input stream represents a code point outside the Basic Multilingual Plane (BMP) and can't be represented as single-character atom

to read-ahead character data outside the BMP, use peek_code/2 or peek_code/1 instead of peek_char/2 and peek_char/1, respectively

permission_error(input, past_end_of_stream, Stream_or_alias)

thrown on an attempt to read past the end of the stream when the stream was opened using the eof_action(error) stream option

if, on the other hand, eof_action(eof_code) is used as effective read-option, then the atom end_of_stream is bound to/unified with in_character instead

type_error(in_character, In_character)

thrown if the in_character argument is neither variable, nor a single-character atom, nor the end_of_file atom

get_code(@stream_or_alias, ?in_character_code)

Succeeds while reading a character from a stream, representing read data as an integer containing an ISO/IEC 10646 (Unicode) code point.

@stream_or_alias

stream to read from

?in_character_code

variable or integer representing a Unicode code point, or -1

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term nor stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a read stream

permission_error(input, binary_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a binary stream

representation_error(character)

thrown if the data read from the input stream is an invalid sequence of code units

note get_code/2, in contrast to get_char/2, can read code sequences representing characters outside the Basic Multilingual Plane (BMP)

note a code unit sequence representing U+FFFD REPLACEMENT CHARACTER (which is used by Unicode applications to represent unmappable or otherwise invalid character data) is considered an invalid sequence of code units by get_code/2; to read character data containing U+FFFD, use get_byte/2 instead

permission_error(input, past_end_of_stream, Stream_or_alias)

thrown on an attempt to read past the end of the stream when the stream was opened using the eof_action(error) stream-option

if, on the other hand, eof_action(eof_code) was used as effective read-option, then -1 is bound to/unified with in_character_code instead

type_error(integer)

thrown if the in_character_code argument is neither variable, nor an integer

peek_code(@stream_or_alias, ?in_character_code)

Succeeds while reading-ahead a character from a stream, representing read data as an integer containing an ISO/IEC-10646 (Unicode) code point, leaving the stream's current file position unchanged.

peek_code/2 works identical to get_code/2, except that the stream to read is left unchanged. Subsequent read_code/2 or peek_code/2 invocations will read the same character value from the stream that is read by peek_code/2.

@stream_or_alias

stream to read from

?in_character_code

variable or integer representing an ISO/IEC 10646 (Unicode) code point, or -1

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term nor stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a read stream

permission_error(input, binary_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a binary stream

representation_error(character)

thrown if the data read-ahead from the input stream is an invalid sequence of code units

note peek_code/2, in contrast to peek_char/2, can read code sequences representing characters outside the Basic Multilingual Plane (BMP)

note a code unit sequence representing U+FFFD REPLACEMENT CHARACTER (which is used by Unicode applications to represent unmappable or otherwise invalid character data) is considered an invalid sequence of code units by peek_code/2; to read-ahead character data containing U+FFFD, use peek_byte/2 instead

permission_error(input, past_end_of_stream, Stream_or_alias)

thrown on an attempt to read past the end of the stream when the stream was opened using the eof_action(error) stream option

if, on the other hand, eof_action(eof_code) is in use as effective read-option, then the atom end_of_stream is bound to or unified with in_character instead

type_error(integer)

thrown if the in_character_code argument is neither variable, nor an integer

put_char(@stream_or_alias, +character)

Succeeds while writing a single character, presented as a single-character atom, to a stream.

@stream_or_alias

stream to write to

+character

single-character atom representing the character to write

Exceptions

instantiation_error

thrown if Stream_or_alias or character is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term nor stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(output, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a write or append stream

permission_error(output, binary_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a binary stream

type_error(character)

thrown if character is neither variable, nor an atom

representation_error(character)

thrown if the character argument atom hasn't a single-character name

Unsupported char_conversion note Non-ISO restriction

The char_conversion facility to remap characters for input operations isn't supported with Quantum Prolog. instead, Prolog code must always consist of ISO 10646 (Unicode) Basic Multi-Lingual Plane characters in UTF-8 encoding.

Byte I/O No web support

get_byte(@stream_or_alias, ?in_byte)

Succeeds reading a byte, presented as an integer, from a stream.

If the stream to read from has been opened with the eof_action(eof_code) stream option, then, at the end the stream, -1 is reported and assumed for unification with in_byte; otherwise (if eof_action(error) has been specified as stream option for open/4), an exception is thrown (see details below).

@stream_or_alias

stream to read from

+in_byte

integer to bind to, or unify with, the byte read

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term nor stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, text_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a text stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to read stream

type_error(byte, In_byte)

thrown if in_byte isn't a byte value, ie. not an integer not less than zero and not geater than 255

permission_error(input, past_end_of_stream, Stream_or_alias)

thrown on an attempt to read past the end of the stream, when the stream was opened with the eof_action(error) stream-option

peek_byte(@stream_or_alias, ?in_byte)

Succeeds reading-ahead a byte, presented as an integer, from a stream, and leaving the stream's current file position unchanged.

peek_byte/2 works identical to get_byte/2, except that the stream to read is left unchanged. Subsequent read_byte/2 or peek_bte/2 invocations will read the same byte value from the stream that is read by peek_byte/2.

@stream_or_alias

stream to read from

+in_byte

integer to bind to, or unify with, the byte read

Exceptions

instantiation_error

thrown if Stream_or_alias is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term or stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, text_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a text stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a read stream

type_error(byte, In_byte)

thrown if in_byte isn't a byte value, ie. not an integer not less than zero and not geater than 255

permission_error(input, past_end_of_stream, Stream_or_alias)

thrown on an attempt to read past the end of the stream, when the stream was opened with the eof_action(error) stream-option

put_byte(@stream_or_alias, +byte)

Succeeds reading a byte, presented as an integer, from a stream.

@stream_or_alias

stream to read from

+byte

byte, as an integer, to write

Exceptions

instantiation_error

thrown if Stream_or_alias or byte is variable

domain_error(stream_or_alias, Stream_or_alias)

thrown if Stream_or_alias is neither variable nor a stream-term or stream-alias

existence_error(stream, Stream_or_alias)

thrown if @stream_or_alias contains a file descriptor term that doesn't refer to an open stream

permission_error(input, stream, Stream_or_alias)

thrown if Stream_or_alias doesn't refer to a write or append stream

permission_error(output, text_stream, Stream_or_alias)

thrown if Stream_or_alias refers to a text stream

type_error(byte, Byte)

thrown if byte isn't a byte value, ie. not an integer not less than zero and not geater than 255

String and atom predicates

sub_atom(+atom, ?before, ?length, ?after, +sub)

Checks or generates, as atoms, substrings of an atom name.

sub_atom/5 is true if sub is an atom having as name a substring of the name of Atom, preceeded by Before characters, having a length of Length characters, and followed by After characters in the name of Atom. Any combination of before, length, after, and sub can be variable, in which case multiple solutions can be retrieved on backtracking.

Exceptions

instantiation_error

thrown on an attempt to call sub_atom/5 with a variable as Atom

type_error(, Atom)

thrown if Atom is neither an atom nor variable

type_error(atom, Sub)

thrown if Sub is neither an atom nor variable

type_error(integer, Value)

thrown if any of Before, Length, or After is neither variable nor an integer

domain_error(not_less_than_zero, Value)

thrown if Before, Length, or After is neither variable, or is a negative integer or, in the case of Length, isn't a positive integer

atom_chars(+atom, ?character_iist

(or atom_chars(-atom, +character_iist).

Succeeds as character_list is the list of single-character atoms representing the name of atom.

instantiation_error

thrown if both atom and character_list are variables, or Atom is variable and Character_list a partial list

type_error(atom, Atom)

thrown if atom is neither an atom nor variable

type_error(list, Atom)

thrown if character_list is neither a list, nor a partial list, nor variable

type_error(character, E)

thrown if character_list contains an element E that is neither a single-character atom nor variable

atom_codes(+atom, ?character_code_list)

or (atom_codes(-atom, +character_code_list))

Succeeeds as character_list is the list of character codes representing the name of atom.

Exceptions

instantiation_error

thrown if both atom and character_code_list are variable, or Atom is variable and Character_code_list a partial list

type_error(atom, Atom)

thrown if atom is neither an atom nor variable

type_error(list, Atom)

thrown if character_code_list is neither a list, nor a partial list, nor variable

representation_error(character_code)

thrown if character_code_list contains an element that isn't a character code, or

thrown if character_code_list contains a code representing a character that cannot be used in atom names (such as a non-Unicode Basic Multilinigual Plane, control, or special character)

atom_length(+atom, ?integer)

Succeeds as integer is the length of the atom name of atom.

Exceptions

instantiation_error

thrown if atom is variable

type_error(atom, Atom)

thrown if atom is neither an atom nor variable

type_error(integer, Integer)

thrown if integer is neither an integer nor variable

domain_error(not_less_than_zero, Integer)

thrown if integer is an integer less than zero

atom_concat(?start, ?end, ?whole)

Succeeds unifying whole with the concatenation of atom names in start and end, backtracking over multiple possible decompositions of whole into concatenatable parts if both start and end are variable.

If start or end are variable, either can be unified with '' (the null atom), and the other variable with the atom containing all characters of whole (the atom in whole itself).

Exceptions

instantiation_error

thrown if both start and whole are variable, or

thrown if both end and whole are variable

type_error(atom, Start)

thrown if start is neither variable nor an atom

type_error(atom, End)

thrown if end is neither variable nor an atom

type_error(atom, Whole)

thrown if whole is neither variable nor an atom

char_code(+character, ?character_code)

(or char_code(-character, +character_code)).

Succeeds as +character is the single-character atom constructed from the ?character_code Unicode BMP code point.

Exceptions

instantiation_error

thrown if both characater and character_code are variables

type_error(character, Character)

thrown if character is neither a single-character atom nor variable

tpye_error(integer, Character_code)

thrown if character_code is neither an integer nor variable

representation_error(character_code)

thrown if character_code isn't an integer in the Unicode BMP range, or represents a character not in the processor character set and disallowed for atom names

number_chars(+number, =character_list)

(or number_chars(-number, +character_list))

Succeeds as character_code_list is the list of single-char atoms representing the number number in serialized form.

Exceptions

instantiation_error

thrown if both Number and Character_list are variables

type_error(number, Number)

thrown if the Number argument is neither a number nor variable

type_error(list, Character_list)

thrown if the character_list argument is a partial list

type_error(character, E)

thrown if the character_list argument list contains an element E that isn't a single-character atom

syntax_error(Msg)

thrown if the single-character atoms, when concatenated, don't represent a Prolog number (integer or float) token

number_codes(+number, ?character_code_list)

or (number_codes(?number, +character_code_list)).

Succeeds as character_code_list is the list of character codes representing the number number in serialized form.

Exceptions

instantiation_error

thrown if both Number and Character_code_list are variable

type_error(number, Number)

thrown if the Number argument is neither a number nor variable

type_error(list, Character_code_list)

thrown if the character_code_list argument is a partial list

representation_error(character_code)

thrown if the character_code_list argument list contains an element that isn't a character code

syntax_error(Msg)

thrown if the character_code_list list, doesn't, as a sequence of character codes, represent a Prolog number (integer or float) token

Term type checking

var(@term)

Succeeds if the argument term is a variable, fails otherwise.

nonvar(@term)

Fails if the argument term is a variable, succeeds otherwise.

atom(@term)

Succeeds if the argument term is an atom, fails otherwise.

atomic(@term)

Succeeds if the argument term is an atom or a number, and fails otherwise.

number(@term)

Succeeds if the argument term is a number, fails otherwise.

integer(@term)

Succeeds if the argument term is an integer, fails otherwise.

float(@term)

Succeeds if the argument term is a float, fails otherwise.

compound(@term)

Succeeds if the argument term is neither atomic nor a variable, and fails otherwise.

callable(@term) ISO/IEC 13211-1 (2012)

Succeeds if the argument term is an atom or a compound term, and fails otherwise.

ground(@term) ISO/IEC 13211-1 (2012)

Succeeds if the argument term contains no variables, and fails otherwise.

acyclic_term(@term) ISO/IEC 13211-1 (2012)

Succeeds unless the argument term contains a variable that transitively binds "to itself"; halts program execution with error otherwise.

For example, X in the Prolog source text X = f(X) is not acyclic.

Note the result of acyclic_term/1 in the presence of non-acyclic bindings for one or more variables occuring in the term is undefined according to ISO/IEC 13211-1 (2012). The only guarantee given is that programs can rely on execution to continue after a call to acyclic_term/2 if the argument term is actually acyclic. Thus, acyclic_term/2 merely acts as a barrier for running into bogus computation on cyclic terms.

Term construction and deconstruction

arg(+integer, +compound_term, ?term)

Succeeds if the integerth argument in copound_term unifies with term.

Exceptions

instantiation_error

thrown if integer or compound_term is variable

type_error(integer, Integer)

thrown if integer is not an integer value

type_error(compound, Compound_term)

thrown if compound_term is neither variable nor a compound term

domain_error(not_less_than_zero, Integer)

thrown if integer is an integer less than zero

functor(-nonvar, +atomic, +integer)

(or functor(+nonvar, ?atomic, ?integer))

Succeeds while unifying the functor of the nonvar term argument with the atomic argument, and its arity with the integer argument.

Exceptions

instantiation_error

thrown if both the nonvar and atomic arguments are variable, or both the nonvar and integer arguments are variable

type_error(integer, Integer)

thrown if the integer argument is neither variable nor an integer

type_error(atomic, Atomic)

thrown if the atomic argument is not atomic

domain_error(not_less_than_zero, Integer)

thrown if the integer argument integer is less than zero

representation_error(max_arity)

thrown if the nonvar argument is variable and the integer argument integer exceeds the maximal arity value of 63

copy_term(?term1, ?term2)

Succeeds unifying term1 with term2, where all variables in term1 are replaced by anonymous variables.

'=..'(+nonvar, ?list) (the "univ" operator)

(or '=..'(-nonvar, +list))

Succeeds unifying nonvar's principal functor with the head of list and nonvar's arguments, if any, with the remaining elements of list.

Exceptions

instantiation_error

thrown if both the nonvar and the list arguments are variable, or thrown if nonvar is variable and list is a partial list, or if nonvar and the head of list are variable

type_error(list, List)

thrown if list is neither variable nor a list

domain_error(non_empty_list, [])

thrown if list is the empty list

type_error(atom, H)

thrown if list has a head element that is neither an atom nor variable, yet isn't a singleton list but has further elements

type_error(atomic, H)

thrown if list has a head that is neither variable nor atomic

representation_error(max_arity)

if the number of elements on list exceeds 64 (the functor plus the maximal allowed number of arguments 63)

Other predicates

call(Goal)

Succeeds as Goal, when interpreted as a callable term, succeeds. For example, call(p(X)) is equivalent to p(X) (with the exception that any cut/0 invocation doesn't extend outside call/1), but the first variant allows Goal to be constructed dynamically; for example, Goal = p(X), call(Goal) has the same effect as p(X).

Exceptions

representation_error(max_arity)

thrown if Goal has an arity greated than the maximum of 63

type_error(callable, Goal)

thrown if Goal is not a callable term (that is, not a term with principal functor an atom)

call(Goal, ...) ISO/IEC 13211-1 (2012)

call(Goal, Arg1, ...) succeeds as call(GoalX) succeeds where GoalX is constructed from Goal with additional arguments Arg1, ... appended.

Exceptions

representation_error(max_arity)

thrown (in addition to the general rules specified for call/1) when the construction of a goal from the first argument with the subsequent arguments would result in a term with an arity greated than the maximum of 63

once(+callable_term)

once(X) is equivalent to

call(X), !

Exceptions

instantiation_error

thrown if callable_term is variable

type_error(callable, ?Callable_term)

thrown if callable_term is neither a callable term nor variable

unify_with_occurs_check(?term, ?term)

Performs ordinary unification of the first term with the second, succeeding only (unlike ordinary unification) if no variable is bound to a term that contains the bound-to variable itself as a subterm.

current_prolog_flag(?flag, ?term)

Backtracks over Prolog flags (in flag) and their current values (in term).

The atoms recognized as flags by Quantum Prolog, and ther respective values bound to or unified with term are as follows:

bounded

term is unified with true, meaning that representation and precision integer arithmetic is subject to the reported max_integer and min_integer values, respectively

max_integer

term is unified with 2147483647

min_integer

term is unified with -2147483648

integer_rounding_function

term is unified with down, meaning that integer division is performed as F-division

char_conversion

term is always unified with off, meaning that no character conversion can be used with Quantum Prolog

debug

term is unified with off (the default) or on (if switched on using set_prolog_flag(debug, on)

max_arity

term is unified with 63, the maximum term arity for Quantum Prolog

unknown

term is unified with error (the default), or fail or warning if instructed to via set_prolog_flag(unknown, fail) or set_prolog_flag(unknown, warning), respectively

double_quotes

term is unified with codes, meaning that double-quoted strings are always transparently represented as list of character codes (Unicode code points)

Exceptions

type_error(atom, Flag)

thrown if the atom argument isn't an atom

domain_error(prolog_flag, Flag)

thrown if the atom argument atom isn't one of the above listed atoms representing recognized Prolog flags

halt(+integer)

Immediately stops Prolog execution, returning the argument integer as process completion code to the host operating system or other host environment.

Exceptions

instantiation_error

thrown if the argument is variable

type_error(integer, Integer)

thrown if the argument is neither variable nor an integer

sort(@list, -sorted_list)

(or sort(+list, +sorted_list))

Succeeds as sorted_list unifies with a list that contains all the elements of list, sorted uniquely according to Prolog term ordering.

Exceptions

instantiation_error

thrown if list is a partial list (a variable or a term with principal functor '.'/2) and second argument a variable)

type_error(list, list)

thrown if list is neither a list nor partial list

type_error(list, sorted_list)

thrown if sorted_list is neither a list nor partial list

keysort(@pair_list, -sorted_pair_list) ISO/IEC 13211-1 (2012)

(or sort(+pair_list, +sorted_pair_list))

Considers pair_list as a list of terms with principal functor '-'/2 with the respective first argument a key term and the second a value term, and unifies sorted_pair_list with a permutation of pair_list containing elements ordered on key according to Prolog term ordering. Unlike sort/2, ordered_pair_list contains as many elements as pair_list including duplicates (with respect to key), with duplicates preserving their relative ordering in pair_list (ie. a stable sort is performed).

Exceptions

instantiation_error

thrown if pair_list is a partial list (a variable or a term with principal functor '.'/2 and second argument a variable)

type_error(list, Pair_list)

thrown if pair_list is neither a list nor partial list

type_error(list, Sorted_pair_list)

thrown if sorted_pair_list is neither a list nor partial list

type_error(pair, Element)

thrown if an element Element of pair_list isn't a term with principal functor '-'/2, for Element the first such element in pair_list, or

thrown if an element Element of ordered_pair_list is neither variable nor a term with principal functor '-'/2, for Element the first such element in ordered_pair_list

subsumes_term(@generic, @specific) ISO/IEC 13211-1 (2012)

Succeeds if the generic term is equal to the specific term, or can be made equal by consistently substituting variables in generic without assuming substitution of variables in specific.

For example, ?- subsumes(f(X, Y), f(Z, Z)) succeeds, since, in the term f(X, Y), both X and Y can be substituted by Z to result in f(Z, Z).

On the other hand, ?- subsumes_term(f(Z, Z), f(X, Y)) does not succeed, since there is no substitution for the variables in f(Z, Z) that make it equal to f(X, Y). In contrast, regular unification produces a substitution for X into Z and Y into Z regardless of the order of the arguments given, whereas subsumes_term/2 only performs one-sided unification.

subsumes_term/2 only checks if unification succeeds, but doesn't bind variables. subsumes_term/2 performs (single-sided) unification subject to occurs-checking (see unify_with_occurs_check/2).

compare_term(-order, ?term1, ?term2) ISO/IEC 13211-1 (2012)

(or compare_term(+order, @term1, @term2))

Succeeds while unifying order with one of the atoms <, =, and > according to whether term1 precedes term2, or is equal to term2, or term1 precedes term2, respectively, according to Prolog term ordering.

Note in compare_term/2, non-equality order relations (the first argument) are expressed through operators for arithmetic rather than term order, and equality is expressed through the operator used for term unification.

Exceptions

type_error(atom, Order)

thrown if order is neither variable nor an atom

domain_error(order, Order)

thrown if order is an atom other than <, =, or >

term_variables(@term, -list) ISO/IEC 13211-1 (2012)

(or term_variables(?Term, ?List))

Succeeds while unifying list with the list of variables of term, sorted uniquely according to Prolog term order.

Exceptions

type_error(list, List)

thrown if List isn't a list or partial list

numbervars(+term, ?start_index, ?end_index) Non-ISO extension

Binds all free variables in term with terms of the form '$VAR'(n) where n is an integer starting with start_index (or 0 if supplied as variable) and from the left-most subterm of term, proceeding to the right-most subterm in inorder traversal, assigning incremented n values as new free variables are encountered during the traversal.

end_index is bound (or checked against, if not supplied as variable) to the integer following the last assigned one during traversal.

This predicate is used as a supplement for using write/3 with the numvars(true) write-option (or its write_canonical/1 shortcut) but can also be used for term manipulation on it's own.

Exceptions

type_error(integer, Start_index) (or type_error(integer, End_index))

thrown if either start_index or end_index is neither variable nor an integer

subtract(+list, +delete_list, ?result_list) Non-ISO extension

Succeeds as result_list unifies with the list obtained by removing all elements from list that are in delete_list.

Exceptions

instantiation_error

thrown if list or delete_list is variable

type_error(list, List)

thrown if list isn't a list

type_error(list, Delete_list)

thrown if delete_list isn't a list

type_error(list, Result_list)

thrown if result_list is neither variable nor a list

statistics(walltime, ?list) Non-ISO extension

Reports the elapsed time, in milliseconds, since the start of the program, or since the last call to statistics(walltime, _).

statistics/2 unifies a two-member list containing the number of milliseconds since program start time as its first member, and the number of milliseconds since statistics/2 has been called last as its second member. The first argument must be instantiated to the atom walltime (which is the only keyword supported with Quantum Prolog).

This predicate is for assessing basic run-time performance and supplied in a form compatible with traditional (SICStus heritage) Prolog usage. Third-party Prolog systems may support a number of implementation-specifc additional keys to use as first argument with varying semantics. Note as a tool for peformance monitoring, the statistics/2 portability predicate also suffers from low time resolution, and from having stateful semantics not extending well to multi-threaded execution.

Exceptions

instantiation_error

thrown if the first argument is variable

type_error(statistics_key, KeywordArg)

thrown if the first argument isn't the fixed atom walltime

type_error(list, List)

thrown if the second argument is neither variable nor a list

Unimplemented ISO/IEC 13211-1 (2012) predicates Non-ISO restriction

false/0

false/0 is a trivial predicate that could be defined as false :- fail. or doesn't need to be defined at all if :- set_prolog_flag(unknown, fail). is used as a directive. In Quantum Prolog, false/0 isn't predefined as a built-in predicate because it tends to break third-party software such as theorem provers, ILP software, and other Prolog code dealing with custom logic theories making use of a false/0 predcate to represent negative knowledge (eg. as in false :- p(a).). Thus, on balance, false/0 doesn't provide sufficient value when weighed against the need for (trivial) rewrites of large software packages, in particular when this also undermines efforts for exchanging theories represented as Prolog clause terms.