The builtins are listed here in the order in which they appear
in the ISO standard. This is preceded by a table which is in a somewhat
alphabetic order.
Certain constructions, more or less difficult to achieve in pure Prolog
are defined in the standard to be "control constructs".
Ironically, and perhaps somewhat counter intuitively cut can (in the presence of (\+)/1
increase the number of solutions.
As the following example (from the book of Deransart, Ed-Dbali and Cervoni) shows:
p:- true.
p:- throw(b).
q:- catch(p, B, write('hellop')), r(c).
r(X) :- throw(X).
Then the goal:
catch(p, X, (write('error from p'), nl)).
Succeeds twice,
- With the empty substitution,
- With X <- b after writing
error from p.
The goal:
catch(q, C, write(helloq)).
succeeds after writing helloq.
The definition of each flag indicates whether it is changeable or not.
- bounded
-
Possible value: true, false
Default Value: Implementation defined
Changeable: No
- max_integer
-
Possible value: the default value
Default value: implementation defined
Changeable: No
- min_integer
-
Possible value: the default value
Default value: implementation defined
Changeable: No
- integer_rounding_function
-
Possible values: down, toward_zero
Default value: implementation defined
Changeable: No
- char_conversion
-
Possible values: on, off
Default value: on
Changeable: Yes
- debug
-
Possible values: on, off
Default value: off
Changeable: Yes
- max_arity
-
Possible value: the default value
Default value: implementation defined
Changeable: No
- unknown
-
Possible values: error, fail, warning
Default value: error
Changeable: Yes
Determines the behaviour of the processor upon attempting to execute a
procedure which does not exist.
- double_quotes
-
Possible values: chars, codes, atom
Default value: implementation defined
Changeable: Yes
Determines the syntax of a double quoted list.
Templates and modes are given for each builtin.
Term Unification
If X and Y are
Not Subject to Occurs check
then X = Y is true iff X and Y are unifiable.
Template '='(?term,?term)
unify_with_occurs_check(X,Y) is true if and only if
X and Y are unifiable.
Template unify_with_occurs_check(?term,?term)
If X and Y are
Not Subject to Occurs check
then X \= Y is true iff X and Y are not unifiable.
Template '\\='(?term,?term)
Type Testing
var(X) is true if and only if X is a variable.
Template var(@term)
atom(X) is true if and only if X is an atom.
Template atom(@term)
integer(X) is true if and only if X is an integer.
Template integer(@term)
float(X) is true if and only if X is a float.
Template float(@term)
atomic(X) is true if and only if X is atomic (that is
an atom, an integer or a float).
Template atomic(@term)
compound(X) is true if and only if X is a compound term,
that is neither atomic nor a variable.
Template compound(@term)
nonvar(X) is true if and only if X is not a variable.
Template nonvar(@term)
number(X) is true if and only if X is an integer or a float.
Template number(@term)
There is an ordering on Prolog terms obtained as follows:
variables term precede floats which term precede
integers which term precede atoms which term
precede compound.
Within each term the ordering is the obvious one except that
- For variables the order is implementation dependent.
- for compound terms: X term precedes Y if
arity(X) < arity(Y,
if the arities are the same then X term precedes Y if
functor name X term precedes the functor name of Y,
If arity and functor names are the same then the left most differing
arguments determine the term precedence.
- (@=<)/2
- Term less than or equal to.
- (==)/2
- Term identical
- ((\==)/2
- Term not identical
- (@<)/2
- Term less than
- (@>)/2
- Term greater than
- (@>=)/2
- Term greater than or equal to.
Templates
'@=<'(@term,@term)
'=='(@term,@term)
'\=='(@term,@term)
'@<'(@term,@term)
'@>'(@term,@term)
'@>='(@term,@term)
functor(Term, Name, Arity) is true if and only if:
- Term is a compound term with functor name
Name and arity Arity or
- Term is an atomic term equal to
Name and Arity is 0.
It is the second of these possibilities that explains why in the two
templates for
functor/3
- functor(-nonvar, +atomic, +integer)
- functor(+nonvar, ?atomic, ?integer)
the second parameter is atomic and not an atom.
functor(Term throws representation_error if Arity exceeds max_arity.
arg(N,Term, Arg) is true if nad only if the Nth argument
of Term is Arg
Template: arg(+integer, +compound_term, ?term)
Note that arg(N, Term, Arg) throws a
domain_error if N is less than zero.
Term =.. List is true if and only if
- Term is an atomic term and List is the list whose only element is Term, or
- Term is a compound term and List is the list whose
head is the functor name of Term and whose tail is the list of the arguments of Term.
Templates:
- '=..'(+nonvar, ?list)
- '=..'(-nonvar, +list)
copy_term(X,Y) is true if and only if Y unifies with a term T which is a renamed copy of X.
Template: copy_term(?term, ?term).
'is'(Result, Expression) is true if and only if the value
of evaluating Expression as an expression is Result
Template: is(?term, @evaluable)
If Expression is a variable is/2 throws an instantiation_error
'=:='/2 | Arithmetic Equal
|
'=\\='/2 | Arithmetic Not equal
|
'<'/2 | Arithmetic less than
|
'=<'/2 | Arithmetic less than or equal to
|
'>'/2 | Arithmetic greater than
|
'>='/2 | Arithmetic greater than or equal to
|
Templates:
'=:='(@evaluable, @evaluable)
'=\\='(@evaluable, @evaluable)
'<'(@evaluable, @evaluable)
'=<'(@evaluable, @evaluable)
'>'(@evaluable, @evaluable)
'>='(@evaluable, @evaluable)
If either argument is a variable the arithmetic comparison functors
throw an instantiation_error
Clause Retrieval and Information
These predicates allow the contents of the database to be
inspected.
clause(Head, Body) is true if and only if
- The predicate of Head is public (the standard does not specify
how a predicate is declared public but dynamic
predicates are public, and
- There is a clause in the database which corresponds to a term
H:- B which unifies with Head :- Body.
Template: clause(+head, ?callable_term)
Errors:
- Head is a variable -- instantiation_error
- Head is neither a variable nor a predication --
type_error(callable, Head)
- The predicate indicator Pred of Head is that of
a private (ie. Not public) procedure --
permission_error(access,
private_procedure, Pred)
- body is neither a variable nor a callable term
type_error(callable, Body).
current_predicate(PI) is true if and only if
PI is a predicate indicator for one of the user-defined
procedures in the database.
By backtracking current_predicate(X/Y) finds all the user defined
predicates in the current database.
Template: current_predicate(?predicate_indicator)
Errors: If PI is neither a variable nor a predicate
indicator throws type_error(predicate_indicator, PI).
Clause Creation and Destruction
These predicates allow the database to be altered during the course of
execution. Note however that their effect is subject to the
logical view of the database.
The database is " frozen " at the start of a query.
asserta(Clause) is true.
It has for side effect the addition of the clause H :-B to the
database before all other clauses for the predicate associated to H.
H :- B is determined as follows.
- Either Clause unifies with H :-B, or
- Clause unifies with H and
B with true.
Template: asserta(@clause)
Errors:
- H is a variable -- instantiation_error
- H is neither a variable nor does it correspond to a predication-- type_error(callable, H)
- B does not correspond to a callable term --
type_error(callable, B)
- The predicate indicator Pred of H is that of
a static (ie. not dynamic) procedure --
permission_error(modify,
static_procedure, Pred)
assertz(Clause) is true.
It has for side effect the addition of the clause H :-B to the
database after all other clauses for the predicate associated to H.
H :- B is determined as follows.
- Either Clause unifies with H :-B, or
- Clause unifies with H and
B with true.
Template: assertz(@clause)
Errors:
- H is a variable -- instantiation_error
- H is neither a variable nor does it correspond to a predication-- type_error(callable, H)
- B does not correspond to a callable term --
type_error(callable, B)
- The predicate indicator Pred of H is that of
a static (ie. not dynamic) procedure --
permission_error(modify,
static_procedure, Pred)
retract(Clause) is true if the database contains at least one
dynamic procedure with a clause Clause which unifies with
Head :- Body determined as follows:
- Either Clause unifies with Head :-Body, or
- Clause unifies with Head and
Body unifies with true.
As a side effect the clause is removed from the database.
A Predicate all of whose clauses have been removed from the database
by a sequence or retracts is still found by current_predicate
Template: retract(+clause)
Errors:
- Head is a variable -- instantiation_error
- Head is neither a variable nor does it correspond to a predication -- type_error(callable, Head)
- The predicate indicator Pred of Head is that of
a static (ie. not dynamic) procedure --
permission_error(modify,
static_procedure, Pred) Note The standard document says access at
this point this is clearly an error!.
abolish(Pred) is true. It has for side effect the removal of all
clauses of the predicate indicated by Pred. After abolish/1 the predicate is not found by current_predicate.
Template: abolish(@predicate_indicator)
Errors:
Pred is a variable -- instantiation_error
Pred is a term Name/Arity and either Name or
Arity is a variable -- instantiation_error
Pred is neither a variable nor a predicate indicator
-- type_error(predicate_indicator, Pred)
Pred is a term Name/Arity and Name is
neither a variable nor an atom
- type_error(atom, Name)
Pred is a term Name/Arity and Arity is an integer less than zero --
domain_error(not_less_than_zero, Arity)
Pred is a term Name/Arity and Arity is an integer greater than the implementation defined integer max_arity
-- representation_error(max_arity)
The predicate indicator Pred is that of
a static procedure --
permission_error(modify,
static_procedure, Pred)
These predicates are convenient for collecting solutions to a given goal.
It should be noted that bagof/3 and setof/3 fail when
there are no solutions to the goal, whereas findall/3 succeeds
setting the collection to empty.
findall(Template, Goal, Instances) is true if and only if
Instances unifies with the list of values to which a variable
X not occurring in Template or Goal
would be instantiated by successive re-executions of
call(Goal), X = Template
after systematic replacement of all variables in X by new
variables.
Template: findall(?term, +callable_term, ?list)
If the first argument appears in the last argument it can be instantiated
by findall.
Errors:
- Goal is a variable -- instantiation_error
- Goal is neither a variable nor a callable term --
type_error(callable, Goal)
- Instances is neither a partial list nor a list --
type_error(list, Instances)
bagof(Template, Goal, Instances) is true if Instances is a
non-empty list of all terms such that each
unifies with Template for a
fixed instance W of the variables of Goal that are free
with respect to Template. The ordering of the elements of
Instances is the order in which the solutions are found.
On backtracking bagof is resatisfiable with a different instance of W
Template: bagof(?term, +callable_term, ?list)
If the first argument appears in the last argument it can be instantiated
by bagof.
Errors
- Goal is a variable -- instantiation_error
- Goal is neither a variable nor a callable term --
type_error(callable, Goal)
- Instances is neither a partial list nor a list --
type_error(list, Instances)
setof(Template, Goal, Instances) is true if Instances is a
sorted
non-empty list of all terms such that each
unifies with Template for a
fixed instance W of the variables of Goal that are free
with respect to Template.
On backtracking setof is resatisfiable with a different instance of W
Template: setof(?term, +callable_term, ?list)
If the first argument appears in the last argument it can be instantiated
by setof.
Errors
- Goal is a variable -- instantiation_error
- Goal is neither a variable nor a callable term --
type_error(callable, Goal)
- Instances is neither a partial list nor a list --
type_error(list, Instances)
A summary of the I/O predicates is given on a special
page on IO.
These predicates link an external source/sink with a Prolog stream.
Note that the standard does not prescribe the form of a Stream term.
An open stream may also be referred to by a alias
assigned when the stream is opened.
current_input(Stream) is true if the stream term Stream
identifies the current input stream.
Template: current_input(?stream).
Errors.
- Stream is neither a variable nor a stream --
domain_error(stream, Stream)
current_output(Stream) is true if the stream term Stream
identifies the current output stream.
Template: current_output(?stream).
Errors.
- Stream is neither a variable nor a stream --
domain_error(stream, Stream)
set_input(Stream_or_Alias) is true. As a side effect
sets the current input to the Stream identified by Stream_or_Alias
Template set_input(@stream_or_alias)
Errors
- Stream_or_Alias is a variable --
instantiation_error
- Stream_or_Alias is neither a variable, nor a stream term or alias --
domain_error(stream_or_alias, Stream_or_Alias)
- Stream_or_Alias is not associated with an open stream --
existence_error(stream,
Stream_or_Alias)
- Stream_or_Alias is an output stream --
permission_error(input, stream,
Stream_or_Alias)
set_output(Stream_or_Alias) is true. As a side effect
sets the current output to the Stream identified by Stream_or_Alias
Template set_output(@stream_or_alias)
Errors
- Stream_or_Alias is a variable --
instantiation_error
- Stream_or_Alias is neither a variable, nor a stream term or alias --
domain_error(stream_or_alias, Stream_or_Alias)
- Stream_or_Alias is not associated with an open stream --
existence_error(stream,
Stream_or_Alias)
- Stream_or_Alias is an input stream --
permission_error(output, stream,
Stream_or_Alias)
open(Source_Sink, Mode, Stream, Options) is true, and has for side
effect the opening of Source/sink Source_Sink in mode Mode, the term Stream is a implementation
dependent term serving to identify the stream associated to the source/sink by the invocation of open.
Options is a list of open options
with which the stream is opened.
open/3 is like open/4 except that no open options
are supplied.
Template: open(@source_sink, @io_mode, -stream, @stream_options)
Errors
- Source_Sink is a variable --
instantiation_error
- Mode is a variable --
instantiation_error
- Options is a partial list or a list with an element E
which is a variable --
instantiation_error
- Mode is neither a variable nor an atom
-- type_error(atom, Mode)
- Options is neither a partial list nor a list
-- type_error(list, Options)
- Stream is not a variable --
type_error(variable, Stream)
- Source_Sink is neither a variable nor a source/sink
-- domain_error(source_sink, Source_Sink)
- Mode is an atom but not an input/output mode --
domain_error(io_mode, Mode)
- An element E of the Options list is neither a variable nor a stream-option --
domain_error(stream_option, E)
- The source/sink specified by Source_Sink does not exist
-- existence_error(source_sink, Source_Sink)
- The source/sink specified by Source_Sink cannot be opened --
permission_error(open, source_sink, Source_Sink)
- An element E of the Options list is alias
and A is already associated with an open stream
-- permission_error(open, source_sink, alias(A))
- An element E of the Options list is reposition(true) and it is not possible to reposition this stream.
-- permission_error(open, source_sink, reposition(true))
close(S_or_a, Options) is true, with side effect that it closes
the stream associated to S_or_a. The Options argument determines the close options for the operation.
close(S_or_a) is like close/2 except that no close
options are supplied.
Template: close(@stream_or_alias, @close_options)
Errors
- S_or_a is a variable --
instantiation_error
- Options is a partial list or a list with an element E
which is a variable --
instantiation_error
- Options is neither a partial list nor a list
-- type_error(list, Options)
- S_or_a is neither a variable nor a stream-term or alias
-- domain_error(stream_or_alias, S_or_a)
- An element E of the Options list is neither a variable nor a stream-option --
domain_error(stream_option, E)
- S_or_a is not associated with an open stream --
existence_error(stream, S_or_a)
stream_property(stream, Property is true if and only if the stream associated with the stream-term Stream has the stream property Property. On backtracking all properties of all open streams are discovered.
The predicates at_end_of_stream/0 and
at_end_of_stream/1 are defined as if as follows:
- at_end_of_stream:-
-
current_input(S),
stream_property(S, end_of_stream(E)),
!,
(E = at; E = past)
- at_end_of_stream(S_or_a) :-
-
( atom(S_or-a) ->
stream_property(S, alias(S_or_a))
;
S = S_or_a
),
stream_property(S, end_of_stream(E)),
!,
(E = at; E = past)
Templates:
stream_property(?stream,?property)
at_end_of_stream
at_end_of_stream(@stream_or_alias)
Errors
- S_or_a is a variable --
instantiation_error
- Stream is neither a variable nor a stream-term --
domain_error(stream, Stream)
- Property is neither a variable nor a stream property
-- domain_error(stream_property,Propertrty)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is not associated with an open stream --
existence_error(stream, S_or_a)
set_stream_position(S_or_a, Position) is true, with the side effect
of setting the stream_position to
Position. Normally, Position will have been obtained via the position/1 property of the stream.
Template:
set_stream_position(@stream_or_alias, @stream_position)
Errors
- S_or_a is a variable --
instantiation_error
- Position is a variable --
instantiation_error
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is not associated with an open stream --
existence_error(stream, S_or_a)
- S_or_a has stream property reposition(false)
-- permission_error(reposition, stream, S_or_a)
These predicates allow a single character or code to be input
from or output to a text stream.
get_char(S_or_a,Char) is true if and only if
Char unifies with the next character to be input from the target
stream identified by S_or_a, the character is input. get_char(Char) applies to the
current input stream.
get_code/2 and get_code/1
are defined as if
- get_code(Code):-
- current_input(S),
get_char(S,Char),
(Char = end_of_file ->
Code = -1
;
char_code(Char, Code)
).
- get_code(S, Code) :-
- get_char(S,Char),
(Char = end_of_file ->
Code = -1
;
char_code(Char, Code)
).
Templates:
get_char(?in_character)
get_char(@stream_or_alias, ?in_character)
get_code(?in_character_code)
get_code(@stream_or_alias, ?in_character_code)
Errors:
- S_or_a is a variable --
instantiation_error
- Char is neither a variable nor an in-character
-- type_error(in_character, Char)
- Code is neither a variable nor an integer
-- type_error(integer, Char)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is an output stream --
permission_error(input, stream, S_or_a)
- S_or_a is associated with a binary stream --
permission_error(input, binary_stream, S_or_a)
- S_or_a has stream properties end_of_stream(past) and
eof_action(error)
-- permission_error(input, past_end_of_stream, S_or_a)
- The entity input from the stream is not a character --
representation_error(character)
- Code is an integer but not an in-character code
representation_error(in_character_code)
peek_char(S_or_a,Char) is true if and only if
Char unifies with the next character that would be input from the target
stream identified by S_or_a, the character is not input. peek_char(Char) applies to the
current input stream.
peek_code/2 and peek_code/1 are defined as if
- peek_code(Code):-
- current_input(S),
peek_char(S,Char),
(Char = end_of_file ->
Code = -1
;
char_code(Char, Code)
).
- peek_code(S, Code) :-
- peek_char(S,Char),
(Char = end_of_file ->
Code = -1
;
char_code(Char, Code)
).
Templates:
peek_char(?in_character)
peek_char(@stream_or_alias, ?in_character)
peek_code(?in_character_code)
peek_code(@stream_or_alias, ?in_character_code)
Errors:
- S_or_a is a variable --
instantiation_error
- Char is neither a variable nor an in-character
-- type_error(in_character, Char)
- Code is neither a variable nor an integer
-- type_error(integer, Char)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is an output stream --
permission_error(input, stream, S_or_a)
- S_or_a is associated with a binary stream --
permission_error(input, binary_stream, S_or_a)
- S_or_a has stream properties end_of_stream(past) and
eof_action(error)
-- permission_error(input, past_end_of_stream, S_or_a)
- The entity input from the stream is not a character --
representation_error(character)
- Code is an integer but not an in-character code
representation_error(in_character_code)
put_char(S_or_a, Char) is true, with the side effect that Char is output to the stream associated with S_or_a.
put_char(Char) applies to the current output stream.
The predicates put_code/2, put_code/1, nl/1 and nl/0
are defined as if
- put_code(Code) :-
- current_output(S),
char_code(Char, Code),
put_char(S, Char).
- put_code(S,Code) :-
- char_code(Char, Code),
put_char(S, Char).
- nl :-
- current_output(S),
put_char(S, '\n').
- nl(S) :-
- put_char(S, '\n').
Templates
put_char(+character)
put_char(@stream_or_alias, +character)
put_code(+character_code)
put_code(@stream_or_alias, +character_code)
nl
nl(@stream_or_alias)
Errors:
- S_or_a is a variable --
instantiation_error
- Char is a variable --
instantiation_error
- Code is a variable --
instantiation_error
- Char is neither a variable nor a one character atom --
type_error(character, Char)
- Code is neither a variable nor an integer
-- type_error(integer, Char)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is not associated with an open stream --
existence_error(stream, S_or_a)
- S_or_a is an input stream --
permission_error(output, stream, S_or_a)
- S_or_a is associated with a binary stream --
permission_error(output, binary_stream, S_or_a)
- Char is not a character --
representation_error(character)
- Code is an integer but not an character code
representation_error(character_code)
These builtin predicates enable a single byte to be input from or output to
a binary stream.
get_byte(S_or_a,Byte) is true if and only if
Byte unifies with the next byte to be input from the target
stream identified by S_or_a, the byte is input. get_byte(Byte) applies to the
current input stream.
Template: get_byte(@stream_or_alias, ?in_byte)
Errors:
- S_or_a is a variable --
instantiation_error
- Byte is neither a variable nor an in-byte --
type_error(in_byte, Byte)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is an output stream --
permission_error(input, stream, S_or_a)
- S_or_a is associated with a text stream --
permission_error(input, text_stream, S_or_a)
- S_or_a has stream properties end_of_stream(past) and
eof_action(error)
-- permission_error(input, past_end_of_stream, S_or_a)
peek_byte(S_or_a,Byte) is true if and only if
Byte unifies with the next byte to be input from the target
stream identified by S_or_a, the byte is not input. peek_byte(Byte) applies to the
current input stream.
Template: peek_byte(@stream_or_alias, ?in_byte)
Errors:
- S_or_a is a variable --
instantiation_error
- Byte is neither a variable nor an in-byte --
type_error(in_byte, Byte)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is an output stream --
permission_error(input, stream, S_or_a)
- S_or_a is associated with a text stream --
permission_error(input, text_stream, S_or_a)
- S_or_a has stream properties end_of_stream(past) and
eof_action(error)
-- permission_error(input, past_end_of_stream, S_or_a)
put_byte(S_or_a, Byte) is true, with the side effect that Byte is output to the stream associated with S_or_a.
put_byte(Byte) applies to the current output stream.
Template: put_byte(@stream_or_alias, +byte)
Errors:
- S_or_a is a variable --
instantiation_error
- Byte is a variable --
instantiation_error
- Byte is neither a variable nor an byte
-- type_error(byte, Byte)
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- S_or_a is an input stream --
permission_error(output, stream, S_or_a)
- S_or_a is associated with a text stream --
permission_error(output, text_stream, S_or_a)
These predicates enable a Prolog term to input from or output to a
text stream. The syntax of such terms is affected by the operator table, the value of certain Prolog flags
and whether or not
character conversion is in effect.
read_term(S_or_a, Term, Options) is true if and only if Term
unifies with T where T. is a read-term which has been
constructed by inputting and parsing characters from the target stream.
The argument Options determines the
value of the read options in effect for the read.
The predicates read/1, read/2 and read_term/2 are defined as if:
- read_term(Term, Options) :-
- current_input(S),
read_term(S, Term, Options).
- read(S, Term):-
- read_term(S, Term, []).
- read(Term) :-
- current_input(S),
read_term(S, Term, []).
Template:read_term(@stream_or_alias, ?term, +read_options_list)
Errors:
- S_or_a is a variable --
instantiation_error
- Options is a partial list or a list with an element which is
a variable --
instantiation_error
- S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
- Options is neither a partial list nor a list --
type_error(list, Options)
- An element E of the Options list is neither a variable nor a valid read-option --
domain_error(read_option, E)
- S_or_a is not associated with an open stream --
existence_error(stream, S_or_a)
- S_or_a is an output stream --
permission_error(input, stream, S_or_a)
- S_or_a is associated with a binary stream --
permission_error(input, binary_stream, S_or_a)
- S_or_a has stream properties end_of_stream(past) and
eof_action(error)
-- permission_error(input, past_end_of_stream, S_or_a)
- One or more characters were input, but they cannot be parsed as a sequence of tokens --
syntax_error(implementation_dependent_atom)
- The sequence of tokens cannot be parsed as a term using the current
set of operator definitions --
syntax_error(implementation_dependent_atom)
write_term(S_or_a, Term, Options) is true, with for side effect
the output of Term to the target stream according to the operator table and the write-options.
The predicates write_term/2, write/1, write/2,
writeq/1, writeq/2, write_canonical/1, and write_canonical/2
are defined as if:
- write_term(Term, Options):-
- current_output(S),
write_term(S, Term, Options).
- write(Term):-
- current_output(S),
write_term(S, Term, [numbervars(true)]).
- write_term(S, Term) :-
- write_term(S, Term, [numbervars(true)]).
- writeq(Term):-
- current_output(S),
write_term(S, Term, [quoted(true),numbervars(true)]).
- writeq(S,Term):-
- write_term(S, Term, [quoted(true),numbervars(true)]).
- write_canonical(T) :-
- current_output(S),
write_term(S, Term, [quoted(true),ignore_ops(true)]).
- write_canonical(S,T) :-
- write_term(S, Term, [quoted(true),ignore_ops(true)]).
Template write(@stream_or_alias, @Term, @write_options_list)
Errors:
S_or_a is a variable --
instantiation_error
Options is a partial list or a list with an element which is
a variable --
instantiation_error
S_or_a is neither a variable nor a stream term or alias --
domain_error(stream_or_alias, S_or_a)
Options is neither a partial list nor a list --
type_error(list, Options)
An element E of the Options list is neither a variable nor a valid write-option --
domain_error(write_option, E)
S_or_a is not associated with an open stream --
existence_error(stream, S_or_a)
S_or_a is an input stream --
permission_error(output, stream, S_or_a)
S_or_a is associated with a binary stream --
permission_error(output, binary_stream, S_or_a)
These predicates allow the operator table to be altered or inspected.
op(Priority, Op_Specifier, Operator) is true, with the side effect that
- if Priority is 0 then Operator is removed from the
operator table, else
- Operator is added to the Operator table, with priority (lower binds tighter) Priority and associativity determined by
Op_Specifier according to the rules:
Specifier | Type | Associativity
|
fx | prefix | no
|
fy | prefix | yes
|
xf | postfix | no
|
yf | postfix | yes
|
xfx | infix | no
|
yfx | infix | left
|
xfy | infix | right
|
It is forbidden to alter the priority or type of ','.
It is forbidden to have an infix and a postfix operator with the same name,
or two operators with the same class and name.
The initial operator table is given by
Priority | Specifier | Operator(s)
|
1200 | xfx | :- -->
|
1200 | fx | :- ?-
|
1100 | xfy | ;
|
1050 | xfy | ->
|
1000 | xfy | ','
|
900 | fy | \+
|
700 | xfx | = \=
|
700 | xfx | == \== @< @=< @> @>=
|
700 | xfx | =..
|
700 | xfx | is =:= =\= < =< > >=
|
500 | yfx | + - /\ \/
|
400 | yfx | * / // rem mod << >>
|
200 | xfx | **
|
200 | xfy | ^
|
200 | fy | - \
|
Template:op(+integer,+operator_specifier, @atom_or_atom_list)
Errors:
- Priority is a variable --
instantiation_error
- Op_Specifier is a variable --
instantiation_error
- Operator is a partial list or a list with an element
E which is a variable --
instantiation_error
- Priority is neither a variable nor an integer --
type_error(integer, Priority)
- Op_Specifier is neither a variable nor an atom --
type_error(atom, Op_specifier)
- Operator is neither a partial list nor a list nor an atom --
type_error(list, Operator)
- An element E of the Operator list is not an atom --
type_error(atom, E)
- Priority is not between 0 and 1200 inclusive --
domain_error(operator_priority, Priority)
- Op_specifier is not a valid operator specifier --
domain_error(operator_specifier, Op_specifier)
- Operator is ',' --
permission_error(modify, operator, ',')
- An element of the Operator list is ',' --
permission_error(modify, operator, ',')
- Op_specifierOperator would violate the
prohibitions on multiple types --
permission_error(create, operator, Operator)
current_op(Priority, Op_specifier, Operator) is true if
and only if Operator is an operator with properties given by Op_specifier and Priority
Template:current_op(?integer, ?operator_specifier, ?atom)
Errors:
- Priority is neither a variable nor an operator priority --
domain_error(operator_priority, Priority)
- Op_specifier is neither a variable nor an operator specifier --
domain_error(operator_specifier, Op_specifier)
- Operator is neither a variable nor an atom --
type_error(atom, Operator)
char_conversion(In_char, Out_char) is true, with the side effect of adding the pair (In_char, Out_char) to the character conversion table if In_char is not equal to Out_char and removing any pair
(In_char, _) from the table if In_char is equal to
Out_char
.
When the flag char_conversion has the value true, the In_char
will be replaced by Out_char when a term is read using read_term/3.
Template: char_conversion(+character, +character).
Errors:
- In_char is a variable --
instantiation_error
- Out_char is a variable --
instantiation_error
- In_char is neither a variable nor a one character atom --
representation_error(character)
- Out_char is neither a variable nor a one character atom --
representation_error(character)
current_char_conversion(In_char,Out_char) is true if and only if
- In_char is not equal to Out_char, and
- there is an entry in the character conversion table corresponding to the pair (In_char,Out_char)
Template: current_char_conversion(?character, ?character)
Errors:
- In_char is neither a variable nor a one character atom --
representation_error(character)
- Out_char is neither a variable nor a one character atom --
representation_error(character)
\+(Term) is true iff and only if call(Term) is false.
Template:\+(@callable_term)
Errors:
- Term is a variable --
instantiation_error
- Term is neither a variable nor a callable term --
type_error(callable, Term)
once(Term) is true. once/1 is not re-executable.
Template:once(@callable_term)
Errors:
- Term is a variable --
instantiation_error
- Term is neither a variable nor a callable term --
type_error(callable, Term)
repeat is true. It is defined as if:
- repeat.
-
- repeat:-
- repeat.
Template: repeat
Errors: None.
These predicates allow atomic terms to be processed as a string of characters or codes.
atom_length(Atom, Length) is true if and only if the integer
Length equals the number of characters in the name of the atom Atom.
Template: atom_length(+atom, ?integer)
Errors:
- Atom is a variable --
instantiation_error
- Atom is neither a variable nor an atom --
type_error(atom, Atom)
- Length is neither a variable nor an integer --
type_error(integer, Length)
- Length is an integer less than zero --
domain_error(not_less_than_zero, Length))
atom_concat(Start, End, Whole) is true if and only if Whole
is the atom obtained by concatenating the characters of End to those of First. If Whole is instantiated then all decompositions of Whole can be obtained by back-tracking.
Templates:
atom_concat(?atom, ?atom +atom)
atom-concat(+atom, +atom, -atom)
Errors:
- Start and Whole are variables --
instantiation_error
- End and Whole are variables --
instantiation_error
- Start is neither a variable nor an atom --
type_error(atom, Start)
- End is neither a variable nor an atom --
type_error(atom, End)
- Whole is neither a variable nor an atom --
type_error(atom, Whole)
sub_atom(Atom, Before, Length, After, Sub_atom) is true
if and only if Sub_atom is the sub atomof Atom
of length Length that appears
with Before characters preceding it and After characters
following. It is re-executable.
Template:
sub_atom(+atom, ?integer, ?integer, ?integer, ?atom)
Errors:
- Atom is a variable --
instantiation_error
- Atom is neither a variable nor an atom --
type_error(atom, Atom)
- Sub_atom is neither a variable nor an atom --
type_error(atom, Sub_atom)
- Before is neither a variable nor an integer --
type_error(integer, Before)
- Length is neither a variable nor an integer --
type_error(integer, Length)
- After is neither a variable nor an integer --
type_error(integer, After)
- Before is an integer less than zero --
domain_error(not_less_than_zero, Before))
- Length is an integer less than zero --
domain_error(not_less_than_zero, Length))
- After is an integer less than zero --
domain_error(not_less_than_zero, After))
atom_chars(Atom, List) succeeds if and only if List is a list whose elements are the one character atoms that in order make up Atom.
Templates:
atom_chars(+atom, ?character_list)
atom_chars(-atom, +character_list)
Errors:
- Atom is a variable and List is a list or partial
list with an element which is a variable --
instantiation_error
- Atom is neither a variable nor an atom --
type_error(atom, Atom)
- Atom is a variable and List is neither a list nor
a partial list --
type_error(list, List)
- Atom is a variable and an element E of the list
List is neither a variable nor a one-character atom.
a partial list --
type_error(character, E)
atom_codes(Atom, List) succeeds if and only if List is a list whose elements are the character codes that in order correspond to the characters that make up Atom.
Templates:
atom_codes(+atom, ?character_code_list)
atom_codes(-atom, +character_code_list)
Errors:
- Atom is a variable and List is a list or partial
list with an element which is a variable --
instantiation_error
- Atom is neither a variable nor an atom --
type_error(atom, Atom)
- Atom is a variable and List is neither a list nor
a partial list --
type_error(list, List)
- Atom is a variable and an element E of the list
List is neither a variable nor a character-code.
a partial list --
representation_error(character_code)
char_code(Char, Code) succeeds if and only if Code is the
character code that corresponds to the character Char.
Templates:
char_code(+character, ?character_code)
char_code(-character, +character_code)
Errors:
- Char and Code are variables --
instantiation_error
- Char is neither a variable nor a one
character atom atom --
type_error(character, Char)
- Code is neither a variable nor an integer --
type_error(integer, Code)
Code is neither a variable nor a character-code.
representation_error(character_code)
number_chars(Number, List) succeeds if and only if List is a list whose elements are the one character atoms that in order make up Number.
Templates:
number_chars(+number, ?character_list)
number_chars(-number, +character_list)
Errors:
- Number is a variable and List is a list or partial
list with an element which is a variable --
instantiation_error
- Number is neither a variable nor a number --
type_error(number, Number)
- Number is a variable and List is neither a list nor
partial list --
type_error(list, List)
- An element E of the list
List is neither a variable nor a one-character atom.
--
type_error(character, E)
- List is a list of one-char atoms but is not parseable as a number. --
syntax_error(implementation_dependent_atom)
number_codes(Number, CodeList) succeeds if and only if CodeList is a list whose elements are the codes for the one character atoms that in order make up Number.
Templates:
number_codes(+number, ?character_list)
number_codes(-number, +character_list)
Errors:
- Number is a variable and CodeList is a list or partial
list with an element which is a variable --
instantiation_error
- Number is neither a variable nor a number --
type_error(number, Number)
- Number is a variable and CodeList is neither a list nor
a partial list --
type_error(list, CodeList)
- An element E of the list
CodeList is neither a variable nor a character code.
--
representation_error(character_code)
- CodeList is a list of character codes but is not pearseable as a number. --
syntax_error(implementation_dependent_atom)
Conforming Prolog processors are required to support flags whose value can be set or determined by the following predicates.
set_prolog_flag(Flag, Value) sets the Prolog flag Flag
to the value Value. The goal either succeeds or raises an exception.
Template: set_prolog_flag(+flag, @nonvar)
Errors:
- Flag is a variable --
instantiation_error
- Value is a variable --
instantiation_error
- Flag/tt> is neither a variable nor an atom --
type_error(atom, Flag)
- Flag is an atom but an invalid flag for the processor --
domain_error(prolog_flag, Flag)
- Value is inadmissible for Flag --
domain_error(flag_value, Flag + Value)
- Value is admissible for Flag but the flag Flag is not modifiable --
permission_error(modify, flag, Flag)
current_prolog_flag(Flag,Value) is true if and only if Flag is a supported flag and Value is its value. On backtracking the values of all supported flags can be determined.
Template:current_prolog_flag(?flag, ?term)
Errors:
- Flag/tt> is neither a variable nor an atom --
type_error(atom, Flag)
- Flag is an atom but an invalid flag for the processor --
domain_error(prolog_flag, Flag)
These predicates provide means for terminating a Prolog processor.
halt exits the processor and returns to the system that invoked the processor.
Templatehalt.
Errors: None.
halt(X) exits the processor and returns to the system that invoked the processor passing the value of X as a message.
Templatehalt(+int).
Errors:
- X is a variable --
instantiation_error
- X is neither a variable nor an integer --
type_error(integer, X)
A conforming processor is required to support the arithmetic operations specified by the following tables. They conform to the ISO/IEC 10967-1 Language Independent Arithmetic standard.
Types used for the signatures
- I
- Integer
- IF
- Integer or float
- F
- Float
Functor | Signature | Operation
|
(+)/2 | I x I --> I | Addition
|
(+)/2 | F x F --> F | Addition
|
(+)/2 | F x I --> F | Addition
|
(+)/2 | I x F --> F | Addition
|
(-)/2 | I x I --> I | Subtraction
|
(-)/2 | F x F --> F | Subtraction
|
(-)/2 | F x I --> F | Subtraction
|
(-)/2 | I x F --> F | Subtraction
|
(*)/2 | I x I --> I | Multiplication
|
(*)/2 | F x F --> F | Multiplication
|
(*)/2 | F x I --> F | Multiplication
|
(*)/2 | I x F --> F | Multiplication
|
(//)/2 | I x I --> I | Integer Division
|
(/)/2 | I x I --> F | Division
|
(/)/2 | F x F --> F | Division
|
(/)/2 | F x I --> F | Division
|
(/)/2 | I x F --> F | Division
|
(rem)/2 | I x I --> I | Remainder
|
(mod)/2 | I x I --> I | Modulus
|
(-)/1 | I --> I | Negation
|
(-)/1 | F --> F | Negation
|
(abs)/1 | I --> I | Absolute Value
|
(abs)/1 | F --> F | Absolute Value
|
(sign)/1 | I --> I | Sign
|
(sign)/1 | F --> F | SIGN
|
(float_integer_part)/1 | F --> I | integer part
|
(float_fractional_part)/1 | F --> F
| fractional part
|
(float)/1 | I --> F | float coercion.
|
(float)/1 | F --> F | float coercion.
|
(floor)/1 | F --> I | floor.
|
(truncate)/1 | F --> I | truncate.
|
(round)/1 | F --> I | round.
|
(ceiling)/1 | F --> I | ceiling.
|
Errors: It is an
evaluation_error(E) if the value of an expression E is an exceptional value -- float_overflow, int_overflow, underflow, zero_divisor, or undefined
A conforming processor must in addition support the following evaluable functors:
Functor | Template(s) | Name
|
(**)/2 |
'**'(int-exp, int-exp) = float
'**'(float-exp, int-exp) = float
'**'(int-exp, float-exp) = float
'**'(float-exp, float-exp) = float
| Power
|
sin/1 |
sin(float_exp) = float
sin(int_exp) = float
| sine
|
cos/1 |
cos(float_exp) = float
cos(int_exp) = float
| cosine
|
atan/1 |
atan(float_exp) = float
atan(int_exp) = float
| arc tangent
|
exp/1 |
exp(float_exp) = float
exp(int_exp) = float
| exponentiation
|
log/1 |
log(float_exp) = float
log(int_exp) = float
| log
|
sqrt/1 |
sqrt(float_exp) = float
sqrt(int_exp) = float
| square root
|
(>>)/2
| '>>'(int_exp, int_exp) = integer
| bitwise right shift
|
(<<)/2
| '<<'(int_exp, int_exp) = integer
| bitwise left shift
|
(/\)/2
| '/\\'(int-exp, int-exp) = integer
| bit-wise and
|
(\/)/2
| '\\/'(int-exp, int-exp) = integer
| bit-wise or
|
(\)/1
| '\\'(int-exp) = integer
| bitwise complement
|
All of these throw
instantiation_error
when any of their arguments are variables. They throw
type_error(number, VX) ( or type_error(integer, VX)
when an argument X evaluates to an expression which is not a number (resp. an integer). In addition exp/1 can throw evaluation_error(float_overflow), or evaluation_error(underflow), and log/1 can throw
evaluation_error(undefined)
Return to Home Page of the INRIA ISO Prolog Web
Author: J.P.E. Hodgson
Inria Rocquencourt
78153 Le Chesnay Cedex
France
Saint Joseph's University
Philadelphia PA 19131
USA
Last Changed: 1999/04/12 (ISO Date)