1\chapter{Built-in Predicates}			\label{sec:builtin}
2
3\section{Notation of Predicate Descriptions}	\label{sec:preddesc}
4
5We have tried to keep the predicate descriptions clear and concise.
6First, the predicate name is printed in \textbf{bold face}, followed by
7the arguments in \textit{italics}. Arguments are preceded by a
8\jargon{mode indicator}.
9
10\subsection{The argument mode indicator}        \label{sec:argmode}
11
12\index{argument mode indicator}%
13An \jargon{argument mode indicator} gives information about the intended
14direction in which information carried by a predicate argument is supposed
15to flow. Mode indicators (and types) are not a formal part of the Prolog
16language but help in explaining intended semantics to the programmer.
17There is no complete agreement on argument mode indicators in the Prolog
18community.  We use the following definitions:%
19\footnote{These definitions are taken from the \jargon{PlDoc} markup
20	  language description. \jargon{PldDoc} markup is used
21	  for source code markup (as well as for the commenting tool).
22	  The current manual has only one
23	  mode declaration per predicate and therefore predicates
24	  with mode (\chr{+},\chr{-}) and (\chr{-},\chr{+}) are
25	  described as (\chr{?},\chr{?}). The \chr{@}-mode is often
26	  replaced by \\chr{+}.}
27
28\begin{center}
29\begin{tabular}{lp{0.7\linewidth}}
30\hline
31++&	At call time, the argument must be \jargon{ground}, i.e., the
32        argument may not contain any variables that are still unbound. \\
33+ &	At call time, the argument must be instantiated to a term satisfying
34        some (informal) type specification. The argument need not necessarily
35	be ground.
36        For example, the term \exam{[_]} is a list, although its only
37	member is the anonymous variable, which is always unbound (and thus
38        nonground). \\
39- &	Argument is an \emph{output} argument. It may or may not be bound at
40        call-time. If the argument is bound at call time, the goal behaves
41	as if the argument were unbound, and then unified with that term after
42	the goal succeeds. This is what is called being \jargon{steadfast}:
43        instantiation of output arguments at call-time does not change the
44        semantics of the predicate, although optimizations may be performed.
45        For example, the goal \exam{findall(X, Goal, [T])} is good style and
46        equivalent to \exam{findall(X, Goal, Xs), Xs = [T]}%
47        \footnote{The ISO standard dictates that \exam{findall(X, Goal, 1)}
48        raise a \const{type_error} exception, breaking steadfastness. SWI-Prolog
49        does not follow the standard here.} %
50	Note that any \jargon{determinism} specification, e.g., \const{det}, only
51	applies	if the argument is unbound. For the case where the argument is
52        bound or involved in constraints, \const{det} effectively becomes
53        \const{semidet}, and \const{multi} effectively becomes
54        \const{nondet}. \\
55--&	At call time, the argument must be unbound. This is typically used by
56        predicates that	create `something' and return a handle to the created
57        object,	such as open/3, which creates a \jargon{stream}. \\
58? &	At call time, the argument must be bound to a \emph{partial term}
59        (a term which may or may not be ground) satisfying some (informal) type
60        specification. Note that an unbound variable \emph{is} a partial
61        term. Think of the argument as either providing input or accepting
62        output or being used for both input and output.
63        For example, in	\exam{stream_property(S, reposition(Bool))}, the
64        \const{reposition} part of the term provides input and the
65        unbound-at-call-time \arg{Bool} variable accepts output. \\
66: &	Argument is a \jargon{meta-argument}, for example a term that can be
67        called as goal. The predicate is thus a \jargon{meta-predicate}. This
68        flag implies \chr{+}. \\
69@ &	Argument will not be further instantiated than it is at call-time.
70        Typically used for type tests. \\
71! &	Argument contains a mutable structure that may be modified using
72	setarg/3 or nb_setarg/3. \\
73\hline
74\end{tabular}
75\end{center}
76
77See also \secref{metacall} for examples of meta-predicates, and
78\secref{metapred} for mode flags to label meta-predicate arguments in
79module export declarations.
80
81\subsection{Redicate indicators}            \label{sec:predicate_indic}
82
83\index{predicate indicator}%
84Referring to a predicate in running text is done using a
85\jargon{predicate indicator}. The canonical and most generic form of a
86predicate indicator is a term \exam{[<module>:]<name>/<arity>}. The module is
87generally omitted if it is irrelevant (case of a built-in predicate) or if it
88can be inferred from context.
89
90\subsubsection{Non-terminal indicatora}		\label{sec:nonterminal_indic}
91
92\index{non-terminal indicator}%
93Compliant to the ISO standard draft on Definite Clause Grammars (see
94\secref{DCG}), SWI-Prolog also allows for the \jargon{non-terminal
95indicator} to refer to a \jargon{DCG grammar rule}. The non-terminal
96indicator is written as \exam{[<module>]:<name>//<arity>}.
97
98A non-terminal indicator \exam{<name>//<arity>} is understood to be
99equivalent to \exam{<name>/<arity>+2}, regardless of whether or not the
100referenced predicate is defined or can be used as a grammar rule.%
101\footnote{This, however, makes a specific assumption about the
102implementation of DCG rules, namely that DCG rules are preprocessed into
103standard Prolog rules taking two additional arguments, the input list
104and the output list, in accumulator style. This \emph{need} not be true
105in all implementations.}
106The \const{//}-notation can be used in all
107places that traditionally allow for a predicate indicator, e.g., the
108module declaration, spy/1, and dynamic/1.
109
110\subsection{Predicate behaviour and determinism} \label{sec:determinism}
111
112\index{predicate behaviour and determinism}%
113To describe the general behaviour of a predicate, the following vocabulary
114is employed. In source code, structured comments contain the corresponding
115keywords:
116
117\begin{center}
118\begin{tabular}{lp{0.7\linewidth}}
119\hline
120\const{det} &	  A \jargon{deterministic} predicate always succeeds exactly
121                  once and does not leave a choicepoint. \\
122\const{semidet} & A \jargon{semi-deterministic} predicate succeeds at most
123                  once.  If it succeeds it does not leave a choicepoint. \\
124\const{nondet}  & A \jargon{non-deterministic} predicate is the most general
125		  case and no claims are made on the number of solutions (which
126                  may be zero, i.e., the predicate may \jargon{fail}) and whether
127		  or not the predicate leaves an choicepoint on the last
128		  solution. \\
129\const{nondet}  & As \const{nondet}, but succeeds at least once. \\
130\hline
131\end{tabular}
132\end{center}
133
134\section{Character representation}		\label{sec:chars}
135
136In traditional (Edinburgh) Prolog, characters are represented using
137\jargon{character codes}. Character codes are integer indices into
138a specific character set.  Traditionally the character set was 7-bit
139US-ASCII. 8-bit character sets have been allowed for a long time, providing
140support for national character sets, of which iso-latin-1 (ISO 8859-1)
141is applicable to many Western languages.
142
143ISO Prolog introduces three types, two of which are used for characters
144and one for accessing binary streams (see open/4).  These types are:
145
146\begin{itemlist}
147    \item [code]
148A \jargon{character code} is an integer representing a single character.
149As files may use multi-byte encoding for supporting different character
150sets (\idx{utf-8} encoding for example), reading a code from a text file
151is in general not the same as reading a byte.
152    \item [char]
153Alternatively, characters may be represented as
154\jargon{one-character atoms}.  This is a natural representation,
155hiding encoding problems from the programmer as well as providing much
156easier debugging.
157    \item [byte]
158Bytes are used for accessing binary streams.
159\end{itemlist}
160
161In SWI-Prolog, character codes are \emph{always} the Unicode equivalent
162of the encoding. That is, if get_code/1 reads from a stream encoded as
163\const{KOI8-R} (used for the Cyrillic alphabet), it returns the
164corresponding Unicode code points. Similarly, assembling or disassembling
165atoms using atom_codes/2 interprets the codes as Unicode points.  See
166\secref{encoding} for details.
167
168To ease the pain of the two character representations (code and char),
169SWI-Prolog's built-in predicates dealing with character data work as
170flexible as possible: they accept data in any of these formats as long
171as the interpretation is unambiguous. In addition, for output arguments
172that are instantiated, the character is extracted before unification.
173This implies that the following two calls are identical, both testing
174whether the next input character is an \const{a}.
175
176\begin{code}
177peek_code(Stream, a).
178peek_code(Stream, 97).
179\end{code}
180
181The two character representations are handled by a large number of
182built-in predicates, all of which are ISO-compatible. For converting
183between code and character there is char_code/2. For breaking atoms and
184numbers into characters there are atom_chars/2, atom_codes/2,
185number_chars/2 and number_codes/2. For character I/O on streams there are
186get_char/[1,2], get_code/[1,2], get_byte/[1,2], peek_char/[1,2],
187peek_code/[1,2], peek_byte/[1,2], put_code/[1,2], put_char/[1,2] and
188put_byte/[1,2]. The Prolog flag \prologflag{double_quotes} controls how
189text between double quotes is interpreted.
190
191
192\section{Loading Prolog source files}	\label{sec:consulting}
193
194This section deals with loading Prolog source files. A Prolog source
195file is a plain text file containing a Prolog program or part thereof.
196Prolog source files come in three flavours:
197
198\begin{description}
199    \item [ A traditional ] Prolog source file contains Prolog
200clauses and directives, but no \jargon{module declaration} (see
201module/1). They are normally loaded using consult/1 or ensure_loaded/1.
202Currently, a non-module file can only be loaded into a single
203module.\footnote{This limitation may be lifted in the future. Existing
204limitations in SWI-Prolog's source code administration make this
205non-trivial.}
206
207    \item [ A module ] Prolog source file starts with a module
208declaration.  The subsequent Prolog code is loaded into the
209specified module, and only the \jargon{exported} predicates are
210made available to the context loading the module.  Module files
211are normally loaded with use_module/[1,2].  See \chapref{modules}
212for details.
213
214    \item [ An include ] Prolog source file is loaded using
215the include/1 directive, textually including Prolog text into
216another Prolog source.  A file may be included into multiple
217source files and is typically used to share \jargon{declarations}
218such as multifile or dynamic between source files.
219\end{description}
220
221Prolog source files are located using absolute_file_name/3 with
222the following options:
223
224\begin{code}
225locate_prolog_file(Spec, Path) :-
226	absolute_file_name(Spec,
227			   [ file_type(prolog),
228			     access(read)
229			   ],
230			   Path).
231\end{code}
232
233The \term{file_type}{prolog} option is used to determine the extension
234of the file using prolog_file_type/2. The default extension is
235\fileext{pl}.  \arg{Spec} allows for the \jargon{path alias} construct
236defined by absolute_file_name/3.  The most commonly used path alias
237is \term{library}{LibraryFile}.  The example below loads the library
238file \file{ordsets.pl} (containing predicates for manipulating ordered
239sets).
240
241\begin{code}
242:- use_module(library(ordsets)).
243\end{code}
244
245SWI-Prolog recognises grammar rules (\idx{DCG}) as defined in
246\cite{Clocksin:87}. The user may define additional compilation of the
247source file by defining the dynamic multifile predicates
248term_expansion/2, term_expansion/4, goal_expansion/2 and
249goal_expansion/4. It is not allowed to use assert/1, retract/1 or any
250other database predicate in term_expansion/2 other than for local
251computational purposes.\footnote{It does work for normal loading, but
252not for qcompile/1.} Code that needs to create additional clauses must
253use compile_aux_clauses/1. See \pllib{library(apply_macros)} for an
254example.
255
256A \jargon{directive} is an instruction to the compiler. Directives are
257used to set (predicate) properties (see \secref{declare}), set flags
258(see set_prolog_flag/2) and load files (this section).  Directives are
259terms of the form \mbox{\texttt{:-} <term>.}.  Here are some examples:
260
261\begin{code}
262:- use_module(library(lists)).
263:- dynamic
264	store/2.		% Name, Value
265\end{code}
266
267The directive initialization/1 can be used to run arbitrary Prolog
268goals.  The specified goal is started \emph{after} loading the file
269in which it appears has completed.
270
271SWI-Prolog compiles code as it is read from the file, and directives are
272executed as \jargon{goals}. This implies that directives may call any
273predicate that has been defined before the point where the directive
274appears. It also accepts \mbox{\texttt{?-} <term>.} as a synonym.
275
276\index{reconsult}%
277SWI-Prolog does not have a separate \nopredref{reconsult}{1} predicate.
278Reconsulting is implied automatically by the fact that a file is
279consulted which is already loaded.
280
281Advanced topics are handled in subsequent sections: mutually dependent
282files (\secref{depload}), multithreaded loading (\secref{mtload}) and
283reloading running code (\secref{loadrunningcode}).
284
285The core of the family of loading predicates is load_files/2.  The predicates
286consult/1, ensure_loaded/1, use_module/1, use_module/2 and reexport/1 pass the
287file argument directly to load_files/2 and pass additional options as expressed
288in the \tabref{loadpreds}:
289
290\begin{table}
291\begin{center}
292\begin{tabular}{lccc}
293\hline
294\bf Predicate	& \bf if	     & \bf must_be_module & \bf import \\
295\hline
296consult/1	& \const{true}	     & \const{false} & all \\
297ensure_loaded/1	& \const{not_loaded} & \const{false} & all \\
298use_module/1	& \const{not_loaded} & \const{true}  & all\\
299use_module/2	& \const{not_loaded} & \const{true}  & specified \\
300reexport/1	& \const{not_loaded} & \const{true}  & all \\
301reexport/2	& \const{not_loaded} & \const{true}  & specified \\
302\hline
303\end{tabular}
304\end{center}
305    \caption{Properties of the file-loading predicates. The \textit{import}
306	     column specifies what is imported if the loaded file is a module
307	     file.}
308    \label{tab:loadpreds}
309\end{table}
310
311\begin{description}
312    \predicate{load_files}{1}{:Files}
313Equivalent to \term{load_files}{Files, []}.  Same as consult/1,
314See load_files/2 for supported options.
315    \predicate{load_files}{2}{:Files, +Options}
316The predicate load_files/2 is the parent of all the other loading
317predicates except for include/1. It currently supports a subset
318of the options of Quintus load_files/2. \arg{Files} is either
319a single source file or a list of source files. The specification for a
320source file is handed to absolute_file_name/2. See this predicate for
321the supported expansions. \arg{Options} is a list of options using the
322format \arg{OptionName}(\arg{OptionValue}).
323
324The following options are currently supported:
325
326\begin{description}
327    \termitem{autoload}{Bool}
328If \const{true} (default \const{false}), indicate that this load is a
329\jargon{demand} load. This implies that, depending on the setting of the
330Prolog flag \prologflag{verbose_autoload}, the load action is printed at
331level \const{informational} or \const{silent}.  See also print_message/2
332and current_prolog_flag/2.
333
334    \termitem{check_script}{Bool}
335If \const{false} (default \const{true}), do not check the first
336character to be \chr{#} and skip the first line when found.
337
338    \termitem{derived_from}{File}
339Indicate that the loaded file is derived from \arg{File}.  Used by
340make/0 to time-check and load the original file rather than the derived
341file.
342
343    \termitem{dialect}{+Dialect}
344Load \arg{Files} with enhanced compatibility with the target Prolog
345system identified by \arg{Dialect}.  See expects_dialect/1 and
346\secref{dialect} for details.
347
348    \termitem{encoding}{Encoding}
349Specify the way characters are encoded in the file.  Default is taken
350from the Prolog flag \prologflag{encoding}.  See \secref{encoding} for
351details.
352
353    \termitem{expand}{Bool}
354If \const{true}, run the filenames through expand_file_name/2 and load
355the returned files.  Default is \const{false}, except for consult/1
356which is intended for interactive use.  Flexible location of files
357is defined by file_search_path/2.
358
359    \termitem{format}{+Format}
360Used to specify the file format if data is loaded from a stream using
361the \term{stream}{Stream} option. Default is \const{source}, loading
362Prolog source text.  If \const{qlf}, load QLF data (see qcompile/1).
363
364    \termitem{if}{Condition}
365Load the file only if the specified condition is satisfied. The value
366\const{true} loads the file unconditionally, \const{changed} loads the
367file if it was not loaded before or has been modified since it was
368loaded the last time, and \const{not_loaded} loads the file if it was not
369loaded before.
370
371    \termitem{imports}{Import}
372Specify what to import from the loaded module. The default for
373use_module/1 is \const{all}. \arg{Import} is passed from the second
374argument of use_module/2. Traditionally it is a list of predicate
375indicators to import. As part of the SWI-Prolog/YAP integration, we also
376support \arg{Pred} as \arg{Name} to import a predicate under another
377name. Finally, \arg{Import} can be the term \term{except}{Exceptions},
378where \arg{Exceptions} is a list of predicate indicators that specify
379predicates that are \emph{not} imported or \arg{Pred} as \arg{Name}
380terms to denote renamed predicates. See also reexport/2 and
381use_module/2.%
382	\bug{\arg{Name}/\arg{Arity} as \arg{NewName} is currently
383	     implemented using a \jargon{link clause}.  This harms
384	     efficiency and does not allow for querying the relation
385	     through predicate_property/2.}
386
387If \arg{Import} equals \const{all}, all operators are imported as well.
388Otherwise, operators are \emph{not} imported. Operators can be imported
389selectively by adding terms \term{op}{Pri,Assoc,Name} to the
390\arg{Import} list. If such a term is encountered, all exported
391operators that unify with this term are imported. Typically, this
392construct will be used with all arguments unbound to import all
393operators or with only \arg{Name} bound to import a particular operator.
394
395    \termitem{modified}{TimeStamp}
396Claim that the source was loaded at \arg{TimeStamp} without
397checking the source.  This option is intended to be used together with
398the \term{stream}{Input} option, for example after extracting the time
399from an HTTP server or database.
400
401    \termitem{module}{+Module}
402Load the indicated file into the given module, overruling the module
403name specified in the \exam{:- module(Name, ...)} directive. This
404currently serves two purposes: (1) allow loading two module files that
405specify the same module	into the same process and force and (2): force
406loading source code in a specific module, even if the code provides its
407own module name.  Experimental.
408
409    \termitem{must_be_module}{Bool}
410If \const{true}, raise an error if the file is not a module file.  Used by
411use_module/[1,2].
412
413    \termitem{qcompile}{Atom}
414How to deal with quick-load-file compilation by qcompile/1.  Values are:
415
416    \begin{description}
417	\termitem{never}{}
418Default.  Do not use qcompile unless called explicitly.
419	\termitem{auto}{}
420Use qcompile for all writeable files.  See comment below.
421	\termitem{large}{}
422Use qcompile if the file is `large'. Currently, files larger than
423100~Kbytes are considered large.
424        \termitem{part}{}
425If load_files/2 appears in a directive of a file that is compiled
426into Quick Load Format using qcompile/1, the contents of the argument
427files are included in the \fileext{qlf} file instead of the loading
428directive.
429    \end{description}
430
431If this option is not present, it uses the value of the Prolog
432flag \prologflag{qcompile} as default.
433
434    \termitem{optimise}{+Boolean}
435Explicitly set the optimization for compiling this module.  See
436\prologflag{optimise}.
437
438    \termitem{redefine_module}{+Action}
439Defines what to do if a file is loaded that provides a module that is
440already loaded from another file. \arg{Action} is one of \const{false}
441(default), which prints an error and refuses to load the file, or
442\const{true}, which uses unload_file/1 on the old file and then proceeds
443loading the new file. Finally, there is \const{ask}, which starts
444interaction with the user. \const{ask} is only provided if the
445stream \const{user_input} is associated with a terminal.
446
447    \termitem{reexport}{Bool}
448If \const{true} re-export the imported predicate.  Used by reexport/1
449and reexport/2.
450
451    \termitem{register}{Bool}
452If \const{false}, do not register the load location and options.  This
453option is used by make/0 and \libpredref{load_hotfixes}{1} to avoid
454polluting the load-context database. See source_file_property/2.
455
456    \termitem{sandboxed}{Bool}
457Load the file in \jargon{sandboxed} mode.  This option controls the
458flag \prologflag{sandboxed_load}. The only meaningful value for
459\arg{Bool} is \const{true}.  Using \const{false} while the Prolog
460flag is set to \const{true} raises a permission error.
461
462    \termitem{scope_settings}{Bool}
463Scope style_check/1 and expects_dialect/1 to the file and files loaded
464from the file after the directive.  Default is \const{true}.  The system
465and user initialization files (see \cmdlineoption{-f} and
466\cmdlineoption{-F}) are loading with \term{scope_settings}{false}.
467
468    \termitem{silent}{Bool}
469If \const{true}, load the file without printing a message. The
470specified value is the default for all files loaded as a result of
471loading the specified files. This option writes the Prolog flag
472\prologflag{verbose_load} with the negation of \arg{Bool}.
473
474    \termitem{stream}{Input}
475This SWI-Prolog extension compiles the data from the stream
476\arg{Input}.  If this option is used, \arg{Files} must be a single atom
477which is used to identify the source location of the loaded clauses as
478well as to remove all clauses if the data is reconsulted.
479
480This option is added to allow compiling from non-file locations such as
481databases, the web, the \jargon{user} (see consult/1) or other servers.
482It can be combined with \term{format}{qlf} to load QLF data from a
483stream.
484\end{description}
485
486The load_files/2 predicate can be hooked to load other data or data from
487objects other than files.  See prolog_load_file/2 for a description and
488\pllib{http/http_load} for an example. All hooks for load_files/2 are
489documented in \secref{loadfilehook}.
490
491    \predicate{consult}{1}{:File}
492Read \arg{File} as a Prolog source file. Calls to consult/1 may be
493abbreviated by just typing a number of filenames in a list. Examples:
494
495\begin{center}\begin{tabular}{ll}
496\exam{?- consult(load).}     & \% consult \file{load} or \file{load.pl} \\
497\exam{?- [library(lists)].}  & \% load library lists \\
498\exam{?- [user].}	     & \% Type program on the terminal \\
499\end{tabular}\end{center}
500
501The predicate consult/1 is equivalent to \verb$load_files(File, [])$,
502except for handling the special file \const{user}, which reads clauses
503from the terminal. See also the \term{stream}{Input} option of
504load_files/2. Abbreviation using \verb$?- [file1,file2].$ does
505\emph{not} work for the empty list (\verb$[]$). This facility is
506implemented by defining the list as a predicate. Applications may
507only rely on using the list abbreviation at the Prolog toplevel and
508in directives.
509
510    \predicate{ensure_loaded}{1}{:File}
511If the file is not already loaded, this is equivalent to consult/1.
512Otherwise, if the file defines a module, import all public predicates.
513Finally, if the file is already loaded, is not a module file, and the
514context module is not the global user module, ensure_loaded/1 will
515call consult/1.
516
517With this semantics, we hope to get as close as possible to the clear
518semantics without the presence of a module system.  Applications using
519modules should consider using use_module/[1,2].
520
521Equivalent to \verb$load_files(Files, [if(not_loaded)]).$%
522	\footnote{On older versions the condition used to be
523		  \exam{if(changed)}. Poor time management on some
524		  machines or copying often caused problems. The make/0
525		  predicate deals with updating the running system after
526		  changing the source code.}
527
528    \predicate[ISO]{include}{1}{+File}
529Textually include the content of \arg{File} at the position where the
530\jargon{directive} \exam{:- include(File).} appears. The include
531construct is only honoured if it appears as a directive in a
532source file. \jargon{Textual} include (similar to C/C++ \#include) is
533obviously useful for sharing declarations such as dynamic/1 or
534multifile/1 by including a file with directives from multiple files that
535use these predicates.
536
537Textually including files that contain \emph{clauses} is less obvious.
538Normally, in SWI-Prolog, clauses are \emph{owned} by the file in which
539they are defined. This information is used to \emph{replace} the old
540definition after the file has been modified and is reloaded by, e.g.,
541make/0. As we understand it, include/1 is intended to include the same
542file multiple times. Including a file holding clauses multiple times
543into the same module is rather meaningless as it just duplicates the
544same clauses. Including a file holding clauses in multiple modules
545does not suffer from this problem, but leads to multiple equivalent
546\emph{copies} of predicates. Using use_module/1 can achieve the same
547result while \emph{sharing} the predicates.
548
549If include/1 is used to load files holding clauses, and if these files
550are loaded only once, then these include/1 directives can be replaced by
551other predicates (such as consult/1). However, there are several cases
552where either include/1 has no alternative, or using any alternative also
553requires other changes. An example of the former is using include/1 to
554share directives. An example of the latter are cases where clauses of
555different predicates are distributed over multiple files: If these files
556are loaded with include/1, the directive discontiguous/1 is appropriate,
557whereas if they are consulted, one must use the directive multifile/1.
558
559To accommodate included files holding clauses, SWI-Prolog distinguishes
560between the source location of a clause (in this case the included
561file) and the \jargon{owner} of a clause (the file that includes the
562file holding the clause).  The source location is used by, e.g., edit/1,
563the graphical tracer, etc., while the owner is used to determine which
564clauses are removed if the file is modified.  Relevant information is
565found with the following predicates:
566
567    \begin{itemize}
568
569    \item source_file/2 describes the owner relation.
570    \item predicate_property/2 describes the source location (of the
571          first clause).
572    \item clause_property/2 provides access to both source and ownership.
573    \item source_file_property/2 can be used to query include relationships
574          between files.
575    \end{itemize}
576
577    \predicate{require}{1}{+Predicates}
578Declare that this file/module requires the specified predicates to be
579defined ``with their commonly accepted definition''. \arg{Predicates} is
580either a list of predicate indicators or a \jargon{comma-list} of
581predicate indicators. First, all built-in predicates are removed from
582the set. The remaining predicates are searched using the library index
583used for autoloading and mapped to a set of autoload/2 directives. This
584implies that the targets will be loaded lazily if autoloading is not
585completely disabled and loaded using use_module/2 otherwise. See
586\prologflag{autoload}.
587
588The require/1 directive provides less control over the exact nature and
589location of the predicate. As autoload/2, it prevents a local definition
590of this predicate. As SWI-Prolog guarantees that the set of built-in
591predicates and predicates available for autoloading is unambiguous
592(i.e., has no duplicates) the specification is unambiguous. It provides
593four advantages over autoload/2: (1) the user does not have to remember
594the exact library, (2) the directive can be supported in other Prolog
595systems\footnote{SICStus provides it}, providing compatibility despite
596differences in library and built-in predicate organization, (3) it is
597robust against changes to the SWI-Prolog libraries and (4) it is less
598typing.
599
600    \predicate{encoding}{1}{+Encoding}
601This directive can appear anywhere in a source file to define how
602characters are encoded in the remainder of the file.  It can be
603used in files that are encoded with a superset of US-ASCII,
604currently UTF-8 and ISO Latin-1.  See also \secref{encoding}.
605
606    \predicate{make}{0}{}
607Consult all source files that have been changed since they were
608consulted.  It checks \arg{all} loaded source files: files loaded into a
609compiled state using \exam{pl -c \ldots} and files loaded using consult/1
610or one of its derivatives. The predicate make/0 is called after
611edit/1, automatically reloading all modified files.  If the user uses
612an external editor (in a separate window), make/0 is normally used to
613update the program after editing.  In addition, make/0 updates the
614autoload indices (see \secref{autoload}) and runs list_undefined/0
615from the \pllib{check} library to report on undefined predicates.
616
617    \predicate{library_directory}{1}{?Atom}
618Dynamic predicate used to specify library directories. Defaults to
619\term{app_config}{lib} (see file_search_path/2) and the system's library
620(in this order) are defined. The user may add library directories using
621assertz/1, asserta/1 or remove system defaults using retract/1.
622Deprecated. New code should use file_search_path/2.
623
624    \predicate{file_search_path}{2}{+Alias, -Path}
625Dynamic multifile hook predicate used to specify `path aliases'. This
626hook is called by absolute_file_name/3 to search files specified as
627\term{Alias}{Name}, e.g., \term{library}{lists}. This feature is best
628described using an example. Given the definition:
629
630\begin{code}
631file_search_path(demo, '/usr/lib/prolog/demo').
632\end{code}
633
634the file specification \file{demo(myfile)} will be expanded to
635\file{/usr/lib/prolog/demo/myfile}. The second argument of
636file_search_path/2 may be another alias.
637
638Below is the initial definition of the file search path.  This path
639implies \file{swi(<Path>)} and refers to a file in the SWI-Prolog home
640directory.  The alias \file{foreign(<Path>)} is intended for storing
641shared libraries (\fileext{so} or \fileext{DLL} files).  See also
642use_foreign_library/1.
643
644\begin{code}
645user:file_search_path(library, X) :-
646    library_directory(X).
647user:file_search_path(swi, Home) :-
648    current_prolog_flag(home, Home).
649user:file_search_path(foreign, swi(ArchLib)) :-
650    current_prolog_flag(arch, Arch),
651    atom_concat('lib/', Arch, ArchLib).
652user:file_search_path(foreign, swi(lib)).
653user:file_search_path(path, Dir) :-
654    getenv('PATH', Path),
655    (   current_prolog_flag(windows, true)
656    ->  atomic_list_concat(Dirs, (;), Path)
657    ;   atomic_list_concat(Dirs, :, Path)
658    ),
659    member(Dir, Dirs).
660user:file_search_path(user_app_data, Dir) :-
661    '$xdg_prolog_directory'(data, Dir).
662user:file_search_path(common_app_data, Dir) :-
663    '$xdg_prolog_directory'(common_data, Dir).
664user:file_search_path(user_app_config, Dir) :-
665    '$xdg_prolog_directory'(config, Dir).
666user:file_search_path(common_app_config, Dir) :-
667    '$xdg_prolog_directory'(common_config, Dir).
668user:file_search_path(app_data, user_app_data('.')).
669user:file_search_path(app_data, common_app_data('.')).
670user:file_search_path(app_config, user_app_config('.')).
671user:file_search_path(app_config, common_app_config('.')).
672\end{code}
673
674\index{XDG,directories}%
675The \nopredref{'\$xdg_prolog_directory'}{2} uses either the
676\href{https://wiki.archlinux.org/index.php/XDG_Base_Directory}{XDG Base
677Directory} or win_folder/2 on Windows. On Windows, user config is mapped
678to roaming appdata (CSIDL_APPDATA), user data to the non-roaming
679(CSIDL_LOCAL_APPDATA) and common data to (CSIDL_COMMON_APPDATA).
680
681The file_search_path/2 expansion is used by all loading predicates as
682well as by absolute_file_name/[2,3].
683
684The Prolog flag \prologflag{verbose_file_search} can be set to \const{true}
685to help debugging Prolog's search for files.
686
687    \predicate[nondet]{expand_file_search_path}{2}{+Spec, -Path}
688Unifies \arg{Path} with all possible expansions of the filename
689specification \arg{Spec}.  See also absolute_file_name/3.
690
691    \predicate{prolog_file_type}{2}{?Extension, ?Type}
692This dynamic multifile predicate defined in module \module{user}
693determines the extensions considered by file_search_path/2.
694\arg{Extension} is the filename extension without the leading dot, and
695\arg{Type} denotes the type as used by the \term{file_type}{Type}
696option of file_search_path/2.  Here is the initial definition of
697prolog_file_type/2:
698
699\begin{code}
700user:prolog_file_type(pl,	prolog).
701user:prolog_file_type(Ext,	prolog) :-
702	current_prolog_flag(associate, Ext),
703	Ext \== pl.
704user:prolog_file_type(qlf,	qlf).
705user:prolog_file_type(Ext,	executable) :-
706	current_prolog_flag(shared_object_extension, Ext).
707\end{code}
708
709Users can add extensions for Prolog source files to avoid conflicts
710(for example with \program{perl}) as well as to be compatible with
711another Prolog implementation. We suggest using \fileext{pro} for
712avoiding conflicts with \program{perl}. Overriding the system
713definitions can stop the system from finding libraries.
714
715    \predicate{source_file}{1}{?File}
716True if \arg{File} is a loaded Prolog source file.  \arg{File} is
717the absolute and canonical path to the source file.
718
719    \predicate{source_file}{2}{:Pred, ?File}
720True if the predicate specified by \arg{Pred} is owned by file
721\arg{File}, where \arg{File} is an absolute path name (see
722absolute_file_name/2). Can be used with any instantiation pattern, but
723the database only maintains the source file for each predicate. If
724\arg{Pred} is a \jargon{multifile} predicate this predicate succeeds for
725all files that contribute clauses to \arg{Pred}.\footnote{The current
726implementation performs a linear scan through all clauses to establish
727this set of files.} See also clause_property/2. Note that the relation
728between files and predicates is more complicated if include/1 is used.
729The predicate describes the \jargon{owner} of the predicate. See
730include/1 for details.
731
732    \predicate{source_file_property}{2}{?File, ?Property}
733True when \arg{Property} is a property of the loaded file \arg{File}.
734If \arg{File} is non-var, it can be a file specification that is valid
735for load_files/2.  Defined properties are:
736
737    \begin{description}
738	\termitem{derived_from}{Original, OriginalModified}
739\arg{File} was generated from the file \arg{Original}, which was
740last modified at time \arg{OriginalModified} at the time it was loaded.
741This property is available if \arg{File} was loaded using the
742\term{derived_from}{Original} option to load_files/2.
743
744	\termitem{includes}{IncludedFile, IncludedFileModified}
745\arg{File} used include/1 to include \arg{IncludedFile}. The
746last modified time of \arg{IncludedFile} was \arg{IncludedFileModified}
747at the time it was included.
748
749	\termitem{included_in}{MasterFile, Line}
750\arg{File} was included into \arg{MasterFile} from line \arg{Line}. This
751is the inverse of the \const{includes} property.
752
753	\termitem{load_context}{Module, Location, Options}
754\arg{Module} is the module into which the file was loaded. If \arg{File}
755is a module, this is the module into which the exports are imported.
756Otherwise it is the module into which the clauses of the non-module
757file are loaded.  \arg{Location} describes the file location from which
758the file was loaded.  It is either a term <file>:<line> or the atom
759\const{user} if the file was loaded from the terminal or another unknown
760source. \arg{Options} are the options passed to load_files/2. Note that
761all predicates to load files are mapped to load_files/2, using the
762option argument to specify the exact behaviour.
763
764	\termitem{load_count}{-Count}
765\arg{Count} is the number of times the file have been loaded, i.e.,
7661 (one) if the file has been loaded once.
767
768	\termitem{modified}{Stamp}
769File modification time when \arg{File} was loaded.  This is used by
770make/0 to find files whose modification time is different from when
771it was loaded.
772
773	\termitem{source}{Source}
774One of \const{file} if the source was loaded from a file,
775\const{resource} if the source was loaded from a resource or
776\const{state} if the file was included in the saved state.
777
778	\termitem{module}{Module}
779\arg{File} is a module file that declares the module \arg{Module}.
780
781	\termitem{number_of_clauses}{Count}
782\arg{Count} is the number of clauses associated with \arg{File}.
783Note that clauses loaded from included files are counted as part
784of the main file.
785
786	\termitem{reloading}{}
787Present if the file is currently being \textbf{re}loaded.
788    \end{description}
789
790    \predicate[semidet]{exists_source}{1}{+Source}
791True if \arg{Source} (a term valid for load_files/2) exists. Fails
792without error if this is not the case. The predicate is intended to be
793used with \jargon{conditional compilation} (see
794\secref{conditionalcompilation}  For example:
795
796\begin{code}
797:- if(exists_source(library(error))).
798:- use_module_library(error).
799:- endif.
800\end{code}
801
802The implementation uses absolute_file_name/3 using
803\term{file_type}{prolog}.
804
805    \predicate[semidet]{exists_source}{2}{+Source, -File}
806As exists_source/1, binding \arg{File} to an atom describing the full
807absolute path to the source file.
808
809    \predicate{unload_file}{1}{+File}
810Remove all clauses loaded from \arg{File}.  If \arg{File} loaded a
811module, clear the module's export list and disassociate it from the
812file.  \arg{File} is a canonical filename or a file indicator that is
813valid for load_files/2.
814
815This predicate should be used with care. The multithreaded nature of
816SWI-Prolog makes removing static code unsafe. Attempts to do this should
817be reserved for development or situations where the application can
818guarantee that none of the clauses associated to \arg{File} are active.
819
820    \predicate{prolog_load_context}{2}{?Key, ?Value}
821Obtain context information during compilation.  This predicate can be
822used from directives appearing in a source file to get information about
823the file being loaded as well as by the term_expansion/2 and
824goal_expansion/2 hooks. See also source_location/2 and if/1. The
825following keys are defined:
826
827\begin{center}
828\begin{tabular}{|l|p{\linewidth-35mm}|}
829\hline
830\bf Key               & \bf Description \\
831\hline
832\const{directory}     & Directory in which \const{source} lives \\
833\const{dialect}	      & Compatibility mode.  See expects_dialect/1. \\
834\const{file}          & Similar to \const{source}, but returns the file
835			being included when called while an include file
836			is being processed \\
837\const{module}        & Module into which file is loaded \\
838\const{reload}	      & \const{true} if the file is being
839			\textbf{re}loaded.  Not present on first load \\
840\const{script}	      & Boolean that indicates whether the file is
841			loaded as a script file (see
842			\cmdlineoption{-s}) \\
843\const{source}        & File being loaded.  If the system is processing an
844			included file, the value is the \emph{main} file.
845			Returns the original Prolog file when loading a
846			\fileext{qlf} file. \\
847\const{stream}        & Stream identifier (see current_input/1) \\
848\const{term_position} & Start position of last term read.  See also
849			stream_property/2 (\const{position} property and
850			stream_position_data/3.\footnote{Up to version
851			7.1.22, the position term carried fake data
852			except for the \const{line_count} and had
853			\textbf{five} arguments, where the position
854			property of a stream only has \textbf{four}.} \\
855\const{term}	      & Term being expanded by expand_term/2. \\
856\const{variable_names}& A list of `\arg{Name} = \arg{Var}' of the last
857			term read.  See read_term/2 for details. \\
858\hline
859\end{tabular}
860\end{center}
861
862The \const{directory} is commonly used to add rules to file_search_path/2,
863setting up a search path for finding files with absolute_file_name/3.
864For example:
865
866\begin{code}
867:- dynamic user:file_search_path/2.
868:- multifile user:file_search_path/2.
869
870:- prolog_load_context(directory, Dir),
871   asserta(user:file_search_path(my_program_home, Dir)).
872
873    ...
874    absolute_file_name(my_program_home('README.TXT'), ReadMe,
875		       [ access(read) ]),
876    ...
877\end{code}
878
879    \predicate{source_location}{2}{-File, -Line}
880If the last term has been read from a physical file (i.e., not from the
881file \const{user} or a string), unify \arg{File} with an absolute path to
882the file and \arg{Line} with the line number in the file. New code
883should use prolog_load_context/2.
884
885    \predicate{at_halt}{1}{:Goal}
886Register \arg{Goal} to be run from PL_cleanup(), which is called when
887the system halts. The hooks are run in the reverse order they were
888registered (FIFO). Success or failure executing a hook is ignored. If
889the hook raises an exception this is printed using print_message/2. An
890attempt to call halt/[0,1] from a hook is ignored. Hooks may call
891cancel_halt/1, causing halt/0 and PL_halt(0) to print a message
892indicating that halting the system has been cancelled.
893
894    \predicate{cancel_halt}{1}{+Reason}
895If this predicate is called from a hook registered with at_halt/1,
896halting Prolog is cancelled and an informational message is printed
897that includes \arg{Reason}.  This is used by the development tools
898to cancel halting the system if the editor has unsaved data and the
899user decides to cancel.
900
901    \directive[ISO]{initialization}{1}{:Goal}
902Call \arg{Goal} \emph{after} loading the source file in which this
903directive appears has been completed. In addition, \arg{Goal} is
904executed if a saved state created using qsave_program/1 is restored.
905
906The ISO standard only allows for using \exam{:- Term} if \arg{Term} is a
907\emph{directive}. This means that arbitrary goals can only be called
908from a directive by means of the initialization/1 directive. SWI-Prolog
909does not enforce this rule.
910
911The initialization/1 directive must be used to do program initialization
912in saved states (see qsave_program/1). A saved state contains the
913predicates, Prolog flags and operators present at the moment the state
914was created.  Other resources (records, foreign resources, etc.) must
915be recreated using initialization/1 directives or from the entry goal
916of the saved state.
917
918Up to SWI-Prolog 5.7.11, \arg{Goal} was executed immediately rather than
919after loading the program text in which the directive appears as
920dictated by the ISO standard. In many cases the exact moment of
921execution is irrelevant, but there are exceptions. For example,
922load_foreign_library/1 must be executed immediately to make the loaded
923foreign predicates available for exporting. SWI-Prolog now provides the
924directive use_foreign_library/1 to ensure immediate loading as well as
925loading after restoring a saved state. If the system encounters a
926directive \exam{:- initialization(load_foreign_library(...))}, it will
927load the foreign library immediately and issue a warning to update your
928code. This behaviour can be extended by providing clauses for the
929multifile hook predicate \term{prolog:initialize_now}{Term, Advice},
930where \arg{Advice} is an atom that gives advice on how to resolve the
931compatibility issue.
932
933    \predicate{initialization}{2}{:Goal, +When}
934Similar to initialization/1, but allows for specifying when \arg{Goal}
935is executed while loading the program text:
936
937\begin{description}
938    \termitem{now}{} Execute \arg{Goal} immediately.
939
940    \termitem{after_load}{} Execute \arg{Goal} after loading the
941program text in which the directive appears. This is the same as
942initialization/1.
943
944    \termitem{prepare_state}{}
945Execute \arg{Goal} as part of qsave_program/2.  This hook can be
946used for example to eagerly execute initialization that is normally
947done lazily on first usage.
948
949    \termitem{restore_state}{}
950Do not execute \arg{Goal} while loading the program, but \emph{only}
951when restoring a saved state.\footnote{Used to be called
952\const{restore}. \const{restore} is still accepted for backward
953compatibility.}
954
955    \termitem{program}{}
956Execute \arg{Goal} once after executing the \cmdlineoption{-g} goals
957at program startup. Registered goals are executed in the order
958encountered and a failure or exception causes the Prolog to exit with
959non-zero exit status.  These goals are \emph{not} executed if the
960\cmdlineoption{-l} is given to merely \emph{load} files.  In that case
961they may be executed explicitly using initialize/0. See also
962\secref{plscript}.
963
964    \termitem{main}{}
965When Prolog starts, the last goal registered using
966\term{initialization}{Goal, main} is executed as main goal. If
967\arg{Goal} fails or raises an exception, the process terminates with
968non-zero exit code. If not explicitly specified using the
969\cmdlineoption{-t} the \jargon{toplevel goal} is set to halt/0, causing
970the process to exit with status 0. An explicitly specified toplevel is
971executed normally. This implies that \exam{-t prolog} causes the
972application to start the normal interactive toplevel after completing
973\arg{Goal}.  See also the Prolog flag \prologflag{toplevel_goal} and
974\secref{plscript}.
975\end{description}
976
977    \predicate[det]{initialize}{0}{}
978Run all initialization goals registered using
979\term{initialization}{Goal, program}. Raises an error
980\term{initialization_error}{Reason, Goal, File:Line} if \arg{Goal}
981fails or raises an exception.  \arg{Reason} is \const{failed} or
982the exception raised.
983
984    \predicate{compiling}{0}{}
985True if the system is compiling source files with the \cmdlineoption{-c}
986option or qcompile/1 into an intermediate code file. Can be used to
987perform conditional code optimisations in term_expansion/2 (see also the
988\cmdlineoption{-O} option) or to omit execution of directives during
989compilation.
990\end{description}
991
992
993\subsection{Conditional compilation and program transformation}
994\label{sec:progtransform}
995
996\index{transformation,of program}%
997ISO Prolog defines no way for program transformations such as macro
998expansion or conditional compilation. Expansion through term_expansion/2
999and expand_term/2 can be seen as part of the de-facto standard.  This
1000mechanism can do arbitrary translation between valid Prolog terms read
1001from the source file to Prolog terms handed to the compiler.  As
1002term_expansion/2 can return a list, the transformation does not need
1003to be term-to-term.
1004
1005Various Prolog dialects provide the analogous goal_expansion/2 and
1006expand_goal/2 that allow for translation of individual body terms,
1007freeing the user of the task to disassemble each clause.
1008
1009\begin{description}
1010    \predicate{term_expansion}{2}{+Term1, -Term2}
1011Dynamic and multifile predicate, normally not defined. When defined by
1012the user all terms read during consulting are given to this
1013predicate. If the predicate succeeds Prolog will assert \arg{Term2} in
1014the database rather than the read term (\arg{Term1}). \arg{Term2} may be
1015a term of the form \exam{?- Goal.} or \exam{:- Goal}. \arg{Goal} is
1016then treated as a directive. If \arg{Term2} is a list, all terms of the
1017list are stored in the database or called (for directives). If
1018\arg{Term2} is of the form below, the system will assert \arg{Clause}
1019and record the indicated source location with it:
1020
1021\begin{quote}
1022\mbox{\tt '\$source_location'(<File>, <Line>):<Clause>}
1023\end{quote}
1024
1025When compiling a module (see \chapref{modules} and the directive module/2),
1026expand_term/2 will first try term_expansion/2 in the module being
1027compiled to allow for term expansion rules that are local to a module.
1028If there is no local definition, or the local definition fails to
1029translate the term, expand_term/2 will try term_expansion/2 in module
1030\module{user}. For compatibility with SICStus and Quintus Prolog, this
1031feature should not be used. See also expand_term/2, goal_expansion/2 and
1032expand_goal/2.
1033
1034It is possible to act on the beginning and end of a file by expanding
1035the terms \const{begin_of_file} and \const{end_of_file}. The latter is
1036supported by most Prolog systems that support term expansion as
1037read_term/3 returns \const{end_of_file} on reaching the end of the
1038input. Expanding \const{begin_of_file} may be used to initialise the
1039compilation, for example base on the file name extension. It was added
1040in SWI-Prolog 8.1.1.
1041
1042    \predicate{expand_term}{2}{+Term1, -Term2}
1043This predicate is normally called by the compiler on terms read from the
1044input to perform preprocessing.  It consists of four steps, where each
1045step processes the output of the previous step.
1046
1047    \begin{enumerate}
1048        \item Test conditional compilation directives and translate
1049	all input to \verb$[]$ if we are in a `false branch' of the
1050	conditional compilation.  See \secref{conditionalcompilation}.
1051
1052	\item Call term_expansion/2.  This predicate is first tried in
1053	the module that is being compiled and then in modules from which
1054	this module inherits according to default_module/2.  The output
1055	of the expansion in a module is used as input for the next
1056	module.  Using the default setup and when compiling a normal
1057	application module \arg{M}, this implies expansion is executed
1058	in \arg{M}, \const{user} and finally in \const{system}.  Library
1059	modules inherit directly from \const{system} and can thus not be
1060	re-interpreted by term expansion rules in \const{user}.
1061
1062	\item Call DCG expansion (dcg_translate_rule/2).
1063
1064	\item Call expand_goal/2 on each body term that appears in
1065	the output of the previous steps.
1066    \end{enumerate}
1067
1068    \predicate{goal_expansion}{2}{+Goal1, -Goal2}
1069Like term_expansion/2, goal_expansion/2 provides for macro expansion
1070of Prolog source code. Between expand_term/2 and the actual compilation,
1071the body of clauses analysed and the goals are handed to expand_goal/2,
1072which uses the goal_expansion/2 hook to do user-defined expansion.
1073
1074The predicate goal_expansion/2 is first called in the module that is
1075being compiled, and then follows the module inheritance path as defined
1076by default_module/2, i.e., by default \const{user} and \const{system}.
1077If \arg{Goal} is of the form \arg{Module}:\arg{Goal} where \arg{Module}
1078is instantiated, goal_expansion/2 is called on \arg{Goal} using rules
1079from module \arg{Module} followed by default modules for \arg{Module}.
1080
1081Only goals appearing in the body of clauses when reading a source file
1082are expanded using this mechanism, and only if they appear literally in
1083the clause, or as an argument to a defined meta-predicate that is
1084annotated using `0' (see meta_predicate/1). Other cases need a real
1085predicate definition.
1086
1087The expansion hook can use prolog_load_context/2 to obtain information
1088about the context in which the goal is expanded such as the module,
1089variable names or the encapsulating term.
1090
1091    \predicate{expand_goal}{2}{+Goal1, -Goal2}
1092This predicate is normally called by the compiler to perform
1093preprocessing using goal_expansion/2.  The predicate computes a
1094fixed-point by applying transformations until there are no more
1095changes.  If optimisation is enabled (see \cmdlineoption{-O} and
1096\prologflag{optimise}), expand_goal/2 simplifies the result by
1097removing unneeded calls to true/0 and fail/0 as well as
1098trivially unreachable branches.
1099
1100If goal_expansion/2 \jargon{wraps} a goal as in the example below the
1101system still reaches fixed-point as it prevents re-expanding the
1102expanded term while recursing. It does re-enable expansion on the
1103\emph{arguments} of the expanded goal as illustrated in
1104\nopredref{t2}{1} in the example.\footnote{After discussion with
1105Peter Ludemann and Paulo Moura on the forum.}
1106
1107\begin{code}
1108:- meta_predicate run(0).
1109
1110may_not_fail(test(_)).
1111may_not_fail(run(_)).
1112
1113goal_expansion(G, (G *-> true ; error(goal_failed(G),_))) :-
1114    may_not_fail(G).
1115
1116t1(X) :- test(X).
1117t2(X) :- run(run(X)).
1118\end{code}
1119
1120Is expanded into
1121
1122\begin{code}
1123t1(X) :-
1124    (   test(X)
1125    *-> true
1126    ;   error(goal_failed(test(X)), _)
1127    ).
1128
1129t2(X) :-
1130    (   run((run(X)*->true;error(goal_failed(run(X)), _)))
1131    *-> true
1132    ;   error(goal_failed(run(run(X))), _)
1133    ).
1134\end{code}
1135
1136    \predicate{compile_aux_clauses}{1}{+Clauses}
1137Compile clauses on behalf of goal_expansion/2.  This predicate compiles
1138the argument clauses into static predicates, associating the predicates
1139with the current file but avoids changing the notion of current predicate
1140and therefore discontiguous warnings.
1141
1142Note that in some cases multiple expansions of similar goals can share
1143the same compiled auxiliary predicate. In such cases, the implementation
1144of goal_expansion/2 can use predicate_property/2 using the property
1145\const{defined} to test whether the predicate is already defined in the
1146current context.
1147
1148    \predicate{dcg_translate_rule}{2}{+In, -Out}
1149This predicate performs the translation of a term \exam{Head-->Body}
1150into a normal Prolog clause.  Normally this functionality should be
1151accessed using expand_term/2.
1152
1153    \predicate{var_property}{2}{+Var, ?Property}
1154True when \arg{Property} is a property of \arg{Var}. These properties
1155are available during goal- and term-expansion. Defined properties are
1156below. Future versions are likely to provide more properties, such as
1157whether the variable is referenced in the remainder of the term. See
1158also goal_expansion/2.
1159
1160    \begin{description}
1161    \termitem{fresh}{Bool}
1162\arg{Bool} has the value \const{true} if the variable is guaranteed
1163to be unbound at entry of the goal, otherwise its value is \arg{false}.
1164This implies that the variable first appears in this goal or a previous
1165appearance was in a negation (\predref{\+}{1}) or a different branch of
1166a disjunction.
1167
1168    \termitem{singleton}{Bool}
1169\arg{Bool} has the value \const{true} if the variable is a
1170\emph{syntactic} singleton in the term it appears in. Note that this
1171tests that the variable appears exactly once in the term being expanded
1172without making any claim on the syntax of the variable. Variables that
1173appear only once in multiple branches are \emph{not} singletons
1174according to this property. Future implementations may improve on that.
1175
1176    \termitem{name}{Name}
1177True when variable appears with the given name in the source.
1178    \end{description}
1179\end{description}
1180
1181
1182\subsubsection{Program transformation with source layout info}
1183\label{sec:progtransform-layout}
1184
1185This sections documents extended versions of the program transformation
1186predicates that also transform the source layout information.  Extended
1187layout information is currently processed, but unused.  Future versions
1188will use for the following enhancements:
1189
1190\begin{itemize}
1191    \item More precise locations of warnings and errors
1192    \item More reliable setting of breakpoints
1193    \item More reliable source layout information in the graphical
1194          debugger.
1195\end{itemize}
1196
1197\begin{description}
1198    \predicate{expand_goal}{4}{+Goal1, ?Layout1, -Goal2, -Layout2}
1199    \nodescription
1200    \predicate{goal_expansion}{4}{+Goal1, ?Layout1, -Goal2, -Layout2}
1201    \nodescription
1202    \predicate{expand_term}{4}{+Term1, ?Layout1, -Term2, -Layout2}
1203    \nodescription
1204    \predicate{term_expansion}{4}{+Term1, ?Layout1, -Term2, -Layout2}
1205    \predicate{dcg_translate_rule}{4}{+In, ?LayoutIn, -Out, -LayoutOut}
1206These versions are called \emph{before} their 2-argument counterparts.
1207The input layout term is either a variable (if no layout information is
1208available) or a term carrying detailed layout information as returned by
1209the \const{subterm_positions} of read_term/2.
1210\end{description}
1211
1212
1213\subsubsection{Conditional compilation}
1214\label{sec:conditionalcompilation}
1215
1216\index{if, directive}%
1217Conditional compilation builds on the same principle as
1218term_expansion/2, goal_expansion/2 and the expansion of grammar rules to
1219compile sections of the source code conditionally. One of the reasons
1220for introducing conditional compilation is to simplify writing portable
1221code. See \secref{dialect} for more information. Here is a simple
1222example:
1223
1224\begin{code}
1225:- if(\+source_exports(library(lists), suffix/2)).
1226
1227suffix(Suffix, List) :-
1228	append(_, Suffix, List).
1229
1230:- endif.
1231\end{code}
1232
1233Note that these directives can only appear as separate terms in the
1234input.  Typical usage scenarios include:
1235
1236\begin{shortlist}
1237    \item Load different libraries on different dialects.
1238    \item Define a predicate if it is missing as a system predicate.
1239    \item Realise totally different implementations for a particular
1240    part of the code due to different capabilities.
1241    \item Realise different configuration options for your software.
1242\end{shortlist}
1243
1244
1245\begin{description}
1246    \directive{if}{1}{:Goal}
1247Compile subsequent code only if \arg{Goal} succeeds.  For enhanced
1248portability, \arg{Goal} is processed by expand_goal/2 before execution.
1249If an error occurs, the error is printed and processing proceeds as if
1250\arg{Goal} has failed.
1251
1252    \directive{elif}{1}{:Goal}
1253Equivalent to \exam{:- else. :-if(Goal).} ... \exam{:- endif.}  In a sequence as below,
1254the section below the first matching \const{elif} is processed. If no test
1255succeeds, the else branch is processed.
1256
1257\begin{code}
1258:- if(test1).
1259section_1.
1260:- elif(test2).
1261section_2.
1262:- elif(test3).
1263section_3.
1264:- else.
1265section_else.
1266:- endif.
1267\end{code}
1268
1269    \directive{else}{0}{}
1270Start `else' branch.
1271
1272    \directive{endif}{0}{}
1273End of conditional compilation.
1274\end{description}
1275
1276
1277\subsection{Reloading files, active code and threads}
1278\label{sec:loadrunningcode}
1279
1280Traditionally, Prolog environments allow for reloading files holding
1281currently active code.  In particular, the following sequence is a valid
1282use of the development environment:
1283
1284\begin{shortlist}
1285    \item Trace a goal
1286    \item Find unexpected behaviour of a predicate
1287    \item Enter a \jargon{break} using the \textbf{b} command
1288    \item Fix the sources and reload them using make/0
1289    \item Exit the break, \jargon{retry} executing the now
1290	  fixed predicate using the \textbf{r} command
1291\end{shortlist}
1292
1293\jargon{Reloading} a previously loaded file is safe, both in the debug
1294scenario above and when the code is being executed by another
1295\jargon{thread}. Executing threads switch atomically to the new
1296definition of modified predicates, while clauses that belong to the old
1297definition are (eventually) reclaimed by
1298garbage_collect_clauses/0.\footnote{As of version 7.3.12. Older versions
1299wipe all clauses originating from the file before loading the new
1300clauses. This causes threads that executes the code to (typically) die
1301with an \jargon{undefined predicate} exception.}  Below we describe the
1302steps taken for \emph{reloading} a file to help understanding the
1303limitations of the process.
1304
1305\begin{enumerate}
1306    \item If a file is being reloaded, a \jargon{reload context} is
1307    associated to the file administration.  This context includes a
1308    table keeping track of predicates and a table keeping track of
1309    the module(s) associated with this source.
1310    \item If a new predicate is found, an entry is added to the
1311    context predicate table.  Three options are considered:
1312    \begin{enumerate}
1313        \item The predicate is new.  It is handled the same as
1314	if the file was loaded for the first time.
1315	\item The predicate is foreign or thread local.  These
1316	too are treated as if the file was loaded for the first
1317	time.
1318	\item Normal predicates.  Here we initialise a pointer
1319	to the \emph{current clause}.
1320    \end{enumerate}
1321    \item New clauses for `normal predicates' are considered as
1322    follows:
1323    \begin{enumerate}
1324        \item If the clause's byte-code is the same as the predicates
1325	current clause, discard the clause and advance the current
1326	clause pointer.
1327	\item If the clause's byte-code is the same as some clause
1328	further into the clause list of the predicate, discard the
1329	new clause, mark all intermediate clauses for future deletion,
1330	and advance the current clause pointer to the first clause
1331	after the matched one.
1332	\item If the clause's byte-code matches no clause, insert it
1333	for \emph{future activation} before the current clause and
1334	keep the current clause.
1335    \end{enumerate}
1336    \item \jargon{Properties} such as \const{dynamic} or \const{meta_predicate}
1337    are in part applied immediately and in part during the fixup process
1338    after the file completes loading.  Currently, \const{dynamic} and
1339    \const{thread_local} are applied immediately.
1340    \item New modules are recorded in the reload context.  Export declarations
1341    (the module's public list and export/1 calls) are both applied and
1342    recorded.
1343    \item When the end-of-file is reached, the following fixup steps are taken
1344    \begin{enumerate}
1345        \item For each predicate
1346	\begin{enumerate}
1347	    \item The current clause and subsequent clauses are marked for
1348	    future deletion.
1349	    \item All clauses marked for future deletion or creation are
1350	    (in)activated by changing their `erased' or `created'
1351	    \jargon{generation}.  Erased clauses are (eventually)
1352	    reclaimed by the \jargon{clause garbage collector}, see
1353	    garbage_collect_clauses/0.
1354	    \item Pending predicate property changes are applied.
1355	\end{enumerate}
1356	\item For each module
1357	\begin{enumerate}
1358	    \item Exported predicates that are not encountered in the
1359	    reload context are removed from the export list.
1360	\end{enumerate}
1361    \end{enumerate}
1362\end{enumerate}
1363
1364The above generally ensures that changes to the \emph{content} of source
1365files can typically be activated safely using make/0. Global changes
1366such as operator changes, changes of module names, changes to multi-file
1367predicates, etc.\ sometimes require a restart. In almost all cases, the
1368need for restart is indicated by permission or syntax errors during the
1369reload or existence errors while running the program.
1370
1371In some cases the content of a source file refers `to itself'. This is
1372notably the case if local rules for goal_expansion/2 or term_expansion/2
1373are defined or goals are executed using
1374\jargon{directives}.\footnote{Note that initialization/1 directives are
1375executed \emph{after} loading the file. SWI-Prolog allows for directives
1376that are executed \emph{while} loading the file using \exam{:- Goal.} or
1377initialization/2}. Up to version 7.5.12 it was typically needed to
1378reload the file \emph{twice}, once for updating the code that was used
1379for compiling the remainder of the file and once to effectuate this. As
1380of version 7.5.13, conventional \jargon{transaction semantics} apply.
1381This implies that for the thread performing the reload the file's
1382content is first wiped and gradually rebuilt, while other threads see
1383an \jargon{atomic} update from the old file content to the
1384new.\footnote{This feature was implemented by Keri Harris.}
1385
1386\subsubsection{Compilation of mutually dependent code} \label{sec:depload}
1387
1388Large programs are generally split into multiple files. If file $A$
1389accesses predicates from file $B$ which accesses predicates from file
1390$A$, we consider this a mutual or circular dependency. If traditional
1391load predicates (e.g., consult/1) are used to include file $B$ from $A$
1392and $A$ from $B$, loading either file results in a loop. This is because
1393consult/1 is mapped to load_files/2 using the option \term{if(true)}.
1394Such programs are typically loaded using a \jargon{load file} that
1395consults all required (non-module) files. If modules are used, the
1396dependencies are made explicit using use_module/1 statements. The
1397use_module/1 predicate, however, maps to load_files/2 with the option
1398\term{if(not_loaded)}. A use_module/1 on an already loaded file merely
1399makes the public predicates of the used module available.
1400
1401Summarizing, mutual dependency of source files is fully supported with
1402no precautions when using modules. Modules can use each other in an
1403arbitrary dependency graph. When using consult/1, predicate dependencies
1404between loaded files can still be arbitrary, but the consult relations
1405between files must be a proper tree.
1406
1407
1408\subsubsection{Compilation with multiple threads} \label{sec:mtload}
1409
1410This section discusses compiling files for the first time. For
1411reloading, see \secref{loadrunningcode}.
1412
1413In older versions, compilation was thread-safe due to a global
1414\jargon{lock} in load_files/2 and the code dealing with
1415\jargon{autoloading} (see \secref{autoload}). Besides unnecessary
1416stalling when multiple threads trap unrelated undefined predicates,
1417this easily leads to deadlocks, notably if threads are started from an
1418initialization/1 directive.\footnote{Although such goals are started
1419after loading the file in which they appear, the calling thread is still
1420likely to hold the `load' lock because it is compiling the file from
1421which the file holding the directive is loaded.}
1422
1423Starting with version 5.11.27, the autoloader is no longer locked and
1424multiple threads can compile files concurrently. This requires special
1425precautions only if multiple threads wish to load the same file at the
1426same time. Therefore, load_files/2 checks automatically whether some other
1427thread is already loading the file. If not, it starts loading the file.
1428If another thread is already loading the file, the thread blocks until
1429the other thread finishes loading the file. After waiting, and if the
1430file is a module file, it will make the public predicates available.
1431
1432Note that this schema does not prevent deadlocks under all situations.
1433Consider two mutually dependent (see \secref{depload}) module files $A$
1434and $B$, where thread~1 starts loading $A$ and thread~2 starts loading
1435$B$ at the same time. Both threads will deadlock when trying to load the
1436used module.
1437
1438The current implementation does not detect such cases and the involved
1439threads will freeze. This problem can be avoided if a mutually dependent
1440collection of files is always loaded from the same start file.
1441
1442
1443\subsection{Quick load files}		\label{sec:qlf}
1444
1445SWI-Prolog supports compilation of individual or multiple Prolog
1446source files into `Quick Load Files'. A `Quick Load File' (\fileext{qlf}
1447file) stores the contents of the file in a precompiled format.
1448
1449These files load considerably faster than source files and are normally
1450more compact.  They are machine-independent and may thus be loaded
1451on any implementation of SWI-Prolog.  Note, however, that clauses are
1452stored as virtual machine instructions.  Changes to the compiler will
1453generally make old compiled files unusable.
1454
1455Quick Load Files are created using qcompile/1. They are loaded using
1456consult/1 or one of the other file-loading predicates described in
1457\secref{consulting}. If consult/1 is given an explicit \fileext{pl} file,
1458it will load the Prolog source. When given a \fileext{qlf} file, it
1459will load the file. When no extension is specified, it will load the
1460\fileext{qlf} file when present and the \fileext{pl} file otherwise.
1461
1462\begin{description}
1463    \predicate{qcompile}{1}{:File}
1464Takes a file specification as consult/1, etc., and, in addition to the
1465normal compilation, creates a \emph{Quick Load File} from \arg{File}.
1466The file extension of this file is \fileext{qlf}. The basename of the
1467Quick Load File is the same as the input file.
1468
1469If the file contains `\exam{:- consult(\arg{+File})}', `\exam{:-
1470[\arg{+File}]}' or `\exam{:- load_files(\arg{+File}, [qcompile(part),
1471...])}' statements, the referred files are compiled into the
1472same \fileext{qlf} file. Other directives will be stored in the
1473\fileext{qlf} file and executed in the same fashion as when loading the
1474\fileext{pl} file.
1475
1476For term_expansion/2, the same rules as described in
1477\secref{compilation} apply.
1478
1479Conditional execution or optimisation may test the predicate
1480compiling/0.
1481
1482Source references (source_file/2) in the Quick Load File refer to
1483the Prolog source file from which the compiled code originates.
1484
1485    \predicate{qcompile}{2}{:File, +Options}
1486As qcompile/1, but processes additional options as defined by
1487load_files/2.\bug{Option processing is currently incomplete.}
1488\end{description}
1489
1490
1491\section{Editor Interface}	\label{sec:edit}
1492
1493SWI-Prolog offers an extensible interface which allows the user to
1494edit objects of the program: predicates, modules, files, etc.  The
1495editor interface is implemented by edit/1 and consists of three parts:
1496{\em locating}, {\em selecting} and {\em starting} the editor.
1497Any of these parts may be customized.  See \secref{customedit}.
1498
1499The built-in edit specifications for edit/1 (see prolog_edit:locate/3)
1500are described in the table below:
1501
1502\begin{center}
1503\begin{tabular}{|l|p{3.5in}|}
1504\hline
1505\multicolumn{2}{|c|}{\bf Fully specified objects} \\
1506\hline
1507<Module>:<Name>/<Arity>	& Refers to a predicate \\
1508module(<Module>)	& Refers to a module \\
1509file(<Path>)		& Refers to a file \\
1510source_file(<Path>)	& Refers to a loaded source file \\
1511\hline
1512\multicolumn{2}{|c|}{\bf Ambiguous specifications} \\
1513\hline
1514<Name>/<Arity>		& Refers to this predicate in any module \\
1515<Name>			& Refers to (1) the named predicate in any
1516		          module with any arity, (2) a (source) file, or
1517			  (3) a module. \\
1518\hline
1519\end{tabular}
1520\end{center}
1521
1522
1523\begin{description}
1524    \predicate{edit}{1}{+Specification}
1525First, exploit \qpredref{prolog_edit}{locate}{3} to translate
1526\arg{Specification} into a list of \jargon{Locations}. If there is more
1527than one `hit', the user is asked to select from the locations found.
1528Finally, \qpredref{prolog_edit}{edit_source}{1} is used to invoke
1529the user's preferred editor. Typically, edit/1 can be handed the name of
1530a predicate, module, basename of a file, XPCE class, XPCE method, etc.
1531
1532    \predicate{edit}{0}{}
1533Edit the `default' file using edit/1.  The default file is the file
1534loaded with the command line option \cmdlineoption{-s} or, in Windows,
1535the file loaded by double-clicking from the Windows shell.
1536\end{description}
1537
1538\subsection{Customizing the editor interface}
1539\label{sec:customedit}
1540
1541The predicates described in this section are \jargon{hooks} that can be
1542defined to disambiguate specifications given to edit/1, find the related
1543source, and open an editor at the given source location.
1544
1545\begin{description}
1546    \predicate{prolog_edit:locate}{3}{+Spec, -FullSpec, -Location}
1547Where \arg{Spec} is the specification provided through edit/1.  This
1548multifile predicate is used to enumerate locations where an object
1549satisfying the given \arg{Spec} can be found.  \arg{FullSpec} is unified
1550with the complete specification for the object.  This distinction is used
1551to allow for ambiguous specifications.  For example, if \arg{Spec} is
1552an atom, which appears as the basename of a loaded file and as the
1553name of a predicate, \arg{FullSpec} will be bound to \term{file}{Path}
1554or \arg{Name}/\arg{Arity}.
1555
1556\arg{Location} is a list of attributes of the location.  Normally, this
1557list will contain the term \term{file}{File} and, if available, the
1558term \term{line}{Line}.
1559
1560    \predicate{prolog_edit:locate}{2}{+Spec, -Location}
1561Same as prolog_edit:locate/3, but only deals with fully specified
1562objects.
1563
1564    \predicate{prolog_edit:edit_source}{1}{+Location}
1565Start editor on \arg{Location}. See prolog_edit:locate/3 for the format
1566of a location term. This multifile predicate is normally not defined.
1567If it succeeds, edit/1 assumes the editor is started.
1568
1569If it fails, edit/1 uses its internal defaults, which are defined by
1570the Prolog flag \prologflag{editor} and/or the environment variable
1571\env{EDITOR}.  The following rules apply.  If the Prolog flag \prologflag{editor}
1572is of the format \verb|$|<name>, the editor is determined by the environment
1573variable <name>.  Else, if this flag is \const{pce_emacs} or \const{built_in}
1574\emph{and} XPCE is loaded or can be loaded, the built-in Emacs clone is used.
1575Else, if the environment \env{EDITOR} is set, this editor is used.  Finally,
1576\program{vi} is used as default on Unix systems and \program{notepad} on
1577Windows.
1578
1579See the default  user  preferences   file  \file{customize/init.pl}  for
1580examples.
1581
1582    \predicate{prolog_edit:edit_command}{2}{+Editor, -Command}
1583Determines how \arg{Editor} is to be invoked using shell/1. \arg{Editor}
1584is the determined editor (see \qpredref{prolog_edit}{edit_source}{1}),
1585without the full path specification, and without a possible
1586(\fileext{exe}) extension. \arg{Command} is an atom describing the
1587command. The following \%-sequences are replaced in \arg{Command} before
1588the result is handed to shell/1:
1589
1590\begin{center}
1591\begin{tabular}{|l|p{3.5in}|}
1592\hline
1593\%e	& Replaced by the (OS) command name of the editor \\
1594\%f	& Replaced by the (OS) full path name of the file \\
1595\%d	& Replaced by the line number \\
1596\hline
1597\end{tabular}
1598\end{center}
1599
1600If the editor can deal with starting at a specified line, two clauses
1601should be provided. The first pattern invokes the editor with a
1602line number, while the second is used if the line number is unknown.
1603
1604The default contains definitions for \program{vi}, \program{emacs},
1605\program{emacsclient}, \program{vim}, \program{notepad}$^*$ and
1606\program{wordpad}$^*$.  Starred editors do not provide starting
1607at a given line number.
1608
1609Please contribute your specifications to \email{bugs@swi-prolog.org}.
1610
1611    \predicate{prolog_edit:load}{0}{}
1612Normally an undefined multifile predicate.  This predicate may be defined
1613to provide loading hooks for user extensions to the edit module.  For
1614example, XPCE provides the code below to load \pllib{swi_edit}, containing
1615definitions to locate classes and methods as well as to bind this package
1616to the PceEmacs built-in editor.
1617
1618\begin{code}
1619:- multifile prolog_edit:load/0.
1620
1621prolog_edit:load :-
1622	ensure_loaded(library(swi_edit)).
1623\end{code}
1624\end{description}
1625
1626\section{Verify Type of a Term}			\label{sec:typetest}
1627
1628Type tests are semi-deterministic predicates that succeed if the
1629argument satisfies the requested type. Type-test predicates have no
1630error condition and do not instantiate their argument. See also library
1631\pllib{error}.
1632
1633\begin{description}
1634    \predicate[ISO]{var}{1}{@Term}
1635True if \arg{Term} currently is a free variable.
1636
1637    \predicate[ISO]{nonvar}{1}{@Term}
1638True if \arg{Term} currently is not a free variable.
1639
1640    \predicate[ISO]{integer}{1}{@Term}
1641True if \arg{Term} is bound to an integer.
1642
1643    \predicate[ISO]{float}{1}{@Term}
1644True if \arg{Term} is bound to a floating point number.
1645
1646    \predicate{rational}{1}{@Term}
1647True if \arg{Term} is bound to a rational number.  Rational numbers
1648include integers.
1649
1650    \predicate{rational}{3}{@Term, -Numerator, -Denominator}
1651True if \arg{Term} is a rational number with given \arg{Numerator} and
1652\arg{Denominator}.  The \arg{Numerator} and \arg{Denominator} are in
1653canonical form, which means \arg{Denominator} is a positive integer and
1654there are no common divisors between \arg{Numerator} and \arg{Denominator}.
1655
1656    \predicate[ISO]{number}{1}{@Term}
1657True if \arg{Term} is bound to a rational number (including integers) or
1658a floating point number.
1659
1660    \predicate[ISO]{atom}{1}{@Term}
1661True if \arg{Term} is bound to an atom.
1662
1663    \predicate{blob}{2}{@Term, ?Type}
1664True if \arg{Term} is a \jargon{blob} of type \arg{Type}. See
1665\secref{blob}.
1666
1667    \predicate{string}{1}{@Term}
1668True if \arg{Term} is bound to a string. Note that string here refers to
1669the built-in atomic type string as described in \secref{strings}.
1670Starting with version~7, the syntax for a string object is text between
1671double quotes, such as \verb|"hello"|.\footnote{In traditional Prolog
1672systems, double quoted text is often mapped to a list of
1673\jargon{character codes}.} See also the Prolog flag
1674\prologflag{double_quotes}.
1675
1676    \predicate[ISO]{atomic}{1}{@Term}
1677True if \arg{Term} is bound (i.e., not a variable) and is not
1678compound.  Thus, atomic acts as if defined by:
1679
1680\begin{code}
1681atomic(Term) :-
1682	nonvar(Term),
1683	\+ compound(Term).
1684\end{code}
1685
1686SWI-Prolog defines the following atomic datatypes: atom (atom/1),
1687string (string/1), integer (integer/1), floating point number
1688(float/1) and blob (blob/2).  In addition, the symbol \verb$[]$
1689(empty list) is atomic, but not an atom.  See \secref{ext-lists}.
1690
1691    \predicate[ISO]{compound}{1}{@Term}
1692True if \arg{Term} is bound to a compound term.  See also functor/3
1693=../2, compound_name_arity/3 and compound_name_arguments/3.
1694
1695    \predicate[ISO]{callable}{1}{@Term}
1696True if \arg{Term} is bound to an atom or a compound term. This was
1697intended as a type-test for arguments to call/1, call/2 etc. Note that
1698callable only tests the \jargon{surface term}. Terms such as (22,true)
1699are considered callable, but cause call/1 to raise a type error.
1700Module-qualification of meta-argument (see meta_predicate/1) using
1701\functor{:}{2} causes callable to succeed on any
1702meta-argument.\footnote{We think that callable/1 should be deprecated
1703and there should be two new predicates, one performing a test for
1704callable that is minimally module aware and possibly consistent with
1705type-checking in call/1 and a second predicate that tests for atom or
1706compound.} Consider the program and query below:
1707
1708\begin{code}
1709:- meta_predicate p(0).
1710
1711p(G) :-	callable(G), call(G).
1712
1713?- p(22).
1714ERROR: Type error: `callable' expected, found `22'
1715ERROR: In:
1716ERROR:    [6] p(user:22)
1717\end{code}
1718
1719    \predicate[ISO]{ground}{1}{@Term}
1720True if \arg{Term} holds no free variables. See also nonground/2
1721and term_variables/2.
1722
1723    \predicate{cyclic_term}{1}{@Term}
1724True if \arg{Term} contains cycles, i.e.\ is an infinite term.
1725See also acyclic_term/1 and \secref{cyclic}.%
1726	\footnote{The predicates cyclic_term/1 and acyclic_term/1 are
1727		  compatible with SICStus Prolog.  Some Prolog systems
1728		  supporting cyclic terms use \nopredref{is_cyclic}{1}.}
1729
1730    \predicate[ISO]{acyclic_term}{1}{@Term}
1731True if \arg{Term} does not contain cycles,  i.e.\ can be processed
1732recursively in finite time.  See also cyclic_term/1 and \secref{cyclic}.
1733\end{description}
1734
1735\section{Comparison and Unification of Terms}	\label{sec:compare}
1736
1737Although unification is mostly done implicitly while matching the
1738head of a predicate, it is also provided by the predicate =/2.
1739
1740\begin{description}
1741    \infixop[ISO]{=}{?Term1}{?Term2}
1742Unify \arg{Term1} with \arg{Term2}. True if the unification succeeds.
1743For behaviour on cyclic terms see the Prolog flag
1744\prologflag{occurs_check}. It acts as if defined by the following fact:
1745
1746\begin{code}
1747=(Term, Term).
1748\end{code}
1749
1750    \infixop[ISO]{\=}{@Term1}{@Term2}
1751Equivalent to \exam{\Snot Term1 = Term2}.
1752
1753This predicate is logically sound if its arguments are sufficiently
1754instantiated. In other cases, such as \exam{?- X \Sne\ Y.},
1755the predicate fails although there are solutions. This is due to the
1756incomplete nature of~\predref{\+}{1}.
1757
1758To make your programs work correctly also in situations where the
1759arguments are not yet sufficiently instantiated, use dif/2 instead.
1760\end{description}
1761
1762
1763\subsection{Standard Order of Terms}		\label{sec:standardorder}
1764
1765Comparison and unification of arbitrary terms. Terms are ordered in the
1766so-called ``standard order''. This order is defined as follows:
1767
1768\begin{enumerate}
1769    \item $\arg{Variables} < \arg{Numbers} < \arg{Strings} < \arg{Atoms}
1770          < \arg{Compound Terms}$
1771    \item Variables are sorted by address.
1772    \item \arg{Numbers} are compared by value.  Mixed integer/float are compared
1773	  as floats. If the comparison is equal, the float is considered
1774	  the smaller value. If the Prolog flag \prologflag{iso} is defined,
1775	  all floating point numbers precede all integers.
1776    \item \arg{Strings} are compared alphabetically.
1777    \item \arg{Atoms} are compared alphabetically.
1778    \item \arg{Compound} terms are first checked on their arity, then
1779          on their functor name (alphabetically) and finally recursively
1780	  on their arguments, leftmost argument first.
1781\end{enumerate}
1782
1783Although variables are ordered, there are some unexpected properties one
1784should keep in mind when relying on variable ordering. This applies to
1785the predicates below as to predicate such as sort/2 as well as libraries
1786that reply on ordering such as library \pllib{assoc} and library
1787\pllib{ordsets}. Obviously, an established relation \mbox{\arg{A}
1788\const{@<} \arg{B}} no longer holds if \arg{A} is unified with e.g., a
1789number. Also unifying \arg{A} with \arg{B} invalidates the relation
1790because they become equivalent (==/2) after unification.
1791
1792As stated above, variables are sorted by address, which implies that
1793they are sorted by `age', where `older' variables are ordered before
1794`newer' variables. If two variables are unified their `shared' age is
1795the age of oldest variable. This implies we can examine a list of sorted
1796variables with `newer' (fresh) variables without invalidating the order.
1797Attaching an \jargon{attribute}, see \secref{attvar}, turns an `old'
1798variable into a `new' one as illustrated below. Note that the first
1799always succeeds as the first argument of a term is always the oldest.
1800This only applies for the \emph{first} attribute, i.e., further
1801manipulation of the attribute list does \emph{not} change the `age'.
1802
1803\begin{code}
1804?- T = f(A,B), A @< B.
1805T = f(A, B).
1806
1807?- T = f(A,B), put_attr(A, name, value), A @< B.
1808false.
1809\end{code}
1810
1811The above implies you \emph{can} use e.g., an assoc (from library
1812\pllib{assoc}, implemented as an AVL tree) to maintain information about
1813a set of variables. You must be careful about what you do with the
1814attributes though. In many cases it is more robust to use attributes to
1815register information about variables.
1816
1817\begin{description}
1818    \infixop[ISO]{==}{@Term1}{@Term2}
1819True if \arg{Term1} is equivalent to \arg{Term2}. A variable is only
1820identical to a sharing variable.
1821
1822    \infixop[ISO]{\==}{@Term1}{@Term2}
1823Equivalent to \exam{\Snot Term1 == Term2}.
1824
1825    \infixop[ISO]{@<}{@Term1}{@Term2}
1826True if \arg{Term1} is before \arg{Term2} in the standard order of terms.
1827
1828    \infixop[ISO]{@=<}{@Term1}{@Term2}
1829True if both terms are equal (\predref{==}{2}) or \arg{Term1} is
1830before \arg{Term2} in the standard order of terms.
1831
1832    \infixop[ISO]{@>}{@Term1}{@Term2}
1833True if \arg{Term1} is after \arg{Term2} in the standard order of terms.
1834
1835    \infixop[ISO]{@>=}{@Term1}{@Term2}
1836True if both terms are equal (\predref{==}{2}) or \arg{Term1} is
1837after \arg{Term2} in the standard order of terms.
1838
1839    \predicate[ISO]{compare}{3}{?Order, @Term1, @Term2}
1840Determine or test the \arg{Order} between two terms in the standard
1841order of terms. \arg{Order} is one of \const{<}, \const{>} or \const{=},
1842with the obvious meaning.
1843\end{description}
1844
1845
1846\subsection{Special unification and comparison predicates}
1847\label{sec:unifyspecial}
1848
1849This section describes special purpose variations on Prolog unification.
1850The predicate unify_with_occurs_check/2 provides sound unification and
1851is part of the ISO standard. The predicate subsumes_term/2 defines
1852`one-sided unification' and is part of the ISO proposal established in
1853Edinburgh (2010). Finally, unifiable/3 is a `what-if' version of
1854unification that is often used as a building block in constraint
1855reasoners.
1856
1857
1858\begin{description}
1859    \predicate[ISO]{unify_with_occurs_check}{2}{+Term1, +Term2}
1860As \predref{=}{2}, but using \jargon{sound unification}. That is, a
1861variable only unifies to a term if this term does not contain the
1862variable itself.  To illustrate this, consider the two queries below.
1863
1864\begin{code}
18651 ?- A = f(A).
1866A = f(A).
18672 ?- unify_with_occurs_check(A, f(A)).
1868false.
1869\end{code}
1870
1871\index{occurs_check}%
1872The first statement creates a \jargon{cyclic term}, also called a
1873\jargon{rational tree}. The second executes logically sound unification
1874and thus fails. Note that the behaviour of unification through
1875\predref{=}{2} as well as implicit unification in the head can be
1876changed using the Prolog flag \prologflag{occurs_check}.
1877
1878The SWI-Prolog implementation of unify_with_occurs_check/2 is cycle-safe
1879and only guards against \emph{creating} cycles, not against cycles that
1880may already be present in one of the arguments.  This is illustrated in
1881the following two queries:
1882
1883\begin{code}
1884?- X = f(X), Y = X, unify_with_occurs_check(X, Y).
1885X = Y, Y = f(Y).
1886?- X = f(X), Y = f(Y), unify_with_occurs_check(X, Y).
1887X = Y, Y = f(Y).
1888\end{code}
1889
1890Some other Prolog systems interpret unify_with_occurs_check/2 as if
1891defined by the clause below, causing failure on the above two queries.
1892Direct use of acyclic_term/1 is portable and more appropriate for such
1893applications.
1894
1895\begin{code}
1896unify_with_occurs_check(X,X) :- acyclic_term(X).
1897\end{code}
1898
1899    \infixop{=@=}{+Term1}{+Term2}
1900\index{variant}%
1901True if \arg{Term1} is a \jargon{variant} of (or \jargon{structurally
1902equivalent} to) \arg{Term2}. Testing for a variant is weaker than
1903equivalence (\predref{==}{2}), but stronger than unification
1904(\predref{=}{2}). Two terms $A$ and $B$ are variants iff there exists a
1905renaming of the variables in $A$ that makes $A$ equivalent (==) to $B$
1906and vice versa.\footnote{Row~7 and 8 of this table may come as a
1907surprise, but row~8 is satisfied by (left-to-right) $A\rightarrow C$,
1908$B\rightarrow A$ and (right-to-left) $C\rightarrow A$, $A\rightarrow B$.
1909If the same variable appears in different locations in the left and
1910right term, the variant relation can be broken by consistent binding of
1911both terms. E.g., after binding the first argument in row~8 to a value,
1912both terms are no longer variant.} Examples:
1913
1914\begin{quote}
1915\begin{tabular}{rcc}
19161 & \tt	    a  =@= A       & false \\
19172 & \tt     A  =@= B       & true \\
19183 & \tt x(A,A) =@= x(B,C)  & false \\
19194 & \tt x(A,A) =@= x(B,B)  & true \\
19205 & \tt x(A,A) =@= x(A,B)  & false \\
19216 & \tt x(A,B) =@= x(C,D)  & true \\
19227 & \tt x(A,B) =@= x(B,A)  & true \\
19238 & \tt x(A,B) =@= x(C,A)  & true \\
1924\end{tabular}
1925\end{quote}
1926
1927A term is always a variant of a copy of itself. Term copying takes place
1928in, e.g., copy_term/2, findall/3 or proving a clause added with
1929asserta/1. In the pure Prolog world (i.e., without attributed
1930variables), \predref{=@=}{2} behaves as if defined below. With
1931attributed variables, variant of the attributes is tested rather than
1932trying to satisfy the constraints.
1933
1934\begin{code}
1935A =@= B :-
1936	copy_term(A, Ac),
1937	copy_term(B, Bc),
1938	numbervars(Ac, 0, N),
1939	numbervars(Bc, 0, N),
1940	Ac == Bc.
1941\end{code}
1942
1943The SWI-Prolog implementation is cycle-safe and can deal with variables
1944that are shared between the left and right argument. Its performance is
1945comparable to \predref{==}{2}, both on success and (early) failure.
1946\footnote{The current implementation is contributed by Kuniaki Mukai.}
1947
1948This predicate is known by the name \predref{variant}{2} in some other
1949Prolog systems. Be aware of possible differences in semantics if the
1950arguments contain attributed variables or share variables.\footnote{In
1951many systems variant is implemented using two calls to subsumes_term/2.}
1952
1953    \infixop{\=@=}{+Term1}{+Term2}
1954Equivalent to \exam{`\Snot Term1 =@= Term2'}.  See \predref{=@=}{2} for
1955details.
1956
1957    \predicate[ISO]{subsumes_term}{2}{{@}Generic, {@}Specific}
1958True if \arg{Generic} can be made equivalent to \arg{Specific} by only
1959binding variables in \arg{Generic}.  The current implementation performs
1960the unification and ensures that the variable set of \arg{Specific} is
1961not changed by the unification. On success, the bindings are
1962undone.\footnote{This predicate is often named subsumes_chk/2 in older
1963Prolog dialects. The current name was established in the ISO WG17
1964meeting in Edinburgh (2010). The \texttt{chk} postfix was
1965considered to refer to determinism as in e.g., memberchk/2.}
1966This predicate respects constraints.
1967
1968    \predicate{term_subsumer}{3}{+Special1, +Special2, -General}
1969\arg{General} is the most specific term that is a generalisation of
1970\arg{Special1} and \arg{Special2}. The implementation can handle cyclic
1971terms.
1972
1973    \predicate{unifiable}{3}{{@}X, {@}Y, -Unifier}
1974If \arg{X} and \arg{Y} can unify, unify \arg{Unifier} with a list of
1975\mbox{\arg{Var} = \arg{Value}}, representing the bindings required to
1976make \arg{X} and \arg{Y} equivalent.%
1977	\footnote{This predicate was introduced for the implementation
1978		  of dif/2 and when/2 after discussion with Tom
1979		  Schrijvers and Bart Demoen.  None of us is really
1980		  happy with the name and therefore suggestions for
1981		  a new name are welcome.}
1982This predicate can handle cyclic terms.  Attributed variables are
1983handled as normal variables.  Associated hooks are \emph{not}
1984executed.
1985
1986    \predicate{?=}{2}{{@}Term1, {@}Term2}
1987Succeeds if the syntactic equality of \arg{Term1} and \arg{Term2}
1988can be decided safely, i.e.\ if the result of \exam{Term1 == Term2}
1989will not change due to further instantiation of either term.  It
1990behaves as if defined by \verb$?=(X,Y) :- \+ unifiable(X,Y,[_|_]).$
1991\end{description}
1992
1993\section{Control Predicates}		\label{sec:control}
1994
1995The predicates of this section implement control structures. Normally
1996the constructs in this section, except for repeat/0, are translated by
1997the compiler. Please note that complex goals passed as arguments to
1998meta-predicates such as findall/3 below cause the goal to be compiled to
1999a temporary location before execution. It is faster to define a
2000sub-predicate (i.e.\ \nopredref{one_character_atoms}{1} in the example
2001below) and make a call to this simple predicate.
2002
2003\begin{code}
2004one_character_atoms(As) :-
2005        findall(A, (current_atom(A), atom_length(A, 1)), As).
2006\end{code}
2007
2008\begin{description}
2009    \predicate[ISO]{fail}{0}{}
2010Always fail.  The predicate fail/0 is translated into a single virtual
2011machine instruction.
2012    \predicate[ISO]{false}{0}{}
2013Same as fail, but the name has a more declarative connotation.
2014    \predicate[ISO]{true}{0}{}
2015Always succeed. The predicate true/0 is translated into a single virtual
2016machine instruction.
2017    \predicate[ISO]{repeat}{0}{}
2018Always succeed, provide an infinite number of choice points.
2019
2020    \predicate[ISO]{!}{0}{}
2021Cut. Discard all choice points created since entering the predicate in
2022which the cut appears. In other words, \jargon{commit} to the clause in
2023which the cut appears \emph{and} discard choice points that have been
2024created by goals to the left of the cut in the current clause. Meta
2025calling is opaque to the cut. This implies that cuts that appear in a
2026term that is subject to meta-calling (call/1) only affect choice points
2027created by the meta-called term. The following control structures are
2028transparent to the cut: \predref{;}{2}, \predref{->}{2} and
2029\predref{*->}{2}. Cuts appearing in the {\em condition} part of
2030\predref{->}{2} and \predref{*->}{2} are opaque to the cut. The
2031table below explains the scope of the cut with examples. \textit{Prunes}
2032here means ``prunes $X$ choice point created by $X$''.
2033
2034\begin{center}\begin{tabular}{ll}
2035\exam{t0 :- (a, !, b).}                 & \% prunes {a}/0 and {t0}/0 \\
2036\exam{t1 :- (a, !, fail ; b).}          & \% prunes {a}/0 and {t1}/0 \\
2037\exam{t2 :- (a -> b, ! ; c).}           & \% prunes {b}/0 and {t2}/0 \\
2038\exam{t3 :- call((a, !, fail ; b)).}    & \% prunes {a}/0 \\
2039\exam{t4 :- \Snot (a, !, fail).}        & \% prunes {a}/0 \\
2040\end{tabular}\end{center}
2041
2042\infixop[ISO]{,}{:Goal1}{:Goal2}
2043Conjunction.  True if both `Goal1' and `Goal2' can be proved.  It is
2044defined as follows (this definition does not lead to a loop as the second comma
2045is handled by the compiler):
2046\begin{code}
2047Goal1, Goal2 :- Goal1, Goal2.
2048\end{code}
2049\infixop[ISO]{;}{:Goal1}{:Goal2}
2050The `or' predicate is defined as:
2051\begin{code}
2052Goal1 ; _Goal2 :- Goal1.
2053_Goal1 ; Goal2 :- Goal2.
2054\end{code}
2055
2056\infixop{|}{:Goal1}{:Goal2}
2057Equivalent to \predref{;}{2}.  Retained for compatibility only.  New code
2058should use \predref{;}{2}.
2059
2060\infixop[ISO]{->}{:Condition}{:Action}
2061If-then and If-Then-Else. The \predref{->}{2} construct commits to
2062the choices made at its left-hand side, destroying choice points created
2063inside the clause (by \predref{;}{2}), or by goals called by
2064this clause. Unlike \predref{!}{0}, the choice point of the predicate as
2065a whole (due to multiple clauses) is \strong{not} destroyed. The
2066combination \predref{;}{2} and \predref{->}{2} acts as if
2067defined as:
2068
2069\begin{code}
2070If -> Then; _Else :- If, !, Then.
2071If -> _Then; Else :- !, Else.
2072If -> Then :- If, !, Then.
2073\end{code}
2074
2075Please note that (If \verb$->$ Then) acts as (If \verb$->$ Then ;
2076\textbf{fail}), making the construct \emph{fail} if the condition fails.
2077This unusual semantics is part of the ISO and all de-facto Prolog
2078standards.
2079
2080Please note that \mbox{(if{->}then;else)} is read as
2081\mbox{((if{->}then);else)} and that the \emph{combined} semantics of
2082this syntactic construct as defined above is \emph{different} from the
2083simple nesting of the two individual constructs, i.e., the semantics of
2084\predref{->}{2} \emph{changes} when embedded in \predref{;}{2}. See also
2085once/1.
2086
2087\infixop{*->}{:Condition}{:Action ; :Else}
2088This construct implements the so-called `soft-cut'. The control is
2089defined as follows: If \arg{Condition} succeeds at least once, the
2090semantics is the same as (\term{call}{Condition},
2091\arg{Action}).\footnote{Note that the \arg{Condition} is wrapped in
2092call/1, limiting the scope of the cut (\predref{!}{0}} If
2093\arg{Condition} does not succeed, the semantics is that of (\verb$\+$
2094\arg{Condition}, \arg{Else}). In other words, if \arg{Condition}
2095succeeds at least once, simply behave as the conjunction of
2096\term{call}{Condition} and \arg{Action}, otherwise execute \arg{Else}.
2097The construct is known under the name \nopredref{if}{3} in some other
2098Prolog implementations.
2099
2100The construct \arg{A} \verb$*->$ \arg{B}, i.e., without an \arg{Else}
2101branch, the semantics is the same as (\term{call}{A}, \arg{B}).
2102
2103This construct is rarely used. An example use case is the implementation
2104of \textsc{optional} in \textsc{sparql}.  The optional construct should
2105preserve all solutions if the argument succeeds as least once but still
2106succeed otherwise.  This is implemented as below.
2107
2108\begin{code}
2109optional(Goal) :-
2110    (   Goal
2111    *-> true
2112    ;	true
2113    ).
2114\end{code}
2115
2116Now calling e.g., \verb$optional(member(X, [a,b]))$ has the solutions
2117$X=a$ and $X=b$, while \verb$optional(member(X,[]))$ succeeds without
2118binding $X$.
2119
2120\prefixop[ISO]{\+}{:Goal}
2121True if `Goal' cannot be proven (mnemonic: \chr{+} refers to {\em
2122provable} and the backslash (\chr{\}) is normally used to
2123indicate negation in Prolog).
2124
2125Many Prolog implementations (including SWI-Prolog) provide not/1. The
2126not/1 alternative is deprecated due to its strong link to logical
2127negation.
2128
2129\end{description}
2130
2131\section{Meta-Call Predicates}		\label{sec:metacall}
2132
2133Meta-call predicates are used to call terms constructed at run time.
2134The basic meta-call mechanism offered by SWI-Prolog is to use
2135variables as a subclause (which should of course be bound to a valid
2136goal at runtime).  A meta-call is slower than a normal call as it
2137involves actually searching the database at runtime for the predicate,
2138while for normal calls this search is done at compile time.
2139
2140\begin{description}
2141    \predicate[ISO]{call}{1}{:Goal}
2142Call \arg{Goal}. This predicate is normally used for goals that are not
2143known at compile time. For example, the Prolog toplevel essentially
2144performs \exam{read(Goal), call(Goal)}. Also a \jargon{meta} predicates
2145such as ignore/1 are defined using call:
2146
2147\begin{code}
2148ignore(Goal) :- call(Goal), !.
2149ignore(_).
2150\end{code}
2151
2152Note that a plain variable as a body term acts as call/1 and the above
2153is equivalent to the code below.  SWI-Prolog produces the same code for
2154these two progams and listing/1 prints the program above.
2155
2156\begin{code}
2157ignore(Goal) :- Goal, !.
2158ignore(_).
2159\end{code}
2160
2161Note that call/1 restricts the scope of the cut (\predref{!}{0}). A cut
2162inside \arg{Goal} only affects choice points created by \arg{Goal}.
2163
2164    \predicate[ISO]{call}{2}{:Goal, +ExtraArg1, \ldots}		% 2..
2165Append \arg{ExtraArg1, ExtraArg2, \ldots} to the argument list of
2166\arg{Goal} and call the result. For example, \exam{call(plus(1), 2, X)}
2167will call \exam{plus(1, 2, X)}, binding \arg{X} to 3.
2168
2169The call/[2..] construct is handled by the compiler. The predicates
2170call/[2-8] are defined as real (meta-)predicates and are available to
2171inspection through current_predicate/1, predicate_property/2,
2172etc.\footnote{Arities 2..8 are demanded by ISO/IEC
217313211-1:1995/Cor.2:2012.} Higher arities are handled by the compiler and
2174runtime system, but the predicates are not accessible for
2175inspection.\footnote{Future versions of the reflective predicate may
2176fake the presence of \nopredref{call}{9..}. Full logical behaviour,
2177generating all these pseudo predicates, is probably undesirable and will
2178become impossible if \jargon{max_arity} is removed.}
2179
2180    \predicate[deprecated]{apply}{2}{:Goal, +List}
2181Append the members of \arg{List} to the arguments of \arg{Goal} and call
2182the resulting term. For example: \exam{apply(plus(1), [2, X])} calls
2183\exam{plus(1, 2, X)}. New code should use call/[2..] if the length of
2184\arg{List} is fixed.
2185
2186    \predicate[deprecated]{not}{1}{:Goal}
2187True if \arg{Goal} cannot be proven.  Retained for compatibility
2188only. New code should use \predref{\+}{1}.
2189
2190    \predicate[ISO]{once}{1}{:Goal}
2191Make a possibly \jargon{nondet} goal \jargon{semidet}, i.e., succeed at
2192most once.  Defined as:
2193
2194\begin{code}
2195once(Goal) :-
2196    call(Goal), !.
2197\end{code}
2198
2199once/1 can in many cases be replaced with \predref{->}{2}. The only
2200difference is how the cut behaves (see !/0). The following two clauses
2201below are identical. Be careful about the interaction with
2202\predref{;}{2}. The \pllib{apply_macros} library defines an inline
2203expansion of once/1, mapping it to \verb$(Goal->true;fail)$. Using the
2204full if-then-else constructs prevents its semantics from being changed
2205when embedded in a \predref{;}{2} disjunction.
2206
2207\begin{code}
22081) a :- once((b, c)), d.
22092) a :- b, c -> d.
2210\end{code}
2211
2212    \predicate{ignore}{1}{:Goal}
2213Calls \arg{Goal} as once/1, but succeeds, regardless of whether
2214\arg{Goal} succeeded or not. Defined as:
2215
2216\begin{code}
2217ignore(Goal) :-
2218        Goal, !.
2219ignore(_).
2220\end{code}
2221
2222    \predicate{call_with_depth_limit}{3}{:Goal, +Limit, -Result}
2223If \arg{Goal} can be proven without recursion deeper than \arg{Limit}
2224levels, call_with_depth_limit/3 succeeds, binding \arg{Result} to the
2225deepest recursion level used during the proof.  Otherwise, \arg{Result}
2226is unified with \const{depth_limit_exceeded} if the limit was exceeded
2227during the proof, or the entire predicate fails if \arg{Goal} fails
2228without exceeding \arg{Limit}.
2229
2230The depth limit is guarded by the internal machinery. This may differ
2231from the depth computed based on a theoretical model. For example,
2232true/0 is translated into an inline virtual machine instruction. Also,
2233repeat/0 is not implemented as below, but as a non-deterministic foreign
2234predicate.
2235
2236\begin{code}
2237repeat.
2238repeat :-
2239	repeat.
2240\end{code}
2241
2242As a result, call_with_depth_limit/3 may still loop infinitely on programs
2243that should theoretically finish in finite time. This problem can be
2244cured by using Prolog equivalents to such built-in predicates.
2245
2246This predicate may be used for theorem provers to realise techniques
2247like \jargon{iterative deepening}. See also call_with_inference_limit/3.
2248It was implemented after discussion with Steve Moyle
2249\email{smoyle@ermine.ox.ac.uk}.
2250
2251    \predicate{call_with_inference_limit}{3}{:Goal, +Limit, -Result}
2252Equivalent to \term{call}{Goal}, but limits the number of inferences
2253\emph{for each solution of \arg{Goal}}.\footnote{This predicate was
2254realised after discussion with Ulrich Neumerkel and Markus Triska.}.
2255Execution may terminate as follows:
2256
2257    \begin{itemize}
2258	\item If \arg{Goal} does \emph{not} terminate before the
2259	      inference limit is exceeded, \arg{Goal} is aborted by
2260	      injecting the exception \const{inference_limit_exceeded}
2261	      into its execution.  After termination of \arg{Goal},
2262	      \arg{Result} is unified with the atom
2263	      \const{inference_limit_exceeded}.
2264	      \textit{Otherwise},
2265	\item If \arg{Goal} fails, call_with_inference_limit/3 fails.
2266	\item If \arg{Goal} succeeds \emph{without a choice point},
2267	       \arg{Result} is unified with \const{!}.
2268	\item If \arg{Goal} succeeds \emph{with a choice point},
2269	       \arg{Result} is unified with \const{true}.
2270        \item If \arg{Goal} throws an exception, call_with_inference_limit/3
2271	      re-throws the exception.
2272    \end{itemize}
2273
2274An inference is defined as a call or redo on a predicate. Please note
2275that some primitive built-in predicates are compiled to virtual machine
2276instructions for which inferences are not counted. The execution of
2277predicates defined in other languages (e.g., C, C++) count as a single
2278inference. This includes potentially expensive built-in predicates such
2279as sort/2.
2280
2281Calls to this predicate may be nested. An inner call that sets the limit
2282below the current is honoured. An inner call that would terminate after
2283the current limit does not change the effective limit. See also
2284call_with_depth_limit/3 and call_with_time_limit/2.
2285
2286    \predicate{setup_call_cleanup}{3}{:Setup, :Goal, :Cleanup}
2287Calls \exam{(once(Setup), Goal)}. If \arg{Setup} succeeds, \arg{Cleanup}
2288will be called exactly once after \arg{Goal} is finished: either on
2289failure, deterministic success, commit, or an exception. The execution
2290of \arg{Setup} is protected from asynchronous interrupts like
2291call_with_time_limit/2 (package clib) or thread_signal/2. In most uses,
2292\arg{Setup} will perform temporary side-effects required by \arg{Goal}
2293that are finally undone by \arg{Cleanup}.
2294
2295Success or failure of \arg{Cleanup} is ignored, and choice points it
2296created are destroyed (as once/1). If \arg{Cleanup} throws an exception,
2297this is executed as normal while it was not triggered as the result of
2298an exception the exception is propagated as normal. If \arg{Cleanup} was
2299triggered by an exception the rules are described in
2300\secref{urgentexceptions}
2301
2302Typically, this predicate is used to cleanup permanent data storage
2303required to execute \arg{Goal}, close file descriptors, etc. The example
2304below provides a non-deterministic search for a term in a file, closing
2305the stream as needed.
2306
2307\begin{code}
2308term_in_file(Term, File) :-
2309	setup_call_cleanup(open(File, read, In),
2310			   term_in_stream(Term, In),
2311			   close(In) ).
2312
2313term_in_stream(Term, In) :-
2314	repeat,
2315	read(In, T),
2316	(   T == end_of_file
2317	->  !, fail
2318	;   T = Term
2319	).
2320\end{code}
2321
2322Note that it is impossible to implement this predicate in Prolog.  The
2323closest approximation would be to read all terms into a list, close
2324the file and call member/2.  Without setup_call_cleanup/3 there is no
2325way to gain control if the choice point left by repeat/0 is removed by a
2326cut or an exception.
2327
2328setup_call_cleanup/3 can also be used to test determinism of a goal,
2329providing a portable alternative to deterministic/1:
2330
2331\begin{code}
2332?- setup_call_cleanup(true,(X=1;X=2), Det=yes).
2333
2334X = 1 ;
2335
2336X = 2,
2337Det = yes ;
2338\end{code}
2339
2340This predicate is under consideration for inclusion into the ISO standard.
2341For compatibility with other Prolog implementations see call_cleanup/2.
2342
2343    \predicate{setup_call_catcher_cleanup}{4}{:Setup, :Goal, +Catcher, :Cleanup}
2344Similar to \term{setup_call_cleanup}{Setup, Goal, Cleanup} with
2345additional information on the reason for calling \arg{Cleanup}.  Prior
2346to calling \arg{Cleanup}, \arg{Catcher} unifies with the termination
2347code (see below).  If this unification fails, \arg{Cleanup} is
2348\emph{not} called.
2349
2350\begin{description}
2351    \termitem{exit}{}
2352\arg{Goal} succeeded without leaving any choice points.
2353
2354    \termitem{fail}{}
2355\arg{Goal} failed.
2356
2357    \termitem{!}{}
2358\arg{Goal} succeeded with choice points and these are now discarded
2359by the execution of a cut (or other pruning of the search tree such as
2360if-then-else).
2361
2362    \termitem{exception}{Exception}
2363\arg{Goal} raised the given \arg{Exception}.
2364
2365    \termitem{external_exception}{Exception}
2366\arg{Goal} succeeded with choice points and these are now discarded
2367due to an exception.  For example:
2368
2369\begin{code}
2370?- setup_call_catcher_cleanup(true, (X=1;X=2),
2371			      Catcher, writeln(Catcher)),
2372   throw(ball).
2373external_exception(ball)
2374ERROR: Unhandled exception: Unknown message: ball
2375\end{code}
2376
2377\end{description}
2378
2379    \predicate{call_cleanup}{2}{:Goal, :Cleanup}
2380Same as \term{setup_call_cleanup}{true, Goal, Cleanup}.
2381This is provided
2382for compatibility with a number of other Prolog implementations only.  Do
2383not use call_cleanup/2 if you perform side-effects prior to calling
2384that will be undone by \arg{Cleanup}.  Instead, use
2385setup_call_cleanup/3 with an appropriate first argument to perform those
2386side-effects.
2387
2388    \predicate[deprecated]{call_cleanup}{3}{:Goal, +Catcher, :Cleanup}
2389Same as \term{setup_call_catcher_cleanup}{true, Goal, Catcher, Cleanup}.
2390The same warning as for call_cleanup/2 applies.
2391\end{description}
2392
2393
2394\section{Delimited continuations}	     \label{sec:delcont}
2395
2396The predicates reset/3 and shift/1 implement \jargon{delimited
2397continuations} for Prolog. Delimited continuation for Prolog is
2398described in \cite{DBLP:journals/tplp/SchrijversDDW13}
2399(\href{http://www.open-std.org/jtc1/sc22/wg14/www/docs/n1124.pdf}{preprint
2400PDF}). The mechanism allows for proper \jargon{coroutines}, two or more
2401routines whose execution is interleaved, while they exchange data. Note
2402that coroutines in this sense differ from coroutines realised using
2403attributed variables as described in \chapref{clp}.
2404
2405Note that shift/1 captures the \jargon{forward continuation}. It notably
2406does not capture choicepoints. Choicepoints created before the
2407continuation is captures remain open, while choicepoints created when
2408the continuation is executed live their normal life. Unfortunately the
2409consequences for \jargon{committing} a choicepoint is complicated. In
2410general a cut (\predref{!}{0}) in the continuation does not have the
2411expected result. Negation (\predref{\+}{1}) and if-then(-else)
2412(\predref{->}{2}) behave as expected, \emph{provided the continuation is
2413called immediately}. This works because for \predref{\+}{1} and
2414\predref{->}{2} the continuation contains a reference to the choicepoint
2415that must be cancelled and this reference is restored when possible. If,
2416as with tabling, the continuation is saved and called later, the commit
2417has no effect. We illustrate the three scenarios using with the programs
2418below.
2419
2420\begin{code}
2421t1 :-
2422    reset(gbad, ball, Cont),
2423    (   Cont == 0
2424    ->  true
2425    ;   writeln(resuming),
2426        call(Cont)
2427    ).
2428
2429gbad :-
2430    n, !, fail.
2431gbad.
2432
2433n :-
2434    shift(ball),
2435    writeln(n).
2436\end{code}
2437
2438Here, the \predref{!}{0} has \textbf{no effect}:
2439
2440\begin{code}
2441?- t1.
2442resuming
2443n
2444true.
2445\end{code}
2446
2447The second example uses \predref{\+}{1}, which is essentially
2448\exam{(G->fail;true)}.
2449
2450\begin{code}
2451t2 :-
2452    reset(gok, ball, Cont),
2453    (   Cont == 0
2454    ->  true
2455    ;   writeln(resuming),
2456        call(Cont)
2457    ).
2458
2459gok :-
2460    \+ n.
2461\end{code}
2462
2463In this scenario the normal semantics of \predref{\+}{1} is preserved:
2464
2465\begin{code}
2466?- t1.
2467resuming
2468n
2469false.
2470\end{code}
2471
2472In the last example we illustrate what happens if we assert the
2473continuation to be executed later. We write the negation using
2474if-then-else to make it easier to explain the behaviour.
2475
2476\begin{code}
2477:- dynamic cont/1.
2478
2479t3 :-
2480    retractall(cont(_)),
2481    reset(gassert, ball, Cont),
2482    (   Cont == 0
2483    ->  true
2484    ;   asserta(cont(Cont))
2485    ).
2486
2487c3 :-
2488    cont(Cont),
2489    writeln(resuming),
2490    call(Cont).
2491
2492gassert :-
2493    (   n
2494    ->  fail
2495    ;   true
2496    ).
2497\end{code}
2498
2499Now, \nopredref{t3}{0} succeeds \emph{twice}. This is because
2500\nopredref{n}{0} shifts, so the commit to the fail/0 branch is not
2501executed and the true/0 branch is evaluated normally. Calling the
2502continuation later using \nopredref{c3}{0} fails because the choicepoint
2503that realised the if-then-else does not exist in the continuation and
2504thus the effective continuation is the remainder of \nopredref{n}{0} and
2505fail/0 in \nopredref{gassert}{0}.
2506
2507\begin{code}
2508?- t3.
2509true ;
2510true.
2511
2512?- c3.
2513resuming
2514n
2515false.
2516\end{code}
2517
2518
2519The suspension mechanism provided by delimited continuations is used to
2520implement \jargon{tabling} \cite{DBLP:journals/tplp/DesouterDS15},
2521(\href{https://www.cambridge.org/core/journals/theory-and-practice-of-logic-programming/article/div-classtitletabling-as-a-library-with-delimited-controldiv/227B7C0227FD715CF159B6AF894DE96E}{available
2522here}). See \secref{tabling}.
2523
2524\begin{description}
2525    \predicate{reset}{3}{:Goal, ?Ball, -Continuation}
2526Call \arg{Goal}. If \arg{Goal} calls shift/1 and the argument of shift/1
2527can be unified with \arg{Ball},\footnote{The argument order described in
2528\cite{DBLP:journals/tplp/SchrijversDDW13} is
2529\term{reset}{Goal,Continuation,Ball}. We swapped the argument order for
2530compatibility with catch/3} shift/1 causes reset/3 to return, unifying
2531\arg{Continuation} with a goal that represents the \jargon{continuation}
2532after shift/1. In other words, meta-calling \arg{Continuation} completes
2533the execution where shift left it. If \arg{Goal} does not call shift/1,
2534\arg{Continuation} are unified with the integer \const{0}
2535(zero).\footnote{Note that older versions also unify \arg{Ball} with
2536\const{0}.  Testing whether or not shift happened on \arg{Ball} however
2537is \emph{always} ambiguous.}
2538
2539    \predicate{shift}{1}{+Ball}
2540Abandon the execution of the current goal, returning control to just
2541\emph{after} the matching reset/3 call.  This is similar to throw/1
2542except that (1) nothing is `undone' and (2) the 3th argument of
2543reset/3 is unified with the \jargon{continuation}, which allows the
2544code calling reset/3 to \jargon{resume} the current goal.
2545\end{description}
2546
2547
2548\section{Exception handling}
2549\label{sec:exception}
2550
2551The predicates catch/3 and throw/1 provide ISO compliant raising and
2552catching of exceptions.
2553
2554\begin{description}
2555    \predicate[ISO]{catch}{3}{:Goal, +Catcher, :Recover}
2556Behaves as call/1 if no exception is raised when executing \arg{Goal}.
2557If an exception is raised using throw/1 while \arg{Goal} executes, and
2558the \arg{Goal} is the innermost goal for which \arg{Catcher} unifies
2559with the argument of throw/1, all choice points generated by \arg{Goal}
2560are cut, the system backtracks to the start of catch/3 while preserving
2561the thrown exception term, and \arg{Recover} is called as in call/1.
2562
2563The overhead of calling a goal through catch/3 is comparable to
2564call/1.  Recovery from an exception is much slower, especially if the
2565exception term is large due to the copying thereof or is decorated with
2566a stack trace using, e.g., the library \pllib{prolog_stack} based on the
2567prolog_exception_hook/4 hook predicate to rewrite exceptions.
2568
2569    \predicate[ISO]{throw}{1}{+Exception}
2570Raise an exception. The system looks for the innermost catch/3
2571ancestor for which \arg{Exception} unifies with the \arg{Catcher}
2572argument of the catch/3 call.  See catch/3 for details.
2573
2574ISO demands that throw/1 make a copy of \arg{Exception}, walk up the
2575stack to a catch/3 call, backtrack and try to unify the copy of
2576\arg{Exception} with \arg{Catcher}. SWI-Prolog delays backtracking until
2577it actually finds a matching catch/3 goal. The advantage is that we can
2578start the debugger at the first possible location while preserving the
2579entire exception context if there is no matching catch/3 goal. This
2580approach can lead to different behaviour if \arg{Goal} and \arg{Catcher}
2581of catch/3 call shared variables. We assume this to be highly unlikely
2582and could not think of a scenario where this is useful.%
2583	\footnote{I'd like to acknowledge Bart Demoen for his
2584	          clarifications on these matters.}
2585
2586In addition to explicit calls to throw/1, many built-in predicates throw
2587exceptions directly from C. If the \arg{Exception} term cannot be copied
2588due to lack of stack space, the following actions are tried in order:
2589
2590\begin{enumerate}
2591    \item If the exception is of the form \term{error}{Formal, ImplementationDefined},
2592try to raise the exception without the \arg{ImplementationDefined} part.
2593    \item Try to raise \term{error}{\term{resource_error}{stack}, global}.
2594    \item Abort (see abort/0).
2595\end{enumerate}
2596
2597If an exception is raised in a call-back from C (see \chapref{foreign})
2598and not caught in the same call-back, PL_next_solution() fails and
2599the exception context can be retrieved using PL_exception().
2600
2601    \predicate{catch_with_backtrace}{3}{:Goal, +Catcher, :Recover}
2602As catch/3, but if library \pllib{prolog_stack} is loaded and an
2603exception of the shape \term{error}{Format, Context} is raised
2604\arg{Context} is extended with a backtrace.  To catch an error
2605and print its message including a backtrace, use the following
2606template:
2607
2608\begin{code}
2609:- use_module(library(prolog_stack)).
2610
2611    ...,
2612    catch_with_backtrace(Goal, Error,
2613			 print_message(error, Error)),
2614    ...,
2615\end{code}
2616
2617This is good practice for a \jargon{catch-all} wrapper around an
2618application.  See also main/0 from library \pllib{main}.
2619\end{description}
2620
2621
2622\subsection{Urgency of exceptions}
2623\label{sec:urgentexceptions}
2624
2625Under some conditions an exception may be raised as a result of handling
2626another exception.  Below are some of the scenarios:
2627
2628\begin{itemize}
2629    \item
2630The predicate setup_call_cleanup/3 calls the cleanup handler as a result
2631of an exception and the cleanup handler raises an exception itself. In
2632this case the most \jargon{urgent} exception is propagated into the
2633environment.
2634    \item
2635Raising an exception fails due to lack of resources, e.g., lack of
2636stack space to store the exception. In this case a resource exception is
2637raised. If that too fails the system tries to raise a resource exception
2638without (stack) context. If that fails it will raise the exception
2639\verb='$aborted'=, also raised by abort/0. As no stack space is
2640required for processing this atomic exception, this should always
2641succeed.
2642    \item
2643Certain \jargon{callback} operations raise an exception while processing
2644another exception or a previous callback already raised an exception
2645before there was an opportunity to process the exception. The most
2646notable \jargon{callback} subject to this issue are prolog_event_hook/1
2647(supporting e.g., the graphical debugger), prolog_exception_hook/4
2648(rewriting exceptions, e.g., by adding context) and print_message/2 when
2649called from the core facilities such as the internal debugger. As with
2650setup_call_cleanup/3, the most \jargon{urgent} exception is preserved.
2651\end{itemize}
2652
2653If the most urgent exceptions needs to be preserved, the following
2654exception ordering is respected, preserving the topmost matching error.
2655
2656\begin{enumerate}
2657    \item \verb='$aborted'= (abort/0)
2658    \item \verb$time_limit_exceeded$ (call_with_time_limit/2)
2659    \item \term{error}{\term{resource_error}{Resource}, Context}
2660    \item \term{error}{Formal, Context}
2661    \item All other exceptions
2662\end{enumerate}
2663
2664\paragraph{Note} The above resolution is not described in the ISO
2665standard. This is not needed either because ISO does not specify
2666setup_call_cleanup/3 and does not deal with environment management
2667issues such as (debugger) callbacks. Neither does it define abort/0 or
2668timeout handling. Notably abort/0 and timeout are non-logical control
2669structures. They are implemented on top of exceptions as they need to
2670unwind the stack, destroy choice points and call cleanup handlers in
2671the same way.  However, the pending exception should not be replaced
2672by another one before the intended handler is reached.  The abort
2673exception cannot be caught, something which is achieved by wrapping
2674the \jargon{cleanup handler} of catch/3 into
2675\term{call_cleanup}{Handler, abort}.
2676
2677
2678\subsection{Debugging and exceptions}
2679\label{sec:debugexceptions}
2680
2681\index{exceptions,debugging}%
2682\index{debugging,exceptions}%
2683Before the introduction of exceptions in SWI-Prolog a runtime error was
2684handled by printing an error message, after which the predicate failed.
2685If the Prolog flag \prologflag{debug_on_error} was in effect (default),
2686the tracer was switched on. The combination of the error message and
2687trace information is generally sufficient to locate the error.
2688
2689With exception handling, things are different. A programmer may wish to
2690trap an exception using catch/3 to avoid it reaching the user. If the
2691exception is not handled by user code, the interactive top level will
2692trap it to prevent termination.
2693
2694If we do not take special precautions, the context information
2695associated with an unexpected exception (i.e., a programming error) is
2696lost. Therefore, if an exception is raised which is not caught using
2697catch/3 and the top level is running, the error will be printed, and the
2698system will enter trace mode.
2699
2700If the system is in a non-interactive call-back from foreign code and
2701there is no catch/3 active in the current context, it cannot determine
2702whether or not the exception will be caught by the external routine
2703calling Prolog.  It will then base its behaviour on the Prolog flag
2704\prologflag{debug_on_error}:
2705
2706\begin{itemlist}
2707    \item [current_prolog_flag(debug_on_error, false)]
2708The exception does not trap the debugger and is returned to the foreign
2709routine calling Prolog, where it can be accessed using PL_exception().
2710This is the default.
2711    \item [current_prolog_flag(debug_on_error, true)]
2712If the exception is not caught by Prolog in the current context, it will
2713trap the tracer to help analyse the context of the error.
2714\end{itemlist}
2715
2716While looking for the context in which an exception takes place, it is
2717advised to switch on debug mode using the predicate debug/0. The hook
2718prolog_exception_hook/4 can be used to add more debugging facilities to
2719exceptions. An example is the library \pllib{http/http_error},
2720generating a full stack trace on errors in the HTTP server library.
2721
2722\subsection{The exception term}         \label{sec:exceptterm}
2723
2724
2725\subsubsection{General form of the ISO standard exception term}
2726\label{sec:generalformofexceptionterm}
2727
2728The predicate throw/1 takes a single argument, the \jargon{exception
2729term}, and the ISO standard stipulates that the exception term
2730be of the form \term{error}{Formal, Context} with:
2731
2732\begin{itemlist}
2733\item [\arg{Formal}] the `formal' description of the error, as
2734listed in chapter 7.12.2 pp. 62-63 ("Error classification") of the
2735ISO standard. It indicates the \jargon{error class} and possibly
2736relevant \jargon{error context} information.
2737It may be a compound term of arity 1,2 or 3 - or simply an atom if
2738there is no relevant error context information.
2739
2740\item [\arg{Context}] additional context information beyond
2741the one in \arg{Formal}. If may be unset, i.e. a fresh variable, or
2742set to something that hopefully will help the programmer in debugging.
2743The structure of \arg{Context} is left unspecified by the ISO
2744Standard, so SWI-Prolog creates it own convention (see below).
2745\end{itemlist}
2746
2747Thus, constructing an error term and throwing it might take
2748this form (although you would not use the illustrative explicit
2749naming given here; instead composing the exception term directly in
2750a one-liner):
2751
2752\begin{code}
2753Exception = error(Formal, Context),
2754Context   = ... some local convention ...,
2755Formal    = type_error(ValidType, Culprit), % for "type error" for example
2756ValidType = integer,                        % valid atoms are listed in the ISO standard
2757Culprit   = ... some value ...,
2758throw(Exception)
2759\end{code}
2760
2761Note that the ISO standard formal term expresses \emph{what should be
2762the case} or \emph{what is the expected correct state}, and not
2763\emph{what is the problem}.  For example:
2764
2765\begin{itemlist}
2766    \item If a variable is found to be uninstantiated but should be instantiated,
2767the error term is \const{instantiation_error}: The problem is not that there is an
2768unwanted instantiation, but that the correct state is the one with an
2769instantiated variable.
2770
2771    \item In case a variable is found to be instantiated but should be uninstantiated
2772(because it will be used for output), the error term is
2773\term{uninstantiation_error}{Culprit}: The problem is not that there is
2774lack of instantiation, but that the correct state is the one which
2775\arg{Culprit} (or one of its subterms) is more uninstantiated than
2776is the case.
2777
2778    \item If you try to disassemble an empty list with compound_name_arguments/3,
2779the error term is \term{type_error}{compound,[]}. The problem is not
2780that \const{[]} is (erroneously) a compound term, but that a compound
2781term is expected and \const{[]} does not belong to that class.
2782\end{itemlist}
2783
2784\subsubsection{Throwing exceptions from applications and libraries}
2785\label{sec:throwsfromuserpreds}
2786
2787User predicates are free to choose the structure of their \jargon{exception
2788term}s (i.e., they can define their own conventions) but \emph{should}
2789adhere to the ISO standard if possible, in particular for libraries.
2790
2791Notably, exceptions of the shape \term{error}{Formal,Context} are
2792recognised by the development tools and therefore expressing unexpected
2793situations using these exceptions improves the debugging experience.
2794
2795In SWI-Prolog, the second argument of the exception term, i.e., the
2796\arg{Context} argument, is generally of the form
2797\term{context}{Location, Message}, where:
2798
2799\begin{itemlist}
2800\item [\arg{Location}] describes the execution context in which the
2801exception occurred. While the \arg{Location} argument may be specified
2802as a predicate indicator (\arg{Name}/\arg{Arity}), it is typically filled
2803by the \pllib{prolog_stack} library. This library recognises uncaught
2804errors or errors caught by catch_with_backtrace/3 and fills the
2805\arg{Location} argument with a \jargon{backtrace}.
2806
2807\item [\arg{Message}] provides an additional description of the error
2808or can be left as a fresh variable if there is nothing appropriate to
2809fill in.
2810\end{itemlist}
2811
2812ISO standard exceptions can be thrown via the predicates exported
2813from \pllib{error}. Termwise, these predicates look exactly like the
2814\arg{Formal} of the ISO standard error term they throw:
2815
2816\begin{itemlist}
2817\item instantiation_error/1 (the argument is not used: ISO specifies no argument)
2818\item uninstantiation_error/1
2819\item type_error/2
2820\item domain_error/2
2821\item existence_error/2
2822\item existence_error/3 (a SWI-Prolog extension that is not ISO)
2823\item permission_error/3
2824\item representation_error/1
2825\item resource_error/1
2826\item syntax_error/1
2827\end{itemlist}
2828
2829
2830\section{Printing messages}			\label{sec:printmsg}
2831
2832The predicate print_message/2 is used to print a message term in a
2833human-readable format. The other predicates from this section allow the user
2834to refine and extend the message system. A common usage of
2835print_message/2 is to print error messages from exceptions. The code
2836below prints errors encountered during the execution of \arg{Goal},
2837without further propagating the exception and without starting the
2838debugger.
2839
2840\begin{code}
2841	...,
2842	catch(Goal, E,
2843	      ( print_message(error, E),
2844		fail
2845	      )),
2846	...
2847\end{code}
2848
2849Another common use is to define message_hook/3 for printing messages
2850that are normally \jargon{silent}, suppressing messages, redirecting
2851messages or make something happen in addition to printing the message.
2852
2853\begin{description}
2854    \predicate{print_message}{2}{+Kind, +Term}
2855The predicate print_message/2 is used by the system and libraries to
2856print messages. \arg{Kind} describes the nature of the message, while
2857\arg{Term} is a Prolog term that describes the content. Printing
2858messages through this indirection instead of using format/3 to the
2859stream \const{user_error} allows displaying the message appropriate
2860to the application (terminal, logfile, graphics), acting on messages
2861based on their content instead of a string (see message_hook/3) and
2862creating language specific versions of the messages.  See also
2863\secref{libprintmsg}.  The following message kinds are known:
2864
2865\begin{description}
2866    \termitem{banner}{}
2867The system banner message. Banner messages can be suppressed by setting
2868the Prolog flag \prologflag{verbose} to \const{silent}.
2869
2870    \termitem{debug}{Topic}
2871Message from library(debug).  See debug/3.
2872
2873    \termitem{error}{}
2874The message indicates an erroneous situation.  This kind is used to
2875print uncaught exceptions of type \term{error}{Formal, Context}. See
2876section introduction (\secref{printmsg}).
2877
2878    \termitem{help}{}
2879User requested help message, for example after entering `h' or `?' to
2880a prompt.
2881
2882    \termitem{information}{}
2883Information that is requested by the user.  An example is statistics/0.
2884
2885    \termitem{informational}{}
2886Typically messages of events and progress that are considered useful
2887to a developer.  Such messages can be suppressed by setting the
2888Prolog flag \prologflag{verbose} to \const{silent}.
2889
2890    \termitem{silent}{}
2891Message that is normally not printed. Applications may define
2892message_hook/3 to act upon such messages.
2893
2894    \termitem{trace}{}
2895Messages from the (command line) tracer.
2896
2897    \termitem{warning}{}
2898The message indicates something dubious that is not considered fatal.
2899For example, discontiguous predicates (see discontiguous/1).
2900\end{description}
2901
2902The predicate print_message/2 first translates the \arg{Term} into a
2903list of `message lines' (see print_message_lines/3 for details). Next,
2904it calls the hook message_hook/3 to allow the user to intercept the
2905message. If message_hook/3 fails it prints the message unless \arg{Kind}
2906is \const{silent}.
2907
2908The print_message/2 predicate and its rules are in the file
2909\file{<plhome>/boot/messages.pl}, which may be inspected for more
2910information on the error messages and related error terms. If you need
2911to write messages from your own predicates, it is recommended to reuse
2912the existing message terms if applicable. If no existing message term is
2913applicable, invent a fairly unique term that represents the event and
2914define a rule for the multifile predicate prolog:message//1. See
2915\secref{libprintmsg} for a deeper discussion and examples.
2916
2917See also message_to_string/2.
2918
2919    \predicate{print_message_lines}{3}{+Stream, +Prefix, +Lines}
2920Print a message (see print_message/2) that has been translated to
2921a list of message elements.  The elements of this list are:
2922
2923\begin{description}
2924    \termitem{<Format>-<Args>}{}
2925        Where \arg{Format} is an atom and \arg{Args} is a list
2926	of format arguments.  Handed to format/3.
2927    \termitem{flush}{}
2928	If this appears as the last element, \arg{Stream} is flushed
2929	(see flush_output/1) and no final newline is generated.  This
2930	is combined with a subsequent message that starts with
2931	\const{at_same_line} to complete the line.
2932    \termitem{at_same_line}{}
2933        If this appears as first element, no prefix is printed for
2934	the first line and the line position is not forced to 0
2935	(see format/1, \verb$~N$).
2936    \termitem{ansi}{+Attributes, +Format, +Args}
2937	This message may be intercepted by means of the hook
2938	prolog:message_line_element/2.  The library \pllib{ansi_term}
2939	implements this hook to achieve coloured output. If it is not
2940	intercepted it invokes \term{format}{Stream, Format, Args}.
2941    \termitem{nl}{}
2942        A new line is started.  If the message is not complete,
2943	\arg{Prefix} is printed before the remainder of the message.
2944    \termitem{begin}{Kind, Var}
2945    \nodescription
2946    \termitem{end}{Var}
2947	The entire message is headed by \term{begin}{Kind, Var} and
2948	ended by \term{end}{Var}.  This feature is used by, e.g.,
2949	library \pllib{ansi_term} to colour entire messages.
2950    \termitem{<Format>}{}
2951        Handed to format/3 as \term{format}{Stream, Format, []}.
2952	Deprecated because it is ambiguous if \arg{Format} collides
2953	with one of the atomic commands.
2954\end{description}
2955
2956See also print_message/2 and message_hook/3.
2957
2958    \predicate{message_hook}{3}{+Term, +Kind, +Lines}
2959Hook predicate that may be defined in the module \const{user} to
2960intercept messages from print_message/2. \arg{Term} and \arg{Kind} are
2961the same as passed to print_message/2. \arg{Lines} is a list of format
2962statements as described with print_message_lines/3.  See also
2963message_to_string/2.
2964
2965This predicate must be defined dynamic and multifile to allow other
2966modules defining clauses for it too.
2967
2968    \predicate{thread_message_hook}{3}{+Term, +Kind, +Lines}
2969As message_hook/3, but this predicate is local to the calling thread
2970(see thread_local/1).  This hook is called \emph{before} message_hook/3.
2971The `pre-hook' is indented to catch messages they may be produced by
2972calling some goal without affecting other threads.
2973
2974    \predicate{message_property}{2}{+Kind, ?Property}
2975This hook can be used to define additional message kinds and the way
2976they are displayed.  The following properties are defined:
2977
2978    \begin{description}
2979	\termitem{color}{-Attributes}
2980Print message using ANSI terminal attributes.  See ansi_format/3
2981for details.  Here is an example, printing help messages in blue:
2982
2983\begin{code}
2984:- multifile user:message_property/2.
2985
2986user:message_property(help, color([fg(blue)])).
2987\end{code}
2988
2989	\termitem{prefix}{-Prefix}
2990Prefix printed before each line.  This argument is handed to format/3.
2991The default is \verb$'~N'$. For example, messages of kind
2992\const{warning} use \verb$'~NWarning: '$.
2993
2994	\termitem{location_prefix}{+Location, -FirstPrefix, -ContinuePrefix}
2995Used for printing messages that are related to a source location.
2996Currently, \arg{Location} is a term \mbox{\arg{File}:\arg{Line}}.
2997\arg{FirstPrefix} is the prefix for the first line and
2998\arg{-ContinuePrefix} is the prefix for continuation lines.  For
2999example, the default for errors is
3000
3001\begin{code}
3002location_prefix(File:Line,
3003		'~NERROR: ~w:~d:'-[File,Line], '~N\t')).
3004\end{code}
3005
3006	\termitem{stream}{-Stream}
3007Stream to which to print the message. Default is \const{user_error}.
3008
3009	\termitem{wait}{-Seconds}
3010Amount of time to wait after printing the message. Default is not to
3011wait.
3012    \end{description}
3013
3014    \predicate{prolog:message_line_element}{2}{+Stream, +Term}
3015This hook is called to print the individual elements of a message from
3016print_message_lines/3. This hook is used by e.g., library
3017\pllib{ansi_term} to colour messages on ANSI-capable terminals.
3018
3019    \predicate{prolog:message_prefix_hook}{2}{+ContextTerm, -Prefix}
3020This hook is called to add context to the message prefix.
3021\arg{ContextTerm} is a member of the list provided by the
3022\prologflag{message_context}. \arg{Prefix} must be unified with an
3023atomic value that is added to the message prefix.
3024
3025    \predicate{message_to_string}{2}{+Term, -String}
3026Translates a message term into a string object (see \secref{strings}).
3027
3028    \predicate{version}{0}{}
3029Write the SWI-Prolog banner message as well as additional messages
3030registered using version/1. This is the default \jargon{initialization
3031goal} which can be modified using \cmdlineoption{-g}.
3032
3033    \predicate{version}{1}{+Message}
3034Register additional messages to be printed by version/0. Each registered
3035message is handed to the message translation DCG and can thus be defined
3036using the hook prolog:message//1.  If not defined, it is simply printed.
3037\end{description}
3038
3039
3040\subsection{Printing from libraries}		\label{sec:libprintmsg}
3041
3042Libraries should \emph{not} use format/3 or other output predicates
3043directly. Libraries that print informational output directly to the
3044console are hard to use from code that depend on your textual output,
3045such as a CGI script. The predicates in \secref{printmsg} define the API
3046for dealing with messages. The idea behind this is that a library that
3047wants to provide information about its status, progress, events or
3048problems calls print_message/2. The first argument is the
3049\jargon{level}. The supported levels are described with print_message/2.
3050Libraries typically use \const{informational} and \const{warning}, while
3051libraries should use exceptions for errors (see throw/1, type_error/2,
3052etc.).
3053
3054The second argument is an arbitrary Prolog term that carries the
3055information of the message, but \emph{not} the precise text. The text is
3056defined by the grammar rule prolog:message//1. This distinction is made
3057to allow for translations and to allow hooks processing the information
3058in a different way (e.g., to translate progress messages into a
3059progress bar).
3060
3061For example, suppose we have a library that must download data from the
3062Internet (e.g., based on http_open/3). The library wants to print the
3063progress after each downloaded file.  The code below is a good skeleton:
3064
3065\begin{code}
3066download_urls(List) :-
3067	length(List, Total),
3068	forall(nth1(I, List, URL),
3069	       (   download_url(URL),
3070		   print_message(informational,
3071				 download_url(URL, I, Total)))).
3072\end{code}
3073
3074The programmer can now specify the default textual output using the rule
3075below. Note that this rule may be in the same file or anywhere else.
3076Notably, the application may come with several rule sets for different
3077languages. This, and the user-hook example below are the reason to
3078represent the message as a compound term rather than a string. This is
3079similar to using message numbers in non-symbolic languages. The
3080documentation of print_message_lines/3 describes the elements that may
3081appear in the output list.
3082
3083\begin{code}
3084:- multifile
3085	prolog:message//1.
3086
3087prolog:message(download_url(URL, I, Total)) -->
3088	{ Perc is round(I*100/Total) },
3089	[ 'Downloaded ~w; ~D from ~D (~d%)'-[URL, I, Total, Perc] ].
3090\end{code}
3091
3092A \emph{user} of the library may define rules for message_hook/3.   The
3093rule below acts on the message content.  Other applications can act on
3094the message level and, for example, popup a message box for warnings and
3095errors.
3096
3097\begin{code}
3098:- multifile user:message_hook/3.
3099
3100message_hook(download_url(URL, I, Total), _Kind, _Lines) :-
3101	<send this information to a GUI component>
3102\end{code}
3103
3104In addition, using the command line option \cmdlineoption{-q}, the user
3105can disable all \jargon{informational} messages.
3106
3107
3108\section{Handling signals}			\label{sec:signal}
3109
3110As of version 3.1.0, SWI-Prolog is able to handle software interrupts
3111(signals) in Prolog as well as in foreign (C) code (see \secref{csignal}).
3112
3113Signals are used to handle internal errors (execution of a non-existing
3114CPU instruction, arithmetic domain errors, illegal memory access,
3115resource overflow, etc.), as well as for dealing with asynchronous
3116interprocess communication.
3117
3118Signals are defined by the POSIX standard and part of all Unix machines.
3119The MS-Windows Win32 provides a subset of the signal handling routines,
3120lacking the vital functionality to raise a signal in another thread for
3121achieving asynchronous interprocess (or interthread) communication
3122(Unix kill() function).
3123
3124\begin{description}
3125    \predicate{on_signal}{3}{+Signal, -Old, :New}
3126Determines how \arg{Signal} is processed.  \arg{Old} is unified with
3127the old behaviour, while the behaviour is switched to \arg{New}.  As
3128with similar environment control predicates, the current value is
3129retrieved using \exam{on_signal(Signal, Current, Current)}.
3130
3131The action description is an atom denoting the name of the predicate
3132that will be called if \arg{Signal} arrives. on_signal/3 is a
3133meta-predicate, which implies that <Module>:<Name> refers to <Name>/1
3134in module <Module>. The handler is called with a single argument:
3135the name of the signal as an atom. The Prolog names for signals are
3136explained below.
3137
3138Three names have special meaning. \const{throw} implies Prolog will map
3139the signal onto a Prolog exception as described in \secref{exception},
3140\const{debug} specifies the debug interrupt prompt that is initially
3141bound to \const{SIGINT} (Control-C) and \const{default} resets the
3142handler to the settings active before SWI-Prolog manipulated the
3143handler.
3144
3145Signals bound to a foreign function through PL_signal() are reported
3146using the term \term{'\$foreign_function'}{Address}.
3147
3148After receiving a signal mapped to \const{throw}, the exception raised
3149has the following structure:
3150
3151\begin{quote}\tt
3152error(signal(<SigName>, <SigNum>), <Context>)
3153\end{quote}
3154
3155The signal names are defined by the POSIX standard as symbols of the
3156form {\tt SIG}<SIGNAME>. The Prolog name for a signal is the lowercase
3157version of <SIGNAME>. The predicate current_signal/3 may be used to map
3158between names and signals.
3159
3160Initially, the following signals are handled unless the command line
3161option \cmdlineoption{--no-signals} is specified:
3162
3163\begin{description}
3164    \definition{int}
3165Prompts the user, allowing to inspect the current state of the process
3166and start the tracer.
3167    \definition{usr2}
3168Bound to an empty signal handler used to make blocking system calls
3169return.  This allows thread_signal/2 to interrupt threads blocked in
3170a system call.  See also prolog_alert_signal/2.
3171    \definition{hup, term, abrt, quit}
3172Causes normal Prolog cleanup (e.g., at_halt/1) before terminating the
3173process with the same signal.
3174    \definition{segv, ill, bus, sys}
3175Dumps the C and Prolog stacks and runs cleanup before terminating the
3176process with the same signal.
3177    \definition{fpe, alrm, xcpu, xfsz, vtalrm}
3178Throw a Prolog exception (see above).
3179\end{description}
3180
3181    \predicate{current_signal}{3}{?Name, ?Id, ?Handler}
3182Enumerate the currently defined signal handling.  \arg{Name} is the
3183signal name, \arg{Id} is the numerical identifier and \arg{Handler}
3184is the currently defined handler (see on_signal/3).
3185
3186    \predicate{prolog_alert_signal}{2}{?Old, +New}
3187Query or set the signal used to unblock blocking system calls on Unix
3188systems and process pending Prolog signals. The default is
3189\const{SIGUSR2}. See also \cmdlineoption{--sigalert}.
3190\end{description}
3191
3192
3193\subsection{Notes on signal handling}
3194\label{sec:signalhandling}
3195
3196Before deciding to deal with signals in your application, please
3197consider the following:
3198
3199\begin{itemlist}
3200    \item[Portability]
3201On MS-Windows, the signal interface is severely limited. Different Unix
3202brands support different sets of signals, and the relation between
3203signal name and number may vary. Currently, the system only supports
3204signals numbered 1 to 32\footnote{TBD: the system should support the
3205Unix realtime signals}. Installing a signal outside the limited set of
3206supported signals in MS-Windows crashes the application.
3207
3208    \item[Safety]
3209Immediately delivered signals (see below) are unsafe. This implies that
3210foreign functions called from a handler cannot safely use the SWI-Prolog
3211API and	cannot use C longjmp().  Handlers defined as \const{throw} are
3212unsafe.  Handlers defined to call a predicate are safe.  Note that the
3213predicate can call throw/1, but the delivery is delayed until Prolog
3214is in a safe state.
3215
3216The C-interface described in \secref{csignal} provides the option
3217\const{PL_SIGSYNC} to select either safe synchronous or unsafe
3218asynchronous delivery.
3219
3220    \item[Time of delivery]
3221Using \const{throw} or a foreign handler, signals are delivered
3222immediately (as defined by the OS). When using a Prolog predicate,
3223delivery is delayed to a safe moment.  Blocking system calls or
3224foreign loops may cause long delays.  Foreign code can improve
3225on that by calling PL_handle_signals().
3226
3227Signals are blocked when the garbage collector is active.
3228\end{itemlist}
3229
3230
3231\section{DCG Grammar rules}			\label{sec:DCG}
3232
3233\index{DCG}\index{serialize}\index{deserialize}%
3234Grammar rules form a comfortable interface to \jargon{difference lists}.
3235They are designed both to support writing parsers that build a parse
3236tree from a list of characters or tokens and for generating a flat list
3237from a term.
3238
3239Grammar rules look like ordinary clauses using \functor{-->}{2} for
3240separating the head and body rather than \functor{:-}{2}. Expanding
3241grammar rules is done by expand_term/2, which adds two additional
3242arguments to each term for representing the difference list.
3243
3244The body of a grammar rule can contain three types of terms. A callable
3245term is interpreted as a reference to a grammar rule. Code between
3246\verb${$\ldots\verb$}$ is interpreted as plain Prolog code, and finally,
3247a list is interpreted as a sequence of \jargon{literals}. The Prolog
3248control-constructs (\functor{\+}{1}, \functor{->}{2}, \functor{;}/2,
3249\functor{,}{2} and \functor{!}{0}) can be used in grammar rules.
3250
3251We illustrate the behaviour by defining a rule set for parsing an
3252integer.
3253
3254\begin{code}
3255integer(I) -->
3256	digit(D0),
3257	digits(D),
3258	{ number_codes(I, [D0|D])
3259	}.
3260
3261digits([D|T]) -->
3262	digit(D), !,
3263	digits(T).
3264digits([]) -->
3265	[].
3266
3267digit(D) -->
3268	[D],
3269	{ code_type(D, digit)
3270	}.
3271\end{code}
3272
3273Grammar rule sets are called using the built-in predicates phrase/2
3274and phrase/3:
3275
3276\begin{description}
3277    \predicate{phrase}{2}{:DCGBody, ?List}
3278Equivalent to \exam{phrase(\arg{DCGBody}, \arg{InputList}, [])}.
3279    \predicate{phrase}{3}{:DCGBody, ?List, ?Rest}
3280True when \arg{DCGBody} applies to the difference
3281\arg{List}/\arg{Rest}. Although \arg{DCGBody} is typically a
3282\jargon{callable} term that denotes a grammar rule, it can be any
3283term that is valid as the body of a DCG rule.
3284
3285The example below calls the rule set integer//1 defined in \secref{DCG}
3286and available from \pllib{library(dcg/basics)}, binding \arg{Rest} to
3287the remainder of the input after matching the integer.
3288
3289\begin{code}
3290?- [library(dcg/basics)].
3291?- atom_codes('42 times', Codes),
3292   phrase(integer(X), Codes, Rest).
3293X = 42
3294Rest = [32, 116, 105, 109, 101, 115]
3295\end{code}
3296
3297The next example exploits a complete body. Given the following
3298definition of \nodcgref{digit_weight}{1}, we can pose the query
3299below.
3300
3301\begin{code}
3302digit_weight(W) -->
3303	[D],
3304	{ code_type(D, digit(W)) }.
3305\end{code}
3306
3307\begin{code}
3308?- atom_codes('Version 3.4', Codes),
3309   phrase(("Version ",
3310	   digit_weight(Major),".",digit_weight(Minor)),
3311	  Codes).
3312Major = 3,
3313Minor = 4.
3314\end{code}
3315
3316The SWI-Prolog implementation of phrase/3 verifies that the \arg{List}
3317and \arg{Rest} arguments are unbound, bound to the empty list or a list
3318\jargon{cons cell}. Other values raise a type error.\footnote{The ISO
3319standard allows for both raising a type error and accepting any term
3320as input and output. Note the tail of the list is not checked for
3321performance reasons.}  The predicate call_dcg/3 is provided to use
3322grammar rules with terms that are not lists.
3323
3324Note that the syntax for lists of codes changed in SWI-Prolog version~7
3325(see \secref{strings}). If a DCG body is translated, both \verb$"text"$
3326and \verb$`text`$ is a valid code-list literal in version~7. A version~7
3327string (\verb$"text"$) is \textbf{not} acceptable for the second and
3328third arguments of phrase/3. This is typically not a problem for
3329applications as the input of a DCG rarely appears in the source code.
3330For testing in the toplevel, one must use double quoted text in versions
3331prior to~7 and back quoted text in version~7 or later.
3332
3333See also portray_text/1, which can be used to print lists of character
3334codes as a string to the top level and debugger to facilitate debugging
3335DCGs that process character codes. The library \pllib{apply_macros}
3336compiles phrase/3 if the argument is sufficiently instantiated,
3337eliminating the runtime overhead of translating \arg{DCGBody} and
3338meta-calling.
3339
3340    \predicate{call_dcg}{3}{:DCGBody, ?State0, ?State}
3341As phrase/3, but without type checking \arg{State0} and \arg{State}.
3342This allows for using DCG rules for threading an arbitrary state
3343variable. This predicate was introduced after type checking was added to
3344phrase/3.\footnote{After discussion with Samer Abdallah.}
3345
3346A portable solution for threading state through a DCG can be implemented
3347by wrapping the state in a list and use the DCG semicontext facility.
3348Subsequently, the following predicates may be used to access and modify
3349the state:\footnote{This solution was proposed by Markus Triska.}
3350
3351\begin{code}
3352state(S), [S] --> [S].
3353state(S0, S), [S] --> [S0].
3354\end{code}
3355\end{description}
3356
3357As stated above, grammar rules are a general interface to difference
3358lists. To illustrate, we show a DCG-based implementation of
3359reverse/2:
3360
3361\begin{code}
3362reverse(List, Reversed) :-
3363	phrase(reverse(List), Reversed).
3364
3365reverse([])    --> [].
3366reverse([H|T]) --> reverse(T), [H].
3367\end{code}
3368
3369
3370\section{Database}			\label{sec:db}
3371
3372SWI-Prolog offers several ways to store data in globally accessible
3373memory, i.e., outside the Prolog \jargon{stacks}. Data stored this way
3374notably does not change on \jargon{backtracking}. Typically it is a bad
3375idea to use any of the predicates in this section for realising global
3376variables that can be assigned to. Typically, first consider
3377representing data processed by your program as terms passed around as
3378predicate arguments. If you need to reason over multiple solutions to a
3379goal, consider findall/3, aggregate/3 and related predicates.
3380
3381Nevertheless, there are scenarios where storing data outside the Prolog
3382stacks is a good option. Below are the main options for storing data:
3383
3384\begin{description}
3385    \item[Using dynamic predicates]
3386Dynamic predicates are predicates for which the list of clauses is
3387modified at runtime using asserta/1, assertz/1, retract/1 or
3388retractall/1. Following the ISO standard, predicates that are modified
3389this way need to be declared using the dynamic/1 \jargon{directive}.
3390These facilities are defined by the ISO standard and widely supported.
3391The mechanism is often considered slow in the literature. Performance
3392depends on the Prolog implementation. In SWI-Prolog, querying dynamic
3393predicates has the same performance as static ones. The manipulation
3394predicates are fast. Using retract/1 or retractall/1 on a predicate
3395registers the predicate as `dirty'. Dirty predicates are cleaned by
3396garbage_collect_clauses/0, which is normally automatically invoked. Some
3397workloads may result in significant performance reduction due to
3398skipping retracted clauses and/or clause garbage collection.
3399
3400Dynamic predicates can be wrapped using library \pllib{persistency} to
3401maintain a backup of the data on disk. Dynamic predicates come in two
3402flavours, \jargon{shared} between threads and \jargon{local} to each
3403thread. The latter version is created using the directive
3404thread_local/1.
3405
3406    \item[The recorded database]
3407The `recorded database' registers a list of terms with a \jargon{key},
3408an atom or compound term. The list is managed using recorda/3, recordz/3
3409and erase/1. It is queried using recorded/3. The recorded database is
3410not part of the ISO standard but fairly widely supported, notably in
3411implementations building on the `Edinburgh tradition'.  There are few
3412reasons to use this database in SWI-Prolog due to the good performance
3413of dynamic predicates.  Advantages are (1) the handle provides a direct
3414reference to a term, (2) cyclic terms can be stored and (3) attributes
3415(\secref{attvar}) are preserved.  Disadvantages are (1) the terms in
3416a list associated with a key are not indexed, (2) the poorly specified
3417\jargon{immediate update semantics} (see \secref{update} applies to the
3418recorded database and (3) reduced portability.
3419
3420    \item[The flag/3 predicate]
3421The predicate flag/3 associates one simple value (number or atom) with
3422a key (atom, integer or compound).  It is an old SWI-Prolog specific
3423predicate that should be considered deprecated, although there is no
3424plan to remove it.
3425
3426    \item[Using global variables]
3427The predicates b_setval/2 and nb_setval/2 associate a term living on the
3428Prolog stack with a name, either backtrackable or non-backtrackable.
3429Backtrackable and non-backtrackable assignment without using a global
3430name can be realised with setarg/3 and nb_setarg/3.  Notably the latter
3431are used to realise aggregation as e.g., aggregate_all/3 performs.
3432
3433    \item[Tries]
3434As of version 7.3.21, SWI-Prolog provides \jargon{tries} (prefix trees)
3435to associate a term \jargon{variant} with a value. Tries have been
3436introduced to support \arg{tabling} and are described in \secref{trie}.
3437\end{description}
3438
3439\subsection{Managing (dynamic) predicates}
3440\label{sec:dynpreds}
3441
3442\begin{description}
3443    \predicate[ISO]{abolish}{1}{:PredicateIndicator}
3444Removes all clauses of a predicate with functor \arg{Functor} and arity
3445\arg{Arity} from the database. All predicate attributes (dynamic,
3446multifile, index, etc.) are reset to their defaults. Abolishing an
3447imported predicate only removes the import link; the predicate will keep
3448its old definition in its definition module.
3449
3450According to the ISO standard, abolish/1 can only be applied to dynamic
3451procedures.  This is odd, as for dealing with dynamic procedures there
3452is already retract/1 and retractall/1.  The abolish/1 predicate was
3453introduced in DEC-10 Prolog precisely for dealing with static procedures.
3454In SWI-Prolog, abolish/1 works on static procedures, unless the Prolog
3455flag \prologflag{iso} is set to \const{true}.
3456
3457It is advised to use retractall/1 for erasing all clauses of a dynamic
3458predicate.
3459
3460    \predicate{abolish}{2}{+Name, +Arity}
3461Same as \term{abolish}{Name/Arity}. The predicate abolish/2 conforms
3462to the Edinburgh standard, while abolish/1 is ISO compliant.
3463
3464    \predicate{copy_predicate_clauses}{2}{:From, :To}
3465Copy all clauses of predicate \arg{From} to \arg{To}. The predicate
3466\arg{To} must be dynamic or undefined. If \arg{To} is undefined, it is
3467created as a dynamic predicate holding a copy of the clauses of
3468\arg{From}. If \arg{To} is a dynamic predicate, the clauses of
3469\arg{From} are added (as in assertz/1) to the clauses of \arg{To}.
3470\arg{To} and \arg{From} must have the same arity. Acts as if defined by
3471the program below, but at a much better performance by avoiding
3472decompilation and compilation.
3473
3474\begin{code}
3475copy_predicate_clauses(From, To) :-
3476	head(From, MF:FromHead),
3477	head(To, MT:ToHead),
3478	FromHead =.. [_|Args],
3479	ToHead =.. [_|Args],
3480	forall(clause(MF:FromHead, Body),
3481	       assertz(MT:ToHead, Body)).
3482
3483head(From, M:Head) :-
3484	strip_module(From, M, Name/Arity),
3485	functor(Head, Name, Arity).
3486\end{code}
3487
3488    \predicate{redefine_system_predicate}{1}{+Head}
3489This directive may be used both in module \const{user} and in normal
3490modules to redefine any system predicate.  If the system definition is
3491redefined in module \const{user}, the new definition is the default
3492definition for all sub-modules.  Otherwise the redefinition is local
3493to the module.  The system definition remains in the module \const{system}.
3494
3495Redefining system predicate facilitates the definition of compatibility
3496packages.  Use in other contexts is discouraged.
3497
3498    \predicate[ISO,nondet]{retract}{1}{+Term}
3499When \arg{Term} is an atom or a term it is unified with the first
3500unifying fact or clause in the database. The fact or clause is removed
3501from the database. The retract/1 predicate respects the \jargon{logical
3502update view}. This implies that retract/1 succeeds for all clauses that
3503match \arg{Term} when the predicate was \emph{called}. The example below
3504illustrates that the first call to retract/1 succeeds on \const{bee} on
3505backtracking despite the fact that \const{bee} is already
3506retracted.\footnote{Example by Jan Burse}
3507
3508\begin{code}
3509:- dynamic insect/1.
3510insect(ant).
3511insect(bee).
3512
3513?- (   retract(insect(I)),
3514       writeln(I),
3515       retract(insect(bee)),
3516       fail
3517   ;   true
3518   ).
3519ant ;
3520bee.
3521\end{code}
3522
3523If multiple threads start a retract on the same predicate at the same
3524time their notion of the \jargon{entry generation} is adjusted such that
3525they do not retract the same first clause. This implies that, if
3526multiple threads use \verb$once(retract(Term))$, no two threads will
3527retract the same clause. Note that on backtracking over retract/1,
3528multiple threads may retract the same clause as both threads respect the
3529logical update view.
3530
3531    \predicate[ISO,det]{retractall}{1}{+Head}
3532All facts or clauses in the database for which the \arg{head}
3533unifies with \arg{Head} are removed. If \arg{Head} refers to a predicate
3534that is not defined, it is implicitly created as a dynamic predicate.
3535See also dynamic/1.\footnote{The ISO standard only allows using
3536dynamic/1 as a \jargon{directive}.}
3537
3538    \predicate[ISO]{asserta}{1}{+Term}
3539\nodescription
3540    \predicate[ISO]{assertz}{1}{+Term}
3541\nodescription
3542    \predicate[deprecated]{assert}{1}{+Term}
3543Assert a clause (fact or rule) into the database. The predicate
3544asserta/1 asserts the clause as first clause of the predicate while
3545assertz/1 assert the clause as last clause. The deprecated assert/1 is
3546equivalent to assertz/1. If the program space for the target module is
3547limited (see set_module/1), asserta/1 can raise a
3548\term{resource_error}{program_space} exception.  The example below
3549adds two facts and a rule.  Note the double parentheses around the
3550rule.
3551
3552\begin{code}
3553?- assertz(parent('Bob', 'Jane')).
3554?- assertz(female('Jane')).
3555?- assertz((mother(Child, Mother) :-
3556	        parent(Child, Mother),
3557	        female(Mother))).
3558\end{code}
3559
3560    \predicate{asserta}{2}{+Term, -Reference}
3561\nodescription
3562    \predicate{assertz}{2}{+Term, -Reference}
3563\nodescription
3564    \predicate[deprecated]{assert}{2}{+Term, -Reference}
3565Equivalent to asserta/1, assertz/1, assert/1, but in addition unifies
3566\arg{Reference} with a handle to the asserted clauses. The handle can be
3567used to access this clause with clause/3 and erase/1.
3568\end{description}
3569
3570\subsection{The recorded database}
3571\label{sec:recdb}
3572
3573\begin{description}
3574    \predicate{recorda}{3}{+Key, +Term, -Reference}
3575Assert \arg{Term} in the recorded database under key \arg{Key}.
3576\arg{Key} is a small integer (range \prologflag{min_tagged_integer}
3577\ldots \prologflag{max_tagged_integer}, atom or compound term. If the
3578key is a compound term, only the name and arity define the key.
3579\arg{Reference} is unified with an opaque handle to the record (see
3580erase/1).
3581
3582    \predicate{recorda}{2}{+Key, +Term}
3583Equivalent to \exam{recorda(\arg{Key}, \arg{Term}, _)}.
3584
3585    \predicate{recordz}{3}{+Key, +Term, -Reference}
3586Equivalent to recorda/3, but puts the \arg{Term} at the tail of the terms
3587recorded under \arg{Key}.
3588
3589    \predicate{recordz}{2}{+Key, +Term}
3590Equivalent to \exam{recordz(\arg{Key}, \arg{Term}, _)}.
3591
3592    \predicate{recorded}{3}{?Key, ?Value, ?Reference}
3593True if \arg{Value} is recorded under \arg{Key} and has the given
3594database \arg{Reference}. If \arg{Reference} is given, this predicate is
3595semi-deterministic. Otherwise, it must be considered non-deterministic.
3596If neither \arg{Reference} nor \arg{Key} is given, the triples are
3597generated as in the code snippet below.\footnote{Note that, without a
3598given \arg{Key}, some implementations return triples in the order
3599defined by recorda/2 and recordz/2.}  See also current_key/1.
3600
3601\begin{code}
3602	current_key(Key),
3603	recorded(Key, Value, Reference)
3604\end{code}
3605
3606    \predicate{recorded}{2}{+Key, -Value}
3607Equivalent to \exam{recorded(\arg{Key}, \arg{Value}, _)}.
3608
3609    \predicate{erase}{1}{+Reference}
3610Erase a record or clause from the database.  \arg{Reference} is a
3611db-reference returned by recorda/3, recordz/3 or recorded/3, clause/3,
3612assert/2, asserta/2 or assertz/2. Fail silently if the referenced object
3613no longer exists. Notably, if multiple threads attempt to erase the same
3614clause one will succeed and the others will fail.
3615
3616    \predicate{instance}{2}{+Reference, -Term}
3617Unify \arg{Term} with the referenced clause or database record.  Unit
3618clauses are represented as \arg{Head} :- \const{true}.
3619\end{description}
3620
3621
3622\subsection{Flags}				\label{sec:flag}
3623
3624The predicate flag/3 is the oldest way to store global non-backtrackable
3625data in SWI-Prolog. Flags are global and shared by all threads. Their
3626value is limited to atoms, small (64-bit) integers and floating point
3627numbers.  Flags are thread-safe.  The flags described in this section
3628must not be confused with \jargon{Prolog flags} described in
3629\secref{flags}.
3630
3631\begin{description}
3632    \predicate{get_flag}{2}{+Key, -Value}
3633True when \arg{Value} is the value currently associated with \arg{Key}.
3634If \arg{Key} does not exist, a new flag with value `0' (zero) is
3635created.
3636    \predicate{set_flag}{2}{+Key, Value}
3637Set flag \arg{Key} to \arg{Value}. Value must be an atom, small (64-bit)
3638integer or float.
3639    \predicate{flag}{3}{+Key, -Old, +New}
3640True when \arg{Old} is the current value of the flag \arg{Key} and the
3641flag has been set to \arg{New}. \arg{New} can be an arithmetic
3642expression. The update is \jargon{atomic}. This predicate can be used to
3643create a \emph{shared} global counter as illustrated in the example
3644below.
3645
3646\begin{code}
3647next_id(Id) :-
3648    flag(my_id, Id, Id+1).
3649\end{code}
3650\end{description}
3651
3652\subsection{Tries}
3653\label{sec:trie}
3654
3655Tries (also called \jargon{digital tree}, \jargon{radix tree} or
3656\jargon{prefix tree} maintain a mapping between a variant of a term (see
3657\predref{=@=}{2}) and a value. They have been introduced in SWI-Prolog
36587.3.21 as part of the implementation of \jargon{tabling}. The current
3659implementation is rather immature.   In particular, the following
3660limitations currently apply:
3661
3662\begin{shortlist}
3663    \item Tries are not thread-safe.
3664    \item Tries should not be modified while non-deterministic
3665          predicates such as trie_gen/3 are running on the trie.
3666    \item Terms cannot have \jargon{attributed variables}.
3667    \item Terms cannot be \jargon{cyclic}.  Possibly this will
3668	  not change because cyclic terms can only be supported
3669          after creating a canonical form of the term.
3670\end{shortlist}
3671
3672\textbf{We give the definition of these predicates for reference and
3673debugging tabled predicates.  Future versions are likely to get a more
3674stable and safer implementation. The API to tries should not be
3675considered stable.}
3676
3677
3678\begin{description}
3679    \predicate{trie_new}{1}{-Trie}
3680Create a new trie and unify \arg{Trie} with a handle to the trie.  The
3681trie handle is a \jargon{blob}. Tries are subject to atom garbage
3682collection.
3683
3684    \predicate{trie_destroy}{1}{+Trie}
3685Destroy \arg{Trie}. This removes all nodes from the trie and causes
3686further access to \arg{Trie} to raise an existence_error exception. The
3687handle itself is reclaimed by atom garbage collection.
3688
3689    \predicate[semidet]{is_trie}{1}{@Trie}
3690True when \arg{Trie} is a trie object.  See also current_trie/1.
3691
3692    \predicate[nondet]{current_trie}{1}{-Trie}
3693True if \arg{Trie} is a currently existing trie.  As this enumerates and
3694then filters all known atoms this predicate is slow and should only be
3695used for debugging purposes.  See also is_trie/1.
3696
3697    \predicate{trie_insert}{2}{+Trie, +Key}
3698Insert the term \arg{Key} into \arg{Trie}. If \arg{Key} is already part
3699of \arg{Trie} the predicates \emph{fails} silently.  This is the same
3700as trie_insert/3, but using a fixed reserved \arg{Value}.
3701
3702    \predicate{trie_insert}{3}{+Trie, +Key, +Value}
3703Insert the term \arg{Key} into \arg{Trie} and associate it with
3704\arg{Value}. \arg{Value} can be any term.  If \arg{Key}-\arg{Value}
3705is already part of \arg{Trie}, the predicates \emph{fails} silently.
3706If \arg{Key} is in \arg{Trie} associated with a different value, a
3707\const{permission_error} is raised.
3708
3709    \predicate{trie_update}{3}{+Trie, +Key, +Value}
3710As trie_insert/3, but if \arg{Key} is in \arg{Trie}, its associated
3711value is \emph{updated}.
3712
3713    \predicate{trie_insert}{4}{+Trie, +Term, +Value, -Handle}
3714As trie_insert/3, returning a handle to the trie node. This predicate is
3715currently unsafe as \arg{Handle} is an integer used to encode a pointer.
3716It was used to implement a pure Prolog version of the \pllib{tabling}
3717library.
3718
3719    \predicate{trie_delete}{3}{+Trie, +Key, ?Value}
3720Delete \arg{Key} from \arg{Trie} if the value associated with \arg{Key}
3721unifies with \arg{Value}.
3722
3723    \predicate{trie_lookup}{3}{+Trie, +Key, -Value}
3724True if the term \arg{Key} is in \arg{Trie} and associated with
3725\arg{Value}.
3726
3727    \predicate{trie_term}{2}{+Handle, -Term}
3728True when \arg{Term} is a copy of the term associated with \arg{Handle}.
3729The result is undefined (including crashes) if \arg{Handle} is not a
3730handle returned by trie_insert_new/3 or the node has been removed
3731afterwards.
3732
3733    \predicate[nondet]{trie_gen}{2}{+Trie, ?Key}
3734True when \arg{Key} is a member of \arg{Trie}.  See also
3735trie_gen_compiled/2.
3736
3737    \predicate[nondet]{trie_gen}{3}{+Trie, ?Key, -Value}
3738True when \arg{Key} is associated with \arg{Value} in \arg{Trie}.
3739Backtracking retrieves all pairs. Currently scans the entire
3740trie, even if \arg{Key} is partly known.  Currently unsafe if \arg{Trie}
3741is modified while the values are being enumerated.  See also
3742trie_gen_compiled/3.
3743
3744    \predicate[nondet]{trie_gen_compiled}{2}{+Trie, ?Key}
3745\nodescription
3746    \predicate[nondet]{trie_gen_compiled}{3}{+Trie, ?Key, -Value}
3747Similar to trie_gen/3, but uses a \jargon{compiled} representation of
3748\arg{Trie}. The compiled representation is created lazily and
3749manipulations of the trie (insert, delete) invalidate the current
3750compiled representation. The compiled representation generates answers
3751faster and, as it runs on a snapshot of the trie, is immune to
3752concurrent modifications of the trie.  This predicate is used to
3753generate answers from \jargon{answer tries} as used for tabled
3754execution.  See \secref{tabling}.
3755
3756    \predicate[nondet]{trie_property}{2}{?Trie, ?Property}
3757True if \arg{Trie} exists with \arg{Property}.	 Intended for
3758debugging and statistical purposes.  Retrieving some of these
3759properties visit all nodes of the trie. Defined properties are
3760    \begin{description}
3761	\termitem{value_count}{-Count}
3762    Number of key-value pairs in the trie.
3763	\termitem{node_count}{-Count}
3764    Number of nodes in the trie.
3765	\termitem{size}{-Bytes}
3766    Required storage space of the trie.
3767	\termitem{compiled_size}{-Bytes}
3768    Required storage space for the compiled representation as used
3769    by trie_gen_compiled/2,3.
3770	\termitem{hashed}{-Count}
3771    Number of nodes that use a hashed index to its children.
3772	\termitem{lookup_count}{-Count}
3773    Number of trie_lookup/3 calls (only when compiled with
3774    \const{O_TRIE_STATS}).
3775	\termitem{gen_call_count}{-Count}
3776    Number of trie_gen/3 calls (only when compiled with
3777    \const{O_TRIE_STATS}).
3778	\termitem{wait}{-Count}
3779    Number of times a thread waited on this trie for another
3780    thread to complete it (shared tabling, only when compiled with
3781    \const{O_TRIE_STATS}).
3782	\termitem{deadlock}{-Count}
3783    Number of times this trie was part of a deadlock and its completion
3784    was abandoned (shared tabling, only when compiled with
3785    \const{O_TRIE_STATS}).
3786    \end{description}
3787
3788In addition, a number of additional properties are defined on
3789\jargon{answer tries}.
3790
3791    \begin{description}
3792	\termitem{invalidated}{-Count}
3793    Number of times the trie was invalidated (incremental tabling).
3794	\termitem{reevaluated}{-Count}
3795    Number of times the trie was re-evaluated (incremental tabling).
3796	\termitem{idg_affected_count}{-Count}
3797    Number of answer tries affected by this one (incremental tabling).
3798	\termitem{idg_dependent_count}{-Count}
3799    Number of answer tries this one depends on (incremental tabling).
3800	\termitem{idg_size}{-Bytes}
3801    Number of bytes in the IDG node representation.
3802    \end{description}
3803\end{description}
3804
3805
3806\subsection{Update view}			\label{sec:update}
3807
3808\index{logical,update view}%
3809\index{immediate, update view}%
3810\index{update view}%
3811Traditionally, Prolog systems used the \jargon{immediate update view}:
3812new clauses became visible to predicates backtracking over dynamic
3813predicates immediately, and retracted clauses became invisible
3814immediately.
3815
3816Starting with SWI-Prolog 3.3.0 we adhere to the \jargon{logical update
3817view}, where backtrackable predicates that enter the definition of a
3818predicate will not see any changes (either caused by assert/1 or
3819retract/1) to the predicate.  This view is the ISO standard, the
3820most commonly used and the most `safe'.%
3821    \footnote{For example, using the immediate update view, no call to a
3822	      dynamic predicate is deterministic.}
3823Logical updates are realised by keeping reference counts on predicates
3824and \jargon{generation} information on clauses.  Each change to the
3825database causes an increment of the generation of the database.  Each
3826goal is tagged with the generation in which it was started.  Each clause
3827is flagged with the generation it was created in as well as the generation
3828it was erased from.  Only clauses with a `created' \ldots `erased' interval
3829that encloses the generation of the current goal are considered visible.
3830
3831
3832\subsection{Indexing databases}			\label{sec:hashterm}
3833
3834\index{indexing,term-hashes}%
3835
3836The indexing capabilities of SWI-Prolog are described in
3837\secref{jitindex}. Summarizing, SWI-Prolog creates indexes for any
3838applicable argument, pairs of arguments and indexes on the arguments of
3839compound terms when applicable. Extended JIT indexing is not widely
3840supported among Prolog implementations. Programs that aim at
3841portability should consider using term_hash/2 and term_hash/4 to design
3842their database such that indexing on constant or functor (name/arity
3843reference) on the first argument is sufficient. In some cases, using the
3844predicates below to add one or more additional columns (arguments) to a
3845database predicate may improve performance. The overall design of code
3846using these predicates is given below. Note that as term_hash/2 leaves
3847the hash unbound if \arg{Term} is not ground. This causes the lookup to
3848be fast if \arg{Term} is ground and correct (but slow) otherwise.
3849
3850\begin{code}
3851:- dynamic
3852    x/2.
3853
3854assert_x(Term) :-
3855    term_hash(Term, Hash),
3856    assertz(x(Hash, Term)).
3857
3858x(Term) :-
3859    term_hash(Term, Hash),
3860    x(Hash, Term).
3861\end{code}
3862
3863
3864\begin{description}
3865    \predicate[det]{term_hash}{2}{+Term, -HashKey}
3866If \arg{Term} is a ground term (see ground/1), \arg{HashKey} is unified
3867with a positive integer value that may be used as a hash key to the
3868value. If \arg{Term} is not ground, the predicate leaves \arg{HashKey}
3869an unbound variable.  Hash keys are in the range $0 \ldots 16,777,215$,
3870the maximal integer that can be stored efficiently on both 32 and 64
3871bit platforms.
3872
3873This predicate may be used to build hash tables as well as to exploit
3874argument indexing to find complex terms more quickly.
3875
3876The hash key does not rely on temporary information like addresses of
3877atoms and may be assumed constant over different invocations and
3878versions of SWI-Prolog.\footnote{Last change: version 5.10.4} Hashes
3879differ between big and little endian machines. The term_hash/2 predicate
3880is cycle-safe.\bug{All arguments that (indirectly) lead to a cycle
3881have the same hash key.}
3882
3883    \predicate[det]{term_hash}{4}{+Term, +Depth, +Range, -HashKey}
3884As term_hash/2, but only considers \arg{Term} to the specified
3885\arg{Depth}.   The top-level term has depth 1, its arguments have
3886depth 2, etc.  That is, $\arg{Depth} = 0$ hashes nothing; $\arg{Depth} = 1$
3887hashes atomic values or the functor and arity of a compound term,
3888not its arguments; $\arg{Depth} = 2$ also indexes the immediate
3889arguments, etc.
3890
3891\arg{HashKey} is in the range $[0 \ldots \arg{Range}-1]$.  \arg{Range}
3892must be in the range $[1 \ldots 2147483647]$.
3893
3894    \predicate[det]{variant_sha1}{2}{+Term, -SHA1}
3895Compute a SHA1-hash from \arg{Term}. The hash is represented as a
389640-byte hexadecimal atom. Unlike term_hash/2 and friends, this predicate
3897produces a hash key for non-ground terms. The hash is invariant over
3898variable-renaming (see \predref{=@=}{2}) and constants over different
3899invocations of Prolog.\bug{The hash depends on word order
3900(big/little-endian) and the wordsize (32/64 bits).}
3901
3902This predicate raises an exception when trying to compute the hash on
3903a cyclic term or attributed term.  Attributed terms are not handled
3904because subsumes_chk/2 is not considered well defined for attributed
3905terms.  Cyclic terms are not supported because this would require
3906establishing a canonical cycle.  That is, given A=[a|A] and B=[a,a|B],
3907\arg{A} and \arg{B} should produce the same hash.  This is not
3908(yet) implemented.
3909
3910This hash was developed for lookup of solutions to a goal stored in a
3911table.  By using a cryptographic hash, heuristic algorithms can often
3912ignore the possibility of hash collisions and thus avoid storing the
3913goal term itself as well as testing using \predref{=@=}{2}.
3914
3915    \predicate[det]{variant_hash}{2}{+Term, -HashKey}
3916Similar to variant_sha1/2, but using a non-cryptographic hash and
3917produces an integer result like term_hash/2. This version does deal with
3918attributed variables, processing them as normal variables.  This hash is
3919primarily intended to speedup finding variant terms in a set of terms.
3920\bug{As variant_sha1/2, cyclic terms result in an exception.}
3921\end{description}
3922
3923
3924\section{Declaring predicate properties}	\label{ch:dynamic}
3925\label{sec:declare}
3926
3927This section describes directives which manipulate attributes of
3928predicate definitions. The functors dynamic/1, multifile/1,
3929discontiguous/1 and public/1 are operators of priority 1150 (see op/3),
3930which implies that the list of predicates they involve can just be a
3931comma-separated list:
3932
3933\begin{code}
3934:- dynamic
3935        foo/0,
3936        baz/2.
3937\end{code}
3938
3939In SWI-Prolog all these directives are just predicates. This implies
3940they can also be called by a program.  Do not rely on this feature if
3941you want to maintain portability to other Prolog implementations.
3942
3943Notably with the introduction of tabling (see \secref{tabling}) it is
3944common that a set of predicates require multiple options to be set.
3945SWI-Prolog offers two mechanisms to cope with this. The predicate
3946dynamic/2 can be used to make a list of predicates dynamic and set
3947additional options. In addition and for compatibility with
3948XSB,\footnote{Note that \const{as} is in XSB a high-priority operator
3949and in SWI a low-priority and therefore both the sets of predicate
3950indicators as multiple options require parenthesis.} all the predicates
3951below accept a term \term{as}{(:PredicateIndicator, \ldots),
3952(+Options)}, where \arg{Options} is a \jargon{comma-list} of one of more
3953of the following options:
3954
3955\begin{description}
3956    \termitem{incremental}{}
3957Include a dynamic predicate into the incremental tabling dependency
3958graph.  See \secref{tabling-incremental}.
3959    \termitem{opaque}{}
3960Opposite of \const{incremental}. For XSB compatibility.\footnote{In XSB,
3961\const{opaque} is distinct from the default in the sense that dynamic
3962switching between \const{opaque} and \const{incremental} is allowed.}
3963    \termitem{abstract}{Level}
3964Used together with \const{incremental} to reduce the dependency graph.
3965See \secref{tabling-incremental}.
3966    \termitem{volatile}{}
3967Do not save this predicate.  See volatile/1.
3968    \termitem{multifile}{}
3969Predicate may have clauses in multiple clauses.  See multifile/1.
3970    \termitem{discontiguous}{}
3971Predicate clauses may not be contiguous in the file. See
3972discontiguous/1.
3973    \termitem{shared}{}
3974Dynamic predicate is shared between all threads.  This is currently
3975the default.
3976    \termitem{local}{}
3977    \nodescription
3978    \termitem{private}{}
3979Dynamic predicate has distinct set of clauses in each thread.  See
3980thread_local/1.
3981\end{description}
3982
3983Below are some examples, where the last two are semantically identical.
3984
3985\begin{code}
3986:- dynamic person/2 as incremental.
3987:- dynamic (person/2,organization/2) as (incremental, abstract(0)).
3988:- dynamic([ person/2,
3989	     organization/2
3990	   ],
3991	   [ incremental(true),
3992	     abstract(0)
3993	   ]).
3994\end{code}
3995
3996
3997\begin{description}
3998    \prefixop[ISO]{dynamic}{:PredicateIndicator, \ldots}
3999Informs the interpreter that the definition of the predicate(s) may change
4000during execution (using assert/1 and/or retract/1). In the
4001multithreaded version, the clauses of dynamic predicates are shared
4002between the threads. The directive thread_local/1 provides an
4003alternative where each thread has its own clause list for the
4004predicate.  Dynamic predicates can be turned into static ones using
4005compile_predicates/1.
4006
4007    \predicate{dynamic}{2}{:ListOfPredicateIndicators, +Options}
4008As dynamic/1, but allows for setting additional properties. This
4009predicate allows for setting multiple properties on multiple
4010predicates in a single call.  SWI-Prolog also offers the XSB
4011compatible \exam{:- dynamic (p/1) as (incremental,abstract(0)).}
4012syntax. See the introduction of \secref{declare}. Defined \arg{Options}
4013are:
4014
4015    \begin{description}
4016    \termitem{incremental}{+Boolean}
4017Make the dynamic predicate signal depending \jargon{tables}.  See
4018\secref{tabling-incremental}.
4019    \termitem{abstract}{0}
4020This option must be used together with \const{incremental}.  The
4021only supported value is \exam{0}. With this option a call to the
4022incremental dynamic predicate is recorded as the most generic
4023term for the predicate rather than the specific variant.
4024    \termitem{thread}{+Local}
4025\arg{Local} is one of \const{shared} (default) or \const{local}.
4026See also thread_local/1.
4027    \termitem{multifile}{+Boolean}
4028    \nodescription
4029    \termitem{discontiguous}{+Boolean}
4030    \nodescription
4031    \termitem{volatile}{+Boolean}
4032Set the corresponding property.  See multifile/1, discontiguous/1
4033and volatile/1.
4034    \end{description}
4035
4036    \predicate{compile_predicates}{1}{:ListOfPredicateIndicators}
4037Compile a list of specified dynamic predicates (see dynamic/1 and
4038assert/1) into normal static predicates.  This call tells the Prolog
4039environment the definition will not change anymore and further calls
4040to assert/1 or retract/1 on the named predicates raise a permission
4041error.  This predicate is designed to deal with parts of the program
4042that are generated at runtime but do not change during the remainder
4043of the program execution.%
4044	\footnote{The specification of this predicate is from
4045		  Richard O'Keefe.  The implementation is allowed to
4046		  optimise the predicate.  This is not yet implemented.
4047		  In multithreaded Prolog, however, static code runs
4048		  faster as it does not require synchronisation.  This
4049		  is particularly true on SMP hardware.}
4050
4051    \prefixop[ISO]{multifile}{:PredicateIndicator, \ldots}
4052Informs the system that the specified predicate(s) may be defined over
4053more than one file. This stops consult/1 from redefining a predicate
4054when a new definition is found.
4055
4056    \prefixop[ISO]{discontiguous}{:PredicateIndicator, \ldots}
4057Informs the system that the clauses of the specified predicate(s) might
4058not be together in the source file.  See also style_check/1.
4059
4060    \prefixop{public}{:PredicateIndicator, \ldots}
4061Instructs the cross-referencer that the predicate can be called. It has
4062no semantics.\footnote{This declaration is compatible with SICStus. In
4063YAP, public/1 instructs the compiler to keep the source. As the source
4064is always available in SWI-Prolog, our current interpretation also
4065enhances the compatibility with YAP.} The public declaration can be
4066queried using predicate_property/2. The public/1 directive does
4067\emph{not} export the predicate (see module/1 and export/1). The public
4068directive is used for (1) direct calls into the module from, e.g.,
4069foreign code, (2) direct calls into the module from other modules, or (3)
4070flag a predicate as being called if the call is generated by meta-calling constructs that are not analysed by the cross-referencer.
4071
4072    \prefixop{non_terminal}{:PredicateIndicator, \ldots}
4073Sets the \const{non_terminal} property on the predicate. This indicates
4074that the predicate implements a \jargon{grammar rule}. See
4075predicate_property/2. The \const{non_terminal} property is set for
4076predicates exported as \mbox{\arg{Name}//\arg{Arity}} as well as
4077predicates that have at least one clause written using the
4078\functor{-->}{2} notation.
4079\end{description}
4080
4081\section{Examining the program}		\label{sec:examineprog}
4082
4083\begin{description}
4084    \predicate{current_atom}{1}{-Atom}
4085Successively unifies \arg{Atom} with all atoms known to the system.
4086Note that current_atom/1 always succeeds if \arg{Atom} is instantiated to
4087an atom.
4088
4089    \predicate{current_blob}{2}{?Blob, ?Type}
4090Examine the type or enumerate blobs of the given \arg{Type}.  Typed
4091blobs are supported through the foreign language interface for
4092storing arbitrary BLOBs (Binary Large Object) or handles to external
4093entities. See \secref{blob} for details.
4094
4095    \predicate{current_functor}{2}{?Name, ?Arity}
4096True when \arg{Name}/\arg{Arity} is a known functor. This means that at
4097some point in time a term with name \arg{Name} and \arg{Arity} arguments
4098was created. Functor objects are currently not subject to garbage
4099collection. Due to timing, \nopredref{t}{2} below with instantiated
4100\arg{Name} and \arg{Arity} can theoretically fail, i.e., a functor may
4101be visible in instantiated mode while it is not yet visible in unbound
4102mode.  Considering that the only practical value of current_functor/2
4103we are aware of is to analyse resource usage we accept this impure
4104behaviour.
4105
4106\begin{code}
4107t(Name, Arity) :-
4108    (   current_functor(Name, Arity)
4109    ->  current_functor(N, A), N == Name, A == Arity
4110    ;   true
4111    ).
4112\end{code}
4113
4114    \predicate{current_flag}{1}{-FlagKey}
4115Successively unifies \arg{FlagKey} with all keys used for flags (see
4116flag/3).
4117
4118    \predicate{current_key}{1}{-Key}
4119Successively unifies \arg{Key} with all keys used for records (see
4120recorda/3, etc.).
4121
4122    \predicate[ISO]{current_predicate}{1}{:PredicateIndicator}
4123True if \arg{PredicateIndicator} is a currently defined predicate. A
4124predicate is considered defined if it exists in the specified module, is
4125imported into the module or is defined in one of the modules from which
4126the predicate will be imported if it is called (see
4127\secref{importmodule}). Note that current_predicate/1 does \emph{not}
4128succeed for predicates that can be \jargon{autoloaded} unless they are
4129imported using autoload/2. See also current_predicate/2 and
4130predicate_property/2.
4131
4132If \arg{PredicateIndicator} is not fully specified, the predicate only
4133generates values that are defined in or already imported into the target
4134module. Generating all callable predicates therefore requires
4135enumerating modules using current_module/1. Generating predicates
4136callable in a given module requires enumerating the import modules
4137using import_module/2 and the autoloadable predicates using the
4138predicate_property/2 \const{autoload}.
4139
4140    \predicate{current_predicate}{2}{?Name, :Head}
4141Classical pre-ISO implementation of current_predicate/1, where the
4142predicate is represented by the head term.  The advantage is that
4143this can be used for checking the existence of a predicate before calling
4144it without the need for functor/3:
4145
4146\begin{code}
4147call_if_exists(G) :-
4148	current_predicate(_, G),
4149	call(G).
4150\end{code}
4151
4152Because of this intended usage, current_predicate/2 also succeeds if the
4153predicate can be autoloaded.  Unfortunately, checking the autoloader
4154makes this predicate relatively slow, in particular because a failed
4155lookup of the autoloader will cause the autoloader to verify that its
4156index is up-to-date.
4157
4158    \predicate{predicate_property}{2}{:Head, ?Property}
4159True when \arg{Head} refers to a predicate that has property
4160\arg{Property}. With sufficiently instantiated \arg{Head},
4161predicate_property/2 tries to resolve the predicate the same way as
4162calling it would do: if the predicate is not defined it scans the
4163default modules (see default_module/2) and finally tries the autoloader.
4164Unlike calling, failure to find the target predicate causes
4165predicate_property/2 to fail silently. If \arg{Head} is not sufficiently
4166bound, only currently locally defined and already imported predicates
4167are enumerated. See current_predicate/1 for enumerating all predicates.
4168A common issue concerns \emph{generating} all built-in predicates. This
4169can be achieved using the code below:
4170
4171\begin{code}
4172generate_built_in(Name/Arity) :-
4173    predicate_property(system:Head, built_in),
4174    functor(Head, Name, Arity),
4175    \+ sub_atom(Name, 0, _, _, $).   % discard reserved names
4176\end{code}
4177
4178The predicate predicate_property/2 is covered by part-II of the ISO
4179standard (modules). Although we are not aware of any Prolog system that
4180implements part-II of the ISO standard, predicate_property/2 is available
4181in most systems. There is little consensus on the implemented properties
4182though. SWI-Prolog's \jargon{auto loading} feature further complicate
4183this predicate.
4184
4185\arg{Property} is one of:
4186
4187\begin{description}
4188    \termitem{autoload}{File}
4189True if the predicate can be autoloaded from the file \arg{File}.
4190Like \const{undefined}, this property is \emph{not} generated.
4191
4192    \termitem{built_in}{}
4193True if the predicate is locked as a built-in predicate. This
4194implies it cannot be redefined in its definition module and it can
4195normally not be seen in the tracer.
4196
4197    \termitem{defined}{}
4198True if the predicate is defined.  This property is aware of sources
4199being \emph{reloaded}, in which case it claims the predicate defined
4200only if it is defined in another source or it has seen a definition
4201in the current source.  See compile_aux_clauses/1.
4202
4203    \termitem{dynamic}{}
4204True if assert/1 and retract/1 may be used to modify the predicate.
4205This property is set using dynamic/1.
4206
4207    \termitem{exported}{}
4208True if the predicate is in the public list of the context module.
4209
4210    \termitem{imported_from}{Module}
4211Is true if the predicate is imported into the context module from
4212module \arg{Module}.
4213
4214    \termitem{file}{FileName}
4215Unify \arg{FileName} with the name of the source file in which the
4216predicate is defined.  See also source_file/2 and the property
4217\const{line_count}.  Note that this reports the file of the
4218first clause of a predicate.  A more robust interface can be
4219achieved using nth_clause/3 and clause_property/2.
4220
4221    \termitem{foreign}{}
4222True if the predicate is defined in the C language.
4223
4224    \termitem{implementation_module}{-Module}
4225True when \arg{Module} is the module in which \arg{Head} is or will be
4226defined. Resolving this property goes through the same search mechanism
4227as when an undefined predicate is encountered, but does not perform
4228any loading.  It searches (1) the module inheritance hierarchy (see
4229default_module/2) and (2) the autoload index if the \prologflag{unknown}
4230flag is not set to \const{fail} in the target module.
4231
4232    \termitem{indexed}{Indexes}
4233\arg{Indexes} is a list of additional (hash) indexes on the predicate.
4234Each element of the list is a term \arg{ArgSpec}-\arg{Index}.
4235\arg{ArgSpec} denotes the indexed argument(s) and is one of
4236
4237\begin{description}
4238    \termitem{single}{Argument}
4239Hash on a single argument.  \arg{Argument} is the 1-based argument
4240number.
4241    \termitem{multi}{ArgumentList}
4242Hash on a combination of arguments.
4243    \termitem{deep}{Position}
4244Index on a sub-argument.  Position is a list holding first the
4245argument of the predicate then the argument into the compound
4246and recursively into deeper compound terms.
4247\end{description}
4248
4249\arg{Index} is a term \term{hash}{Buckets, Speedup, Size, IsList}. Here
4250\arg{Buckets} is the number of buckets in the hash and \arg{Speedup} is
4251the expected speedup relative to trying all clauses linearly, \arg{Size}
4252is the size of the index in memory in bytes and finally, \arg{IsList}
4253indicates that a list is created for all clauses with the same key. This
4254is used to create \jargon{deep indexes} for the arguments of compound
4255terms.
4256
4257\textbf{Note:} This predicate property should be used for analysis and
4258statistics only. The exact representation of \arg{Indexes} may change
4259between versions. The utilities jiti_list/0 jiti_list/1 list the
4260\jargon{jit} indexes of matching predicates in a user friendly way.
4261
4262    \termitem{interpreted}{}
4263True if the predicate is defined in Prolog. We return true on this
4264because, although the code is actually compiled, it is completely
4265transparent, just like interpreted code.
4266
4267    \termitem{iso}{}
4268True if the predicate is covered by the ISO standard (ISO/IEC
426913211-1).
4270
4271    \termitem{line_count}{LineNumber}
4272Unify \arg{LineNumber} with the line number of the first clause of the
4273predicate.  Fails if the predicate is not associated with a file.  See
4274also source_file/2.  See also the \const{file} property above, notably
4275the reference to clause_property/2.
4276
4277    \termitem{multifile}{}
4278True if there may be multiple (or no) files providing clauses for the
4279predicate.  This property is set using multifile/1.
4280
4281    \termitem{meta_predicate}{Head}
4282If the predicate is declared as a meta-predicate using meta_predicate/1,
4283unify \arg{Head} with the head-pattern.  The head-pattern is a
4284compound term with the same name and arity as the predicate where each
4285argument of the term is a meta-predicate specifier.  See meta_predicate/1
4286for details.
4287
4288    \termitem{nodebug}{}
4289Details of the predicate are not shown by the debugger. This is the
4290default for built-in predicates.  User predicates can be compiled this
4291way using the Prolog flag \prologflag{generate_debug_info}.
4292
4293    \termitem{non_terminal}{}
4294True if the predicate implements a \jargon{grammar rule}.  See
4295non_terminal/1.
4296
4297    \termitem{notrace}{}
4298Do not show ports of this predicate in the debugger.
4299
4300    \termitem{number_of_clauses}{ClauseCount}
4301Unify \arg{ClauseCount} to the number of clauses associated with the
4302predicate.  Fails for foreign predicates.
4303
4304    \termitem{number_of_rules}{RuleCount}
4305Unify \arg{RuleCount} to the number of clauses associated with the
4306predicate. A \jargon{rule} is defined as a clauses that has a body that
4307is not just \const{true} (i.e., a \jargon{fact}). Fails for foreign
4308predicates. This property is used to avoid analysing predicates with
4309only facts in \pllib{prolog_codewalk}.
4310
4311    \termitem{last_modified_generation}{Generation}
4312Database generation at which the predicate was modified for the last
4313time.  Intended to quickly assesses the validity of caches.
4314
4315    \termitem{public}{}
4316Predicate is declared public using public/1.  Note that without further
4317definition, public predicates are considered undefined and this property
4318is \emph{not} reported.
4319
4320    \termitem{quasi_quotation_syntax}{}
4321The predicate (with arity~4) is declared to provide quasi quotation
4322syntax with quasi_quotation_syntax/1.
4323
4324    \termitem{size}{Bytes}
4325Memory used for this predicate. This includes the memory of the
4326predicate header, the combined memory of all clauses including erased
4327but not yet garbage collected clauses (see garbage_collect_clauses/0 and
4328clause_property/2) and the memory used by clause indexes (see the
4329\term{indexed}{Indexes} property. \emph{Excluded} are \jargon{lingering}
4330data structures. These are garbage data structures that have been
4331detached from the predicate but cannot yet be reclaimed because
4332they may be in use by some thread.
4333
4334    \termitem{static}{}
4335The definition can \emph{not} be modified using assertz/1 and friends.
4336This property is the opposite from \const{dynamic}, i.e., for each
4337defined predicate, either \const{static} or \const{dynamic} is true but
4338never both.
4339
4340    \termitem{tabled}{}
4341True of the predicate is \jargon{tabled}. The \term{tabled}{?Flag}
4342property can be used to obtain details about how the predicate is
4343tabled.
4344
4345    \termitem{tabled}{?Flag}
4346True of the predicate is \jargon{tabled} and \arg{Flag} applies.  Any
4347tabled predicate has one of the mutually exclusive flags \const{variant}
4348or \const{subsumptive}. In addition, tabled predicates may have one or
4349more of the following flags
4350
4351    \begin{description}
4352	\termitem{shared}{} The table is shared between threads.
4353	See \secref{tabling-shared}.
4354	\termitem{incremental}{} The table is subject to
4355	\jargon{incremental tabling}.  See \secref{tabling-incremental}
4356    \end{description}
4357
4358Use the \const{tabled} property to enumerate all tabled predicates. See
4359table/1 for details.
4360
4361    \termitem{thread_local}{}
4362If true (only possible on the multithreaded version) each thread has
4363its own clauses for the predicate. This property is set using
4364thread_local/1.
4365
4366    \termitem{transparent}{}
4367True if the predicate is declared transparent using the
4368module_transparent/1 or meta_predicate/1 declaration.  In the
4369latter case the property \term{meta_predicate}{Head} is also provided.
4370See \chapref{modules} for details.
4371
4372    \termitem{undefined}{}
4373True if a procedure definition block for the predicate exists, but there
4374are no clauses for it and it is not declared dynamic or multifile. This
4375is true if the predicate occurs in the body of a loaded predicate, an
4376attempt to call it has been made via one of the meta-call predicates,
4377the predicate has been declared as e.g., a meta-predicate or the
4378predicate had a definition in the past. Originally used to find missing
4379predicate definitions. The current implementation of list_undefined/0
4380used cross-referencing. Deprecated.
4381
4382    \termitem{visible}{}
4383True when predicate can be called without raising a predicate existence
4384error. This means that the predicate is (1) defined, (2) can be
4385inherited from one of the default modules (see default_module/2) or (3)
4386can be autoloaded. The behaviour is logically consistent iff the property
4387\const{visible} is provided explicitly. If the property is left unbound,
4388only defined predicates are enumerated.
4389
4390    \termitem{volatile}{}
4391If true, the clauses are not saved into a saved state
4392by qsave_program/[1,2].  This property is set using volatile/1.
4393\end{description}
4394
4395    \predicate{dwim_predicate}{2}{+Term, -Dwim}
4396`Do What I Mean' (`dwim') support predicate. \arg{Term} is a term, whose
4397name and arity are used as a predicate specification. \arg{Dwim} is
4398instantiated with the most general term built from \arg{Name} and the
4399arity of a defined predicate that matches the predicate specified by
4400\arg{Term} in the `Do What I Mean' sense. See dwim_match/2 for `Do What
4401I Mean' string matching. Internal system predicates are not generated,
4402unless the access level is \const{system} (see
4403\prologflag{access_level}). Backtracking provides all alternative
4404matches.
4405
4406    \predicate[ISO]{clause}{2}{:Head, ?Body}
4407True if \arg{Head} can be unified with a clause head and \arg{Body} with
4408the corresponding clause body. Gives alternative clauses on
4409backtracking. For facts, \arg{Body} is unified with the atom \arg{true}.
4410
4411    \predicate{clause}{3}{:Head, ?Body, ?Reference}
4412Equivalent to clause/2, but unifies \arg{Reference} with a unique
4413reference to the clause (see also assert/2, erase/1). If \arg{Reference}
4414is instantiated to a reference the clause's head and body will be
4415unified with \arg{Head} and \arg{Body}.
4416
4417    \predicate{nth_clause}{3}{?Pred, ?Index, ?Reference}
4418Provides access to the clauses of a predicate using their index number.
4419Counting starts at 1.  If \arg{Reference} is specified it unifies \arg{Pred}
4420with the most general term with the same name/arity as the predicate and
4421\arg{Index} with the index number of the clause.  Otherwise the name and
4422arity of \arg{Pred} are used to determine the predicate.  If \arg{Index}
4423is provided, \arg{Reference} will be unified with the clause reference.
4424If \arg{Index} is unbound, backtracking will yield both the indexes and
4425the references of all clauses of the predicate.  The following example
4426finds the 2nd clause of append/3:
4427
4428\begin{code}
4429?- use_module(library(lists)).
4430...
4431?- nth_clause(append(_,_,_), 2, Ref), clause(Head, Body, Ref).
4432Ref = <clause>(0x994290),
4433Head = lists:append([_G23|_G24], _G21, [_G23|_G27]),
4434Body = append(_G24, _G21, _G27).
4435\end{code}
4436
4437    \predicate{clause_property}{2}{+ClauseRef, -Property}
4438Queries properties of a clause. \arg{ClauseRef} is a reference to a
4439clause as produced by clause/3, nth_clause/3 or
4440prolog_frame_attribute/3. Unlike most other predicates that access
4441clause references, clause_property/2 may be used to get information
4442about erased clauses that have not yet been reclaimed. \arg{Property} is
4443one of the following:
4444
4445\begin{description}
4446    \termitem{file}{FileName}
4447Unify \arg{FileName} with the name of the file from which the clause
4448is loaded.  Fails if the clause was not created by loading a file
4449(e.g., clauses added using assertz/1).  See also \const{source}.
4450    \termitem{line_count}{LineNumber}
4451Unify \arg{LineNumber} with the line number of the clause.  Fails if
4452the clause is not associated to a file.
4453    \termitem{size}{SizeInBytes}
4454True when \arg{SizeInBytes} is the size that the clause uses in memory
4455in bytes.  The size required by a predicate also includes the predicate
4456data record, a linked list of clauses, clause selection instructions and
4457optionally one or more clause indexes.
4458    \termitem{source}{FileName}
4459Unify \arg{FileName} with the name of the source file that created
4460the clause.  This is the same as the \const{file} property, unless the
4461file is loaded from a file that is textually included into source using
4462include/1.  In this scenario, \const{file} is the included file, while
4463the \const{source} property refers to the \jargon{main} file.
4464    \termitem{fact}{}
4465True if the clause has no body.
4466    \termitem{erased}{}
4467True if the clause has been erased, but not yet reclaimed because
4468it is referenced.
4469    \termitem{predicate}{PredicateIndicator}
4470\arg{PredicateIndicator} denotes the predicate to which this clause
4471belongs. This is needed to obtain information on erased clauses because
4472the usual way to obtain this information using clause/3 fails for erased
4473clauses.
4474    \termitem{module}{Module}
4475\arg{Module} is the context module used to execute the body of the
4476clause.  For normal clauses, this is the same as the module in which
4477the predicate is defined.  However, if a clause is compiled with a
4478module qualified \jargon{head}, the clause belongs to the predicate
4479with the qualified head, while the body is executed in the context
4480of the module in which the clause was defined.
4481\end{description}
4482\end{description}
4483
4484\section{Input and output}		\label{sec:IO}
4485
4486SWI-Prolog provides two different packages for input and output.  The
4487native I/O system is based on the ISO standard predicates open/3,
4488close/1 and friends.%
4489	\footnote{Actually based on Quintus Prolog, providing this interface
4490		  before the ISO standard existed.}
4491Being more widely portable and equipped with a clearer and more robust
4492specification, new code is encouraged to use these predicates for
4493manipulation of I/O streams.
4494
4495\Secref{edinburghIO} describes tell/1, see/1 and friends, providing I/O
4496in the spirit of the traditional Edinburgh standard. These predicates
4497are layered on top of the ISO predicates. Both packages are fully
4498integrated; the user may switch freely between them.
4499
4500\subsection{Predefined stream aliases}			\label{sec:streamalias}
4501
4502Each thread has five stream aliases: \const{user_input},
4503\const{user_output}, \const{user_error}, \const{current_input}, and
4504\const{current_output}. Newly created threads inherit these stream
4505aliases from their parent. The \const{user_input}, \const{user_output}
4506and \const{user_error} aliases of the \const{main} thread are initially
4507bound to the standard operating system I/O streams (\jargon{stdin},
4508\jargon{stdout} and \jargon{stderr}, normally bound to the POSIX file
4509handles 0,~1 and~2). These aliases may be re-bound, for example if
4510standard I/O refers to a window such as in the \program{swipl-win.exe}
4511GUI executable for Windows. They can be re-bound by the user using
4512set_prolog_IO/3 and set_stream/2 by setting the alias of a stream (e.g,
4513\exam{set_stream(S, alias(user_output))}). An example of rebinding can
4514be found in library \pllib{prolog_server}, providing a \program{telnet}
4515service. The aliases \const{current_input} and \const{current_output}
4516define the source and destination for predicates that do not take a
4517stream argument (e.g., read/1, write/1, get_code/1, \ldots). Initially,
4518these are bound to the same stream as \const{user_input} and
4519\const{user_error}. They are re-bound by see/1, tell/1, set_input/1 and
4520set_output/1. The \const{current_output} stream is also temporary
4521re-bound by with_output_to/2 or format/3 using e.g.,
4522\exam{format(atom(A), ...}. Note that code which explicitly writes to
4523the streams \const{user_output} and \const{user_error} will not be
4524redirected by with_output_to/2.
4525
4526\paragraph{Compatibility}
4527
4528Note that the ISO standard only defines the \const{user_*} streams. The
4529`current' streams can be accessed using current_input/1 and
4530current_output/1.  For example, an ISO compatible implementation of
4531write/1 is
4532
4533\begin{code}
4534write(Term) :- current_output(Out), write_term(Out, Term).
4535\end{code}
4536
4537while SWI-Prolog additionally allows for
4538
4539\begin{code}
4540write(Term) :- write(current_output, Term).
4541\end{code}
4542
4543
4544\subsection{ISO Input and Output Streams}		\label{sec:isoIO}
4545
4546The predicates described in this section provide ISO compliant I/O,
4547where streams are explicitly created using the predicate open/3. The
4548resulting stream identifier is then passed as a parameter to the reading
4549and writing predicates to specify the source or destination of the data.
4550
4551This schema is not vulnerable to filename and stream ambiguities as
4552well as changes to the working directory.  On the other hand, using
4553the notion of current-I/O simplifies reusability of code without the
4554need to pass arguments around.  E.g., see with_output_to/2.
4555
4556SWI-Prolog streams are, compatible with the ISO standard, either input
4557or output streams.  To accommodate portability to other systems, a
4558pair of streams can be packed into a \jargon{stream-pair}.  See
4559stream_pair/3 for details.
4560
4561SWI-Prolog stream handles are unique symbols that have no syntactical
4562representation. They are written as \verb$<stream>(hex-number)$, which
4563is not valid input for read/1.  They are realised using a \jargon{blob}
4564of type \const{stream} (see blob/2 and \secref{blob}).
4565
4566
4567\begin{description}
4568    \predicate[ISO]{open}{4}{+SrcDest, +Mode, --Stream, +Options}
4569True when \arg{SrcDest} can be opened in \arg{Mode} and \arg{Stream} is
4570an I/O stream to/from the object. \arg{SrcDest} is normally the name of
4571a file, represented as an atom or string. \arg{Mode} is one of
4572\const{read}, \const{write}, \const{append} or \const{update}. Mode
4573\const{append} opens the file for writing, positioning the file pointer
4574at the end. Mode \const{update} opens the file for writing, positioning
4575the file pointer at the beginning of the file without truncating the
4576file. \arg{Stream} is either a variable, in which case it is bound to an
4577integer identifying the stream, or an atom, in which case this atom will
4578be the stream identifier.%
4579    \footnote{New code should use the \term{alias}{Alias}
4580	      option for compatibility with the ISO standard.}
4581
4582SWI-Prolog also allows \arg{SrcDest} to be a term \term{pipe}{Command}.
4583In this form, \arg{Command} is started as a child process and if
4584\arg{Mode} is \const{write}, output written to \arg{Stream} is sent to
4585the standard input of \arg{Command}. Vice versa, if \arg{Mode} is
4586\const{read}, data written by \arg{Command} to the standard output may
4587be read from \arg{Stream}. On Unix systems, \arg{Command} is handed to
4588popen() which hands it to the Unix shell. On Windows, \arg{Command} is
4589executed directly. See also process_create/3 from \pllib{process}.
4590
4591If \arg{SrcDest} is an \jargon{IRI}, i.e., starts with
4592<scheme>\verb$://$, where <scheme> is a non-empty sequence of lowercase
4593ASCII letters open/3,4 calls hooks registered by register_iri_scheme/3.
4594Currently the only predefined IRI scheme is \const{res}, providing
4595access to the \jargon{resource database}. See
4596\secref{program-resources}.
4597
4598The following \arg{Options} are recognised by open/4:
4599
4600\begin{description}
4601    \termitem{alias}{Atom}
4602Gives the stream a name.   Below is an example.   Be careful with this
4603option as stream names are global.  See also set_stream/2.
4604
4605\begin{code}
4606?- open(data, read, Fd, [alias(input)]).
4607
4608	...,
4609	read(input, Term),
4610	...
4611\end{code}
4612
4613    \termitem{bom}{Bool}
4614Check for a BOM (\jargon{Byte Order Marker}) or write
4615one.  If omitted, the default is \const{true} for mode \const{read} and
4616\const{false} for mode \const{write}.  See also stream_property/2 and
4617especially \secref{bom} for a discussion of this feature.
4618
4619    \termitem{buffer}{Buffering}
4620Defines output buffering. The atom \const{full} (default) defines full
4621buffering, \const{line} buffering by line, and \const{false} implies the
4622stream is fully unbuffered.  Smaller buffering is useful if another
4623process or the user is waiting for the output as it is being produced.
4624See also flush_output/[0,1]. This option is not an ISO option.
4625
4626    \termitem{close_on_abort}{Bool}
4627If \const{true} (default), the stream is closed on an abort (see
4628abort/0). If \const{false}, the stream is not closed. If it is an output
4629stream, however, it will be flushed.  Useful for logfiles and if the
4630stream is associated to a process (using the \functor{pipe}{1}
4631construct).
4632
4633    \termitem{create}{+List}
4634Specifies how a new file is created when opening in \const{write},
4635\const{append} or \const{update} mode. Currently, \arg{List} is a list
4636of atoms that describe the permissions of the created
4637file.\footnote{Added after feedback from Joachim Shimpf and Per
4638Mildner.} Defined values are below. Not recognised values are silently
4639ignored, allowing for adding platform specific extensions to this set.
4640
4641    \begin{description}
4642	\termitem{read}{}
4643    Allow read access to the file.
4644	\termitem{write}{}
4645    Allow write access to the file.
4646	\termitem{execute}{}
4647    Allow execution access to the file.
4648	\termitem{default}{}
4649    Allow read and write access to the file.
4650	\termitem{all}{}
4651    Allow any access provided by the OS.
4652    \end{description}
4653
4654Note that if \arg{List} is empty, the created file has no associated
4655access permissions. The create options map to the POSIX \arg{mode}
4656option of open(), where \const{read} map to 0444, \const{write} to 0222
4657and \const{execute} to 0111. On POSIX systems, the final permission is
4658defined as (mode \& \chr{~}umask).
4659
4660    \termitem{encoding}{Encoding}
4661Define the encoding used for reading and writing text to this stream.
4662The default encoding for type \const{text} is derived from the Prolog
4663flag \prologflag{encoding}. For \const{binary} streams the default encoding
4664is \const{octet}. For details on encoding issues, see \secref{encoding}.
4665
4666    \termitem{eof_action}{Action}
4667Defines what happens if the end of the input stream is reached. The
4668default value for Action is \const{eof_code}, which makes get0/1 and
4669friends return -1, and read/1 and friends return the atom
4670\const{end_of_file}.  Repetitive reading keeps yielding the same
4671result.  Action \const{error} is like \const{eof_code}, but repetitive
4672reading will raise an error.  With action \const{reset}, Prolog will
4673examine the file again and return more data if the file has grown.
4674
4675    \termitem{locale}{+Locale}
4676Set the locale that is used by notably format/2 for output on this
4677stream.  See \secref{locale}.
4678
4679    \termitem{lock}{LockingMode}
4680Try to obtain a lock on the open file.  Default is \const{none}, which
4681does not lock the file.  The value \const{read} or \const{shared} means
4682other processes may read the file, but not write it.  The value
4683\const{write} or \const{exclusive} means no other process may read
4684or write the file.
4685
4686Locks are acquired through the POSIX function fcntl() using the command
4687\const{F_SETLKW}, which makes a blocked call wait for the lock to be
4688released. Please note that fcntl() locks are {\em advisory} and
4689therefore only other applications using the same advisory locks
4690honour your lock. As there are many issues around locking in Unix,
4691especially related to NFS (network file system), please study the
4692fcntl() manual page before trusting your locks!
4693
4694The \const{lock} option is a SWI-Prolog extension.
4695
4696    \termitem{type}{Type}
4697Using type \const{text} (default), Prolog will write a text file in
4698an operating system compatible way. Using type \const{binary} the
4699bytes will be read or written without any translation.  See also
4700the option \const{encoding}.
4701
4702    \termitem{wait}{Bool}
4703This option can be combined with the \const{lock} option. If
4704\const{false} (default \const{true}), the open call returns immediately
4705with an exception if the file is locked.  The exception has the format
4706\term{permission_error}{lock, source_sink, SrcDest}.
4707\end{description}
4708
4709The option \const{reposition} is not supported in SWI-Prolog.  All streams
4710connected to a file may be repositioned.
4711
4712    \predicate[ISO]{open}{3}{+SrcDest, +Mode, --Stream}
4713Equivalent to open/4 with an empty option list.
4714
4715    \predicate{open_null_stream}{1}{--Stream}
4716Open an output stream that produces no output. All counting functions
4717are enabled on such a stream. It can be used to discard output (like
4718Unix \file{/dev/null}) or exploit the counting properties. The initial
4719encoding of \arg{Stream} is \const{utf8}, enabling arbitrary Unicode
4720output. The encoding can be changed to determine byte counts of the
4721output in a particular encoding or validate if output is possible in a
4722particular encoding. For example, the code below determines the number
4723of characters emitted when writing \arg{Term}.
4724
4725\begin{code}
4726write_length(Term, Len) :-
4727	open_null_stream(Out),
4728	write(Out, Term),
4729	character_count(Out, Len0),
4730	close(Out),
4731	Len = Len0.
4732\end{code}
4733
4734    \predicate[ISO]{close}{1}{+Stream}
4735Close the specified stream. If \arg{Stream} is not open, an existence
4736error is raised.  See stream_pair/3 for the implications of closing a
4737\jargon{stream pair}.
4738
4739If the closed stream is the current input, output or error stream, the
4740stream alias is bound to the initial standard I/O streams of the
4741process. Calling close/1 on the initial standard I/O streams of the
4742process is a no-op for an input stream and flushes an output stream
4743without closing it.\footnote{This behaviour was defined with purely
4744interactive usage of Prolog in mind. Applications should not count on
4745this behaviour. Future versions may allow for closing the initial
4746standard I/O streams.}
4747
4748    \predicate[ISO]{close}{2}{+Stream, +Options}
4749Provides \term{close}{Stream, [force(true)]} as the only option.  Called
4750this way, any resource errors (such as write errors while flushing the
4751output buffer) are ignored.
4752
4753    \predicate[ISO]{stream_property}{2}{?Stream, ?StreamProperty}
4754True when \arg{StreamProperty} is a property of \arg{Stream}. If
4755enumeration of streams or properties is demanded because either
4756\arg{Stream} or \arg{StreamProperty} are unbound, the implementation
4757enumerates all candidate streams and properties while locking the stream
4758database.  Properties are fetched without locking the stream and may
4759be outdated before this predicate returns due to asynchronous activity.
4760
4761\begin{description}
4762    \termitem{alias}{Atom}
4763If \arg{Atom} is bound, test if the stream has the specified alias.
4764Otherwise unify \arg{Atom} with the first alias of the stream.%
4765	\bug{Backtracking does not give other aliases.}
4766
4767    \termitem{buffer}{Buffering}
4768SWI-Prolog extension to query the buffering mode of this stream.
4769\arg{Buffering} is one of \const{full}, \const{line} or \const{false}.
4770See also open/4.
4771
4772    \termitem{buffer_size}{Integer}
4773SWI-Prolog extension to query the size of the I/O buffer associated
4774to a stream in bytes.  Fails if the stream is not buffered.
4775
4776    \termitem{bom}{Bool}
4777If present and \const{true}, a BOM (\jargon{Byte Order Mark}) was
4778detected while opening the file for reading, or a BOM was written while
4779opening the stream. See \secref{bom} for details.
4780
4781    \termitem{close_on_abort}{Bool}
4782Determine whether or not abort/0 closes the stream.  By default
4783streams are closed.
4784
4785    \termitem{close_on_exec}{Bool}
4786Determine whether or not the stream is closed when executing a new
4787process (exec() in Unix, CreateProcess() in Windows). Default is to
4788close streams. This maps to fcntl() \const{F_SETFD} using the flag
4789\const{FD_CLOEXEC} on Unix and (negated) \const{HANDLE_FLAG_INHERIT} on
4790Windows.
4791
4792    \termitem{encoding}{Encoding}
4793Query the encoding used for text.  See \secref{encoding} for an
4794overview of wide character and encoding issues in SWI-Prolog.
4795
4796    \termitem{end_of_stream}{E}
4797If \arg{Stream} is an input stream, unify \arg{E} with one of the
4798atoms \const{not}, \const{at} or \const{past}. See also
4799at_end_of_stream/[0,1].
4800
4801    \termitem{eof_action}{A}
4802Unify \arg{A} with one of \const{eof_code}, \const{reset} or
4803\const{error}.  See open/4 for details.
4804
4805    \termitem{file_name}{Atom}
4806If \arg{Stream} is associated to a file, unify \arg{Atom} to the
4807name of this file.
4808
4809    \termitem{file_no}{Integer}
4810If the stream is associated with a POSIX file descriptor, unify
4811\arg{Integer} with the descriptor number.  SWI-Prolog extension used
4812primarily for integration with foreign code.  See also Sfileno() from
4813\file{SWI-Stream.h}.
4814
4815    \termitem{input}{}
4816True if \arg{Stream} has mode \const{read}.
4817
4818    \termitem{locale}{Locale}
4819True when \arg{Locale} is the current locale associated with the
4820stream. See \secref{locale}.
4821
4822    \termitem{mode}{IOMode}
4823Unify \arg{IOMode} to the mode given to open/4 for opening the stream.
4824Values are: \const{read}, \const{write}, \const{append} and the
4825SWI-Prolog extension \const{update}.
4826
4827    \termitem{newline}{NewlineMode}
4828One of \const{posix} or \const{dos}.  If \const{dos}, text streams
4829will emit \verb$\r\n$ for \verb$\n$ and discard \verb$\r$ from input
4830streams.  Default depends on the operating system.
4831
4832    \termitem{nlink}{-Count}
4833Number of hard links to the file.  This expresses the number of `names'
4834the file has. Not supported on all operating systems and the value might
4835be bogus.  See the documentation of fstat() for your OS and the value
4836\texttt{st_nlink}.
4837
4838    \termitem{output}{}
4839True if \arg{Stream} has mode \const{write}, \const{append} or
4840\const{update}.
4841
4842    \termitem{position}{Pos}
4843Unify \arg{Pos} with the current stream position. A stream position is
4844an opaque term whose fields can be extracted using
4845stream_position_data/3. See also set_stream_position/2.
4846
4847    \termitem{reposition}{Bool}
4848Unify \arg{Bool} with \arg{true} if the position of the stream can
4849be set (see seek/4).  It is assumed the position can be set if the
4850stream has a \jargon{seek-function} and is not based on a POSIX
4851file descriptor that is not associated to a regular file.
4852
4853    \termitem{representation_errors}{Mode}
4854Determines behaviour of character output if the stream cannot represent
4855a character. For example, an ISO Latin-1 stream cannot represent
4856Cyrillic characters.  The behaviour is one of \const{error} (throw
4857an I/O error exception), \const{prolog} (write \verb$\...\$ escape
4858code) or \const{xml} (write \verb$&#...;$ XML character entity).
4859The initial mode is \const{prolog} for the user streams and
4860\const{error} for all other streams. See also \secref{encoding}
4861and set_stream/2.
4862
4863    \termitem{timeout}{-Time}
4864\arg{Time} is the timeout currently associated with the stream.  See
4865set_stream/2 with the same option. If no timeout is specified,
4866\arg{Time} is unified to the atom \const{infinite}.
4867
4868    \termitem{type}{Type}
4869Unify \arg{Type} with \const{text} or \const{binary}.
4870
4871    \termitem{tty}{Bool}
4872This property is reported with \arg{Bool} equal to \const{true} if
4873the stream is associated with a terminal.  See also set_stream/2.
4874
4875    \termitem{write_errors}{Atom}
4876\arg{Atom} is one of \const{error} (default) or \const{ignore}. The
4877latter is intended to deal with service processes for which the standard
4878output handles are not connected to valid streams. In these cases write
4879errors may be ignored on \const{user_error}.
4880\end{description}
4881
4882    \predicate{current_stream}{3}{?Object, ?Mode, ?Stream}
4883The predicate current_stream/3 is used to access the status of a
4884stream as well as to generate all open streams.  \arg{Object} is the
4885name of the file opened if the stream refers to an open file, an
4886integer file descriptor if the stream encapsulates an operating system
4887stream, or the atom \const{[]} if the stream refers to some other object.
4888\arg{Mode} is one of \const{read} or \const{write}.
4889
4890    \predicate{is_stream}{1}{+Term}
4891True if \arg{Term} is a stream name or valid stream handle.  This
4892predicate realises a safe test for the existence of a stream alias
4893or handle.
4894
4895    \predicate{stream_pair}{3}{?StreamPair, ?Read, ?Write}
4896This predicate can be used in mode (-,+,+) to create a
4897\jargon{stream-pair} from an input stream and an output stream. Mode
4898(+,-,-) can be used to get access to the underlying streams. If a stream
4899has already been closed, the corresponding argument is left unbound. If
4900mode (+,-,-) is used on a single stream, either \arg{Read} or
4901\arg{Write} is unified with the stream while the other argument is left
4902unbound. This behaviour simplifies writing code that must operate both
4903on streams and stream pairs.
4904
4905Stream-pairs can be used by all I/O operations on streams, where the
4906operation selects the appropriate member of the pair. The predicate
4907close/1 closes the still open streams of the pair.\footnote{As of
4908version 7.1.19, it is allowed to close one of the members of the
4909stream directly and close the pair later.} The output stream is
4910closed before the input stream. If closing the output stream results in
4911an error, the input stream is still closed. Success is only returned if
4912both streams were closed successfully.
4913
4914    \predicate[ISO]{set_stream_position}{2}{+Stream, +Pos}
4915Set the current position of \arg{Stream} to \arg{Pos}.  \arg{Pos} is
4916a term as returned by stream_property/2 using the \term{position}{Pos}
4917property.  See also seek/4.
4918
4919    \predicate{stream_position_data}{3}{?Field, +Pos, -Data}
4920Extracts information from the opaque stream position term as returned
4921by stream_property/2 requesting the \term{position}{Pos} property.
4922\arg{Field} is one of \const{line_count}, \const{line_position},
4923\const{char_count} or \const{byte_count}.  See also line_count/2,
4924line_position/2, character_count/2 and byte_count/2.%
4925	\footnote{Introduced in version 5.6.4 after extending the
4926		  position term with a byte count.  Compatible with
4927		  SICStus Prolog.}
4928
4929    \predicate{seek}{4}{+Stream, +Offset, +Method, -NewLocation}
4930Reposition the current point of the given \arg{Stream}.  \arg{Method}
4931is one of \const{bof}, \const{current} or \const{eof}, indicating
4932positioning relative to the start, current point or end of the
4933underlying object.  \arg{NewLocation} is unified with the new offset,
4934relative to the start of the stream.
4935
4936Positions are counted in `units'. A unit is 1 byte, except for
4937text files using 2-byte Unicode encoding (2 bytes) or \emph{wchar}
4938encoding (sizeof(wchar_t)). The latter guarantees comfortable
4939interaction with wide-character text objects. Otherwise, the use of
4940seek/4 on non-binary files (see open/4) is of limited use, especially
4941when using multi-byte text encodings (e.g.\ UTF-8) or multi-byte newline
4942files (e.g.\ DOS/Windows). On text files, SWI-Prolog offers reliable
4943backup to an old position using stream_property/2 and
4944set_stream_position/2. Skipping $N$ character codes is achieved calling
4945get_code/2 $N$ times or using copy_stream_data/3, directing the output
4946to a null stream (see open_null_stream/1). If the seek modifies the
4947current location, the line number and character position in the line are
4948set to 0.
4949
4950If the stream cannot be repositioned, a \const{permission_error} is
4951raised. If applying the offset would result in a file position less than
4952zero, a \const{domain_error} is raised. Behaviour when seeking to
4953positions beyond the size of the underlying object depend on the object
4954and possibly the operating system. The predicate seek/4 is compatible with
4955Quintus Prolog, though the error conditions and signalling is ISO
4956compliant. See also stream_property/2 and set_stream_position/2.
4957
4958    \predicate{set_stream}{2}{+Stream, +Attribute}
4959Modify an attribute of an existing stream. \arg{Attribute} specifies the
4960stream property to set. If stream is a \emph{pair} (see stream_pair/3)
4961both streams are modified, unless the property is only meaningful on
4962one of the streams or setting both is not meaningful.  In particular,
4963\const{eof_action} only applies to the \emph{read} stream,
4964\const{representation_errors} only applies to the \emph{write} stream
4965and trying to set \const{alias} or \const{line_position} on a pair
4966results in a \const{permission_error} exception. See also
4967stream_property/2 and open/4.
4968
4969\begin{description}
4970    \termitem{alias}{AliasName}
4971Set the alias of an already created stream. If \arg{AliasName} is the
4972name of one of the standard streams, this stream is rebound.
4973Thus, \exam{set_stream(S, current_input)} is the same as set_input/1, and
4974by setting the alias of a stream to \const{user_input}, etc., all user
4975terminal input is read from this stream. See also interactor/0.
4976
4977    \termitem{buffer}{Buffering}
4978Set the buffering mode of an already created stream.  Buffering is one
4979of \const{full}, \const{line} or \const{false}.
4980
4981    \termitem{buffer_size}{+Size}
4982Set the size of the I/O buffer of the underlying stream to \arg{Size}
4983bytes.
4984
4985    \termitem{close_on_abort}{Bool}
4986Determine whether or not the stream is closed by abort/0.  By default,
4987streams are closed.
4988
4989    \termitem{close_on_exec}{Bool}
4990Set the \const{close_on_exec} property.  See stream_property/2.
4991
4992    \termitem{encoding}{Atom}
4993Defines the mapping between bytes and character codes used for the
4994stream.  See \secref{encoding} for supported encodings.  The value
4995\const{bom} causes the stream to check whether the current character
4996is a Unicode BOM marker.  If a BOM marker is found, the encoding is
4997set accordingly and the call succeeds.  Otherwise the call fails.
4998
4999    \termitem{eof_action}{Action}
5000Set end-of-file handling to one of \const{eof_code}, \const{reset} or
5001\const{error}.
5002
5003    \termitem{file_name}{FileName}
5004Set the filename associated to this stream.  This call can be used
5005to set the file for error locations if \arg{Stream} corresponds to
5006\arg{FileName} and is not obtained by opening the file directly but,
5007for example, through a network service.
5008
5009    \termitem{line_position}{LinePos}
5010Set the line position attribute of the stream.  This feature is
5011intended to correct position management of the stream after sending
5012a terminal escape sequence (e.g., setting ANSI character attributes).
5013Setting this attribute raises a permission error if the stream does
5014not record positions. See line_position/2 and stream_property/2
5015(property \const{position}).
5016
5017    \termitem{locale}{+Locale}
5018Change the locale of the stream.  See \secref{locale}.
5019
5020    \termitem{newline}{NewlineMode}
5021Set input or output translation for newlines. See corresponding
5022stream_property/2 for details.  In addition to the detected modes,
5023an input stream can be set in mode \const{detect}.  It will be set
5024to \const{dos} if a \verb$\r$ character was removed.
5025
5026    \termitem{timeout}{Seconds}
5027This option can be used to make streams generate an exception if it
5028takes longer than \arg{Seconds} before any new data arrives at the
5029stream.  The value \arg{infinite} (default) makes the stream block
5030indefinitely.  Like wait_for_input/3, this call only applies to
5031streams that support the select() system call. For further information
5032about timeout handling, see wait_for_input/3. The exception is of the
5033form
5034
5035\begin{quote}
5036    \term{error}{\term{timeout_error}{read, Stream}, _}
5037\end{quote}
5038
5039    \termitem{type}{Type}
5040Set the type of the stream to one of \const{text} or \const{binary}.
5041See also open/4 and the \const{encoding} property of streams. Switching
5042to \const{binary} sets the encoding to \const{octet}.  Switching to
5043\const{text} sets the encoding to the default text encoding.
5044
5045    \termitem{record_position}{Bool}
5046Do/do not record the line count and line position (see line_count/2
5047and line_position/2). Calling \exam{set_stream(S,
5048record_position(true))} resets the position the start of line~1.
5049
5050    \termitem{representation_errors}{Mode}
5051Change the behaviour when writing characters to the stream that cannot
5052be represented by the encoding.  See also stream_property/2 and
5053\secref{encoding}.
5054
5055    \termitem{tty}{Bool}
5056Modify whether Prolog thinks there is a terminal (i.e.\ human
5057interaction) connected to this stream.  On Unix systems the initial
5058value comes from isatty().  On Windows, the initial user streams are
5059supposed to be associated to a terminal.  See also stream_property/2.
5060\end{description}
5061
5062    \predicate{set_prolog_IO}{3}{+In, +Out, +Error}
5063Prepare the given streams for interactive behaviour normally associated
5064to the terminal. \arg{In} becomes the \const{user_input} and
5065\const{current_input} of the calling thread. \arg{Out} becomes
5066\const{user_output} and \const{current_output}. If \arg{Error} equals
5067\arg{Out} an unbuffered stream is associated to the same destination and
5068linked to \const{user_error}. Otherwise \arg{Error} is used for
5069\const{user_error}. Output buffering for \arg{Out} is set to
5070\const{line} and buffering on \arg{Error} is disabled.
5071See also prolog/0 and set_stream/2.  The \emph{clib} package
5072provides the library \pllib{prolog_server}, creating a TCP/IP
5073server for creating an interactive session to Prolog.
5074
5075    \predicate{set_system_IO}{3}{+In, +Out, +Error}
5076Bind the given streams to the operating system I/O streams 0-2 using
5077POSIX dup2() API. \arg{In} becomes \const{stdin}. \arg{Out} becomes
5078\const{stdout}. If \arg{Error} equals \arg{Out} an unbuffered stream is
5079associated to the same destination and linked to \const{stderr}.
5080Otherwise \arg{Error} is used for \const{stderr}. Output buffering for
5081\arg{Out} is set to line and buffering on \arg{Error} is disabled. The
5082operating system I/O streams are shared across all threads. The three
5083streams must be related to a \jargon{file descriptor} or a
5084\const{domain_error} \const{file_stream} is raised.  See also
5085stream_property/2, property \term{file_no}{Fd}.
5086
5087Where set_prolog_IO/3 rebinds the Prolog streams \const{user_input},
5088\const{user_output} and \const{user_error} for a specific thread
5089providing a private interactive session, set_system_IO/3 rebinds the
5090shared console I/O and also captures Prolog kernel events (e.g.,
5091low-level debug messages, unexpected events) as well as messages from
5092foreign libraries that are directly written to \const{stdout} or
5093\const{stderr}.
5094
5095This predicate is intended to capture all output in situations where
5096standard I/O is normally lost, such as when Prolog is running as a
5097service on Windows.
5098\end{description}
5099
5100\subsection{Edinburgh-style I/O}	\label{sec:edinburghIO}
5101
5102The package for implicit input and output destinations is (almost)
5103compatible with Edinburgh DEC-10 and C-Prolog. The reading and writing
5104predicates refer to, resp., the \emph{current} input and output streams.
5105Initially these streams are connected to the terminal. The current
5106output stream is changed using tell/1 or append/1. The current input
5107stream is changed using see/1. The stream's current value can be obtained
5108using telling/1 for output and seeing/1 for input.
5109
5110Source and destination are either a file, \const{user}, or a term
5111`pipe(\arg{Command})'. The reserved stream name \const{user} refers
5112to the terminal.%
5113	\footnote{The ISO I/O layer uses \const{user_input},
5114		  \const{user_output} and \const{user_error}.}
5115In the predicate descriptions below we will call the source/destination
5116argument `\arg{SrcDest}'. Below are some examples of source/destination
5117specifications.
5118
5119\begin{center}\begin{tabular}{ll}
5120\exam{?- see(data).}        & \% Start reading from file `data'. \\
5121\exam{?- tell(user).}       & \% Start writing to the terminal. \\
5122\exam{?- tell(pipe(lpr)).}  & \% Start writing to the printer.
5123\end{tabular}\end{center}
5124
5125Another example of using the \functor{pipe}{1} construct is shown
5126below.%
5127	\footnote{As of version 5.3.15, the pipe construct is supported
5128		  in the MS-Windows version, both for
5129		  \program{swipl.exe} and \program{swipl-win.exe}. The
5130		  implementation uses code from the LUA programming
5131		  language (\url{http://www.lua.org}).}
5132Note that the \functor{pipe}{1} construct is not part of
5133Prolog's standard I/O repertoire.
5134
5135\begin{code}
5136getwd(Wd) :-
5137        seeing(Old), see(pipe(pwd)),
5138        collect_wd(String),
5139        seen, see(Old),
5140        atom_codes(Wd, String).
5141
5142collect_wd([C|R]) :-
5143        get0(C), C \== -1, !,
5144        collect_wd(R).
5145collect_wd([]).
5146\end{code}
5147
5148The effect of tell/1 is not undone on backtracking, and since the
5149stream handle is not specified explicitly in further I/O operations
5150when using Edinburgh-style I/O, you may write to unintended streams
5151more easily than when using ISO compliant I/O. For example, the
5152following query writes both "a" and "b" into the file `out' :
5153
5154\begin{code}
5155?- (tell(out), write(a), false ; write(b)), told.
5156\end{code}
5157
5158
5159\subsubsection*{Compatibility notes}
5160
5161Unlike Edinburgh Prolog systems, telling/1 and seeing/1 do not return
5162the filename of the current input/output but rather the stream identifier, to
5163ensure the design pattern below	works under all circumstances:%
5164	\footnote{Filenames can be ambiguous and SWI-Prolog streams can
5165		  refer to much more than just files.}
5166
5167\begin{code}
5168	...,
5169	telling(Old), tell(x),
5170	...,
5171	told, tell(Old),
5172	...,
5173\end{code}
5174
5175The predicates tell/1 and see/1 first check for \const{user}, the
5176\term{pipe}{command} and a stream handle.  Otherwise, if the argument
5177is an atom it is first compared to open streams associated to a file
5178with \emph{exactly} the same name.  If such a stream exists, created using
5179tell/1 or see/1, output (input) is switched to the open stream.
5180Otherwise a file with the specified name is opened.
5181
5182The behaviour is compatible with Edinburgh Prolog.  This is not without
5183problems. Changing directory, non-file streams, and multiple names referring
5184to the same file easily lead to unexpected behaviour. New code,
5185especially when managing multiple I/O channels, should consider using
5186the ISO I/O predicates defined in \secref{isoIO}.
5187
5188\begin{description}
5189    \predicate{see}{1}{+SrcDest}
5190Open \arg{SrcDest} for reading and make it the current input (see
5191set_input/1). If \arg{SrcDest} is a stream handle, just make this
5192stream the current input. See the introduction of \secref{edinburghIO}
5193for details.
5194
5195    \predicate{tell}{1}{+SrcDest}
5196Open \arg{SrcDest} for writing and make it the current output (see
5197set_output/1).  If \arg{SrcDest} is a stream handle, just make this
5198stream the current output. See the introduction of \secref{edinburghIO}
5199for details.
5200
5201    \predicate{append}{1}{+File}
5202Similar to tell/1, but positions the file pointer at the end of \arg{File}
5203rather than truncating an existing file. The pipe construct is not
5204accepted by this predicate.
5205
5206    \predicate{seeing}{1}{?SrcDest}
5207Same as current_input/1, except that \const{user} is returned if the
5208current input is the stream \const{user_input} to improve compatibility
5209with traditional Edinburgh I/O. See the introduction of
5210\secref{edinburghIO} for details.
5211
5212    \predicate{telling}{1}{?SrcDest}
5213Same as current_output/1, except that \const{user} is returned if the
5214current output is the stream \const{user_output} to improve compatibility
5215with traditional Edinburgh I/O. See the introduction of
5216\secref{edinburghIO} for details.
5217
5218    \predicate{seen}{0}{}
5219Close the current input stream. The new input stream becomes
5220\const{user_input}.
5221
5222    \predicate{told}{0}{}
5223Close the current output stream. The new output stream becomes
5224\const{user_output}.
5225\end{description}
5226
5227
5228\subsection{Switching between Edinburgh and ISO I/O}
5229\label{sec:edinburgh-iso-io}
5230
5231The predicates below can be used for switching between the implicit
5232and the explicit stream-based I/O predicates.
5233
5234\begin{description}
5235    \predicate[ISO]{set_input}{1}{+Stream}
5236Set the current input stream to become \arg{Stream}.  Thus, \exam{open(file,
5237read, Stream), set_input(Stream)} is equivalent to \exam{see(file)}.
5238    \predicate[ISO]{set_output}{1}{+Stream}
5239Set the current output stream to become \arg{Stream}.  See also
5240with_output_to/2.
5241    \predicate[ISO]{current_input}{1}{-Stream}
5242Get the current input stream.  Useful for getting access to the status
5243predicates associated with streams.
5244    \predicate[ISO]{current_output}{1}{-Stream}
5245Get the current output stream.
5246\end{description}
5247
5248\subsection{Adding IRI schemas}
5249\label{sec:iri-schema}
5250
5251The file handling predicates may be \jargon{hooked} to deal with
5252\jargon{IRIs}. An IRI starts with <scheme>\verb$://$, where <scheme> is
5253a non-empty sequence of lowercase ASCII letters. After detecting the
5254scheme the file manipulation predicates call a hook that is registered
5255using register_iri_scheme/3.
5256
5257Hooking the file operations using extensible IRI schemas allows us to
5258place any resource that is accessed through Prolog I/O predicates on
5259arbitrary devices such as web servers or the ZIP archive used to store
5260program resources (see \secref{saved-states}). This is typically
5261combined with file_search_path/2 declarations to switch between
5262accessing a set of resources from local files, from the program
5263resource database, from a web-server, etc.
5264
5265
5266\begin{description}
5267    \predicate{register_iri_scheme}{3}{+Scheme, :Hook, +Options}
5268Register \arg{Hook} to be called by all file handling predicates
5269if a name that starts with \arg{Scheme}:// is encountered.  The
5270\arg{Hook} is called by call/4 using the \jargon{operation}, the
5271\arg{IRI} and a term that receives the \textit{result} of the
5272operation.  The following operations are defined:
5273
5274\begin{description}
5275    \termitem{open}{Mode,Options}
5276Called by open/3,4.  The result argument must be unified with
5277a stream.
5278
5279    \termitem{access}{Mode}
5280Called by access_file/2, exists_file/1 (\arg{Mode} is \const{file}) and
5281exists_directory/1 (\arg{Mode} is \const{directory}). The result
5282argument must be unified with a boolean.
5283
5284    \termitem{time}{}
5285Called by time_file/2.  The result must be unified with a time stamp.
5286
5287    \termitem{size}{}
5288Called by size_file/2.  The result must be unified with an integer
5289representing the size in bytes.
5290\end{description}
5291\end{description}
5292
5293
5294\subsection{Write onto atoms, code-lists, etc.}
5295\label{sec:write-on-atom}
5296
5297\begin{description}
5298    \predicate{with_output_to}{2}{+Output, :Goal}
5299Run \arg{Goal} as once/1, while characters written to the current output
5300are sent to \arg{Output}. The predicate is SWI-Prolog-specific, inspired
5301by various posts to the mailinglist. It provides a flexible replacement
5302for predicates such as \nopredref{sformat}{3}, swritef/3,
5303term_to_atom/2, atom_number/2 converting numbers to atoms, etc. The
5304predicate format/3 accepts the same terms as output argument.
5305
5306Applications should generally avoid creating atoms by breaking and
5307concatenating other atoms, as the creation of large numbers of
5308intermediate atoms generally leads to poor performance, even more so in
5309multithreaded applications.  This predicate supports creating
5310difference lists from character data efficiently.  The example below
5311defines the DCG rule term//1 to insert a term in the output:
5312
5313\begin{code}
5314term(Term, In, Tail) :-
5315	with_output_to(codes(In, Tail), write(Term)).
5316
5317?- phrase(term(hello), X).
5318
5319X = [104, 101, 108, 108, 111]
5320\end{code}
5321
5322\arg{Output} takes one of the shapes below. Except for the first, the
5323system creates a temporary stream using the \const{wchar_t} internal
5324encoding that points at a memory buffer. The encoding cannot be changed
5325and an attempt to call set_stream/2 using \term{encoding}{Encoding}
5326results in a \const{permission_error} exception.
5327
5328\begin{description}
5329    \definition{A Stream handle or alias}
5330Temporarily switch current output to the given stream.  Redirection using
5331with_output_to/2 guarantees the original output is restored, also if
5332\arg{Goal} fails or raises an exception.  See also call_cleanup/2.
5333
5334    \termitem{atom}{-Atom}
5335Create an atom from the emitted characters. Please note the remark
5336above.
5337
5338    \termitem{string}{-String}
5339Create a string object as defined in \secref{strings}.
5340
5341    \termitem{codes}{-Codes}
5342Create a list of character codes from the emitted characters, similar to
5343atom_codes/2.
5344
5345    \termitem{codes}{-Codes, -Tail}
5346Create a list of character codes as a difference list.
5347
5348    \termitem{chars}{-Chars}
5349Create a list of one-character atoms from the emitted characters,
5350similar to atom_chars/2.
5351
5352    \termitem{chars}{-Chars, -Tail}
5353Create a list of one-character atoms as a difference list.
5354\end{description}
5355\end{description}
5356
5357
5358\subsection{Fast binary term I/O}
5359\label{sec:fast-term-io}
5360
5361The predicates in this section provide fast binary I/O of arbitrary
5362Prolog terms, including cyclic terms and terms holding attributed
5363variables. Library \pllib{fastrw} is a SICSTus/Ciao compatible library
5364that extends the core primitives described below.
5365
5366The binary representation the same as used by PL_record_external(). The
5367use of these primitives instead of using write_canonical/2 has
5368advantages and disadvantages. Below are the main considerations:
5369
5370\begin{itemize}
5371    \item Using write_canonical/2 allows or exchange of terms with
5372    other Prolog systems.  The format is stable and, as it is text
5373    based, it can be inspected and corrected.
5374    \item Using the binary format improves the performance roughly
5375    3 times.
5376    \item The size of both representations is comparable.
5377    \item The binary format can deal with cycles, sharing and
5378    attributes.  Special precautions are needed to transfer
5379    such terms using write_canonical/2.  See term_factorized/3
5380    and copy_term/3.
5381    \item In the current version, reading the binary format has
5382    only incomplete consistency checks.  This implies a user must
5383    be able to \textbf{trust the source} as crafted messages may
5384    compromise the reading Prolog system.
5385\end{itemize}
5386
5387\begin{description}
5388    \predicate{fast_term_serialized}{2}{?Term, ?String}
5389(De-)serialize \arg{Term} to/from \arg{String}.
5390
5391    \predicate{fast_write}{2}{+Output, +Term}
5392Write \arg{Term} using the fast serialization format to the
5393\arg{Output} stream.  \arg{Output} \emph{must} be a binary
5394stream.
5395
5396    \predicate{fast_read}{2}{+Input, -Term}
5397Read \arg{Term} using the fast serialization format from the
5398\arg{Input} stream.  \arg{Input} \emph{must} be a binary
5399stream.\bug{The predicate fast_read/2 may crash on arbitrary
5400input.}
5401\end{description}
5402
5403
5404\section{Status of streams}		\label{sec:streamstat}
5405
5406\begin{description}
5407    \predicate[det]{wait_for_input}{3}{+ListOfStreams, -ReadyList, +TimeOut}
5408Wait for input on one of the streams in \arg{ListOfStreams} and return a
5409list of streams on which input is available in \arg{ReadyList}. Each
5410element of \arg{ListOfStreams} is either a stream or an integer.
5411Integers are consider waitable OS handles. This can be used to
5412(also) wait for handles that are not associated with Prolog streams such
5413as UDP sockets. See tcp_setopt/2.
5414
5415This predicate waits for at most \arg{TimeOut} seconds. \arg{TimeOut}
5416may be specified as a floating point number to specify fractions of a
5417second. If \arg{TimeOut} equals \const{infinite}, wait_for_input/3 waits
5418indefinitely. If \arg{Timeout} is 0 or 0.0 this predicate returns
5419without waiting.\footnote{Prior to 7.3.23, the integer value `0' was the
5420same as \const{infinite}.}
5421
5422This predicate can be used to implement timeout while reading and to
5423handle input from multiple sources and is typically used to wait for
5424multiple (network) sockets. On Unix systems it may be used on any stream
5425that is associated with a system file descriptor. On Windows it can only
5426be used on sockets. If \arg{ListOfStreams} contains a stream that is not
5427associated with a supported device, a \term{domain_error}{waitable_stream,
5428Stream} is raised.
5429
5430The example below waits for input from the user and an explicitly opened
5431secondary terminal stream. On return, \arg{Inputs} may hold
5432\const{user_input} or \arg{P4} or both.
5433
5434\begin{code}
5435?- open('/dev/ttyp4', read, P4),
5436   wait_for_input([user_input, P4], Inputs, 0).
5437\end{code}
5438
5439\index{select()}\index{poll()}%
5440When available, the implementation is based on the poll() system call.
5441The poll() puts no additional restriction on the number of open files
5442the process may have. It does limit the time to $2^{31}-1$ milliseconds
5443(a bit less than 25 days). Specifying a too large timeout raises a
5444\term{representation_error}{timeout} exception. If poll() is not
5445supported by the OS, select() is used. The select() call can only handle
5446file descriptors up to \const{FD_SETSIZE}. If the set contains a
5447descriptor that exceeds this limit a
5448\term{representation_error}{'FD_SETSIZE'} is raised.
5449
5450Note that wait_for_input/3 returns streams that have data waiting. This
5451does not mean you can, for example, call read/2 on the stream without
5452blocking as the stream might hold an incomplete term. The predicate
5453set_stream/2 using the option \term{timeout}{Seconds} can be used to
5454make the stream generate an exception if no new data arrives within
5455the timeout period.  Suppose two processes communicate by exchanging Prolog
5456terms.  The following code makes the server immune for clients that
5457write an incomplete term:
5458
5459\begin{code}
5460    ...,
5461    tcp_accept(Server, Socket, _Peer),
5462    tcp_open(Socket, In, Out),
5463    set_stream(In, timeout(10)),
5464    catch(read(In, Term), _, (close(Out), close(In), fail)),
5465    ...,
5466\end{code}
5467
5468    \predicate{byte_count}{2}{+Stream, -Count}
5469Byte position in \arg{Stream}.  For binary streams this is the same
5470as character_count/2.  For text files the number may be different due
5471to multi-byte encodings or additional record separators (such as
5472Control-M in Windows).
5473
5474    \predicate{character_count}{2}{+Stream, -Count}
5475Unify \arg{Count} with the current character index.  For input streams
5476this is the number of characters read since the open; for output
5477streams this is the number of characters written. Counting starts at 0.
5478
5479    \predicate{line_count}{2}{+Stream, -Count}
5480Unify \arg{Count} with the number of lines read or written.  Counting
5481starts at 1.
5482
5483    \predicate{line_position}{2}{+Stream, -Count}
5484Unify \arg{Count} with the position on the current line. Note that this
5485assumes the position is 0 after the open.  Tabs are assumed to be
5486defined on each 8-th character, and backspaces are assumed to reduce the
5487count by one, provided it is positive.
5488\end{description}
5489
5490
5491\section{Primitive character I/O}		\label{sec:chario}
5492
5493See \secref{chars} for an overview of supported character
5494representations.
5495
5496\begin{description}
5497    \predicate[ISO]{nl}{0}{}
5498Write a newline character to the current output stream.  On Unix systems
5499nl/0 is equivalent to \exam{put(10)}.
5500
5501    \predicate[ISO]{nl}{1}{+Stream}
5502Write a newline to \arg{Stream}.
5503
5504    \predicate{put}{1}{+Char}
5505Write \arg{Char} to the current output stream. \arg{Char} is either an
5506integer expression evaluating to a character code or an atom of one
5507character.  Deprecated.  New code should use put_char/1 or put_code/1.
5508
5509    \predicate{put}{2}{+Stream, +Char}
5510Write \arg{Char} to \arg{Stream}.  See put/1 for details.
5511
5512    \predicate[ISO]{put_byte}{1}{+Byte}
5513Write a single byte to the output.  \arg{Byte} must be an integer
5514between 0 and 255.
5515
5516    \predicate[ISO]{put_byte}{2}{+Stream, +Byte}
5517Write a single byte to \arg{Stream}. \arg{Byte} must be an integer
5518between 0 and 255.
5519
5520    \predicate[ISO]{put_char}{1}{+Char}
5521Write a character to the current output, obeying the encoding defined
5522for the current output stream. Note that this may raise an exception if
5523the encoding of the output stream cannot represent \arg{Char}.
5524
5525    \predicate[ISO]{put_char}{2}{+Stream, +Char}
5526Write a character to \arg{Stream}, obeying the encoding defined for
5527\arg{Stream}. Note that this may raise an exception if the
5528encoding of \arg{Stream} cannot represent \arg{Char}.
5529
5530    \predicate[ISO]{put_code}{1}{+Code}
5531Similar to put_char/1, but using a \jargon{character code}.  \arg{Code}
5532is a non-negative integer.  Note that this may raise an exception if the
5533encoding of the output stream cannot represent \arg{Code}.
5534
5535    \predicate[ISO]{put_code}{2}{+Stream, +Code}
5536Same as put_code/1 but directing \arg{Code} to \arg{Stream}.
5537
5538    \predicate{tab}{1}{+Amount}
5539Write \arg{Amount} spaces on the current output stream.  \arg{Amount}
5540should be an expression that evaluates to a positive integer (see
5541\secref{arith}).
5542
5543    \predicate{tab}{2}{+Stream, +Amount}
5544Write \arg{Amount} spaces to \arg{Stream}.
5545
5546    \predicate[ISO]{flush_output}{0}{}
5547Flush pending output on current output stream. flush_output/0 is
5548automatically generated by read/1 and derivatives if the current input
5549stream is \const{user} and the cursor is not at the left margin.
5550
5551    \predicate[ISO]{flush_output}{1}{+Stream}
5552Flush output on the specified stream.  The stream must be open for
5553writing.
5554
5555    \predicate{ttyflush}{0}{}
5556Flush pending output on stream \const{user}. See also flush_output/[0,1].
5557    \predicate[ISO]{get_byte}{1}{-Byte}
5558Read the current input stream and unify the next byte with \arg{Byte}
5559(an integer between 0 and 255). \arg{Byte} is unified with -1 on end of
5560file.
5561
5562    \predicate[ISO]{get_byte}{2}{+Stream, -Byte}
5563Read the next byte from \arg{Stream} and unify \arg{Byte} with an integer between
55640 and 255.
5565
5566    \predicate[ISO]{get_code}{1}{-Code}
5567Read the current input stream and unify \arg{Code} with the character
5568code of the next character. \arg{Code} is unified with -1 on end of
5569file.  See also get_char/1.
5570
5571    \predicate[ISO]{get_code}{2}{+Stream, -Code}
5572Read the next character code from \arg{Stream}.
5573
5574    \predicate[ISO]{get_char}{1}{-Char}
5575Read the current input stream and unify \arg{Char} with the next
5576character as a one-character atom.  See also atom_chars/2.
5577On end-of-file, \arg{Char} is unified to the atom \const{end_of_file}.
5578
5579    \predicate[ISO]{get_char}{2}{+Stream, -Char}
5580Unify \arg{Char} with the next character from \arg{Stream} as a
5581one-character atom.  See also get_char/2, get_byte/2 and get_code/2.
5582
5583    \predicate[deprecated]{get0}{1}{-Char}
5584Edinburgh version of the ISO get_code/1 predicate. Note that Edinburgh
5585Prolog didn't support wide characters and therefore technically speaking
5586get0/1 should have been mapped to get_byte/1.  The intention of get0/1,
5587however, is to read character codes.
5588
5589    \predicate[deprecated]{get0}{2}{+Stream, -Char}
5590Edinburgh version of the ISO get_code/2 predicate.  See also get0/1.
5591
5592    \predicate[deprecated]{get}{1}{-Char}
5593Read the current input stream and unify the next non-blank character
5594with \arg{Char}. \arg{Char} is unified with -1 on end of file.  The
5595predicate get/1 operates on character \emph{codes}.  See also get0/1.
5596
5597    \predicate[deprecated]{get}{2}{+Stream, -Char}
5598Read the next non-blank character from \arg{Stream}.  See also
5599get/1, get0/1 and get0/2.
5600
5601    \predicate[ISO]{peek_byte}{1}{-Byte}
5602    \nodescription
5603    \predicate[ISO]{peek_byte}{2}{+Stream, -Byte}
5604    \nodescription
5605    \predicate[ISO]{peek_code}{1}{-Code}
5606    \nodescription
5607    \predicate[ISO]{peek_code}{2}{+Stream, -Code}
5608    \nodescription
5609    \predicate[ISO]{peek_char}{1}{-Char}
5610    \nodescription
5611    \predicate[ISO]{peek_char}{2}{+Stream, -Char}
5612Read the next byte/code/char from the input without removing it.
5613These predicates do not modify the stream's position or end-of-file
5614status. These predicates require a buffered stream (see set_stream/2)
5615and raise a permission error if the stream is unbuffered or the buffer
5616is too small to hold the longest multi-byte sequence that might need to
5617be buffered.
5618
5619    \predicate{peek_string}{3}{+Stream, +Len, -String}
5620Read the next \arg{Len} characters (if the stream is a text stream) or
5621bytes (if the stream is binary) from Stream without removing the data.
5622If \arg{Len} is larger that the stream buffer size, the buffer size is
5623increased to \arg{Len}.  \arg{String} can be shorter than \arg{Len} if
5624the stream contains less data. This predicate is intended to guess the
5625content type of data read from non-repositionable streams.
5626
5627    \predicate{skip}{1}{+Code}
5628Read the input until \arg{Code} or the end of the file is encountered.
5629A subsequent call to get_code/1 will read the first character after
5630\arg{Code}.
5631
5632    \predicate{skip}{2}{+Stream, +Code}
5633Skip input (as skip/1) on \arg{Stream}.
5634
5635    \predicate{get_single_char}{1}{-Code}
5636Get a single character from input stream `user' (regardless of the
5637current input stream). Unlike get_code/1, this predicate does not
5638wait for a return. The character is not echoed to the user's terminal.
5639This predicate is meant for keyboard menu selection, etc. If SWI-Prolog
5640was started with the \cmdlineoption{--no-tty} option this predicate
5641reads an entire line of input and returns the first non-blank character
5642on this line, or the character code of the newline (10) if the entire
5643line consisted of blank characters. See also with_tty_raw/1.
5644
5645    \predicate{with_tty_raw}{1}{:Goal}
5646Run goal with the user input and output streams set in \jargon{raw
5647mode}, which implies the terminal makes the input available immediately
5648instead of line-by-line and input that is read is not echoed. As a
5649consequence, line editing does not work.  See also get_single_char/1.
5650
5651    \predicate[ISO]{at_end_of_stream}{0}{}
5652Succeeds after the last character of the current input stream has
5653been read.  Also succeeds if there is no valid current input stream.
5654
5655    \predicate[ISO]{at_end_of_stream}{1}{+Stream}
5656Succeeds after the last character of the named stream is read, or
5657\arg{Stream} is not a valid input stream.  The end-of-stream test
5658is only available on buffered input streams (unbuffered input streams
5659are rarely used; see open/4).
5660
5661    \predicate{set_end_of_stream}{1}{+Stream}
5662Set the size of the file opened as \arg{Stream} to the current
5663file position.  This is typically used in combination with the
5664open-mode \const{update}.
5665
5666    \predicate{copy_stream_data}{3}{+StreamIn, +StreamOut, +Len}
5667Copy \arg{Len} codes from \arg{StreamIn} to \arg{StreamOut}.
5668Note that the copy is done using the semantics of get_code/2 and
5669put_code/2, taking care of possibly recoding that needs to take place
5670between two text files.  See \secref{encoding}.
5671
5672    \predicate{copy_stream_data}{2}{+StreamIn, +StreamOut}
5673Copy all (remaining) data from \arg{StreamIn} to
5674\arg{StreamOut}.
5675
5676    \predicate[det]{fill_buffer}{1}{+Stream}
5677Fill the \arg{Stream}'s input buffer. Subsequent calls try to read more
5678input until the buffer is completely filled. This predicate is used
5679together with read_pending_codes/3 to process input with minimal
5680buffering.
5681
5682    \predicate{read_pending_codes}{3}{+StreamIn, -Codes, ?Tail}
5683Read input pending in the input buffer of \arg{StreamIn} and return
5684it in the difference list \arg{Codes}-\arg{Tail}. That is, the
5685available characters codes are used to create the list \arg{Codes}
5686ending in the tail \arg{Tail}. On encountering end-of-file, both
5687\arg{Codes} and \arg{Tail} are unified with the empty list ({[]}).
5688
5689This predicate is intended for efficient unbuffered copying and
5690filtering of input coming from network connections or devices. It also
5691enables the library \pllib{pure_input}, which processes input from files
5692and streams using a DCG.
5693
5694The following code fragment realises efficient non-blocking copying of data
5695from an input to an output stream. The at_end_of_stream/1 call checks
5696for end-of-stream and fills the input buffer.  Note that the use of
5697a get_code/2 and put_code/2 based loop requires a flush_output/1 call
5698after \emph{each} put_code/2.  The copy_stream_data/2 does not allow
5699for inspection of the copied data and suffers from the same buffering
5700issues.
5701
5702\begin{code}
5703copy(In, Out) :-
5704	repeat,
5705	    fill_buffer(In),
5706	    read_pending_codes(In, Chars, Tail),
5707	    \+ \+ ( Tail = [],
5708		    format(Out, '~s', [Chars]),
5709		    flush_output(Out)
5710		  ),
5711	    (   Tail == []
5712	    ->  !
5713	    ;   fail
5714	    ).
5715\end{code}
5716
5717    \predicate{read_pending_chars}{3}{+StreamIn, -Chars, ?Tail}
5718As read_pending_codes/3, but returns a difference list of one-character
5719atoms.
5720\end{description}
5721
5722\section{Term reading and writing}		\label{sec:termrw}
5723
5724This section describes the basic term reading and writing predicates.
5725The predicates format/[1,2] and writef/2 provide formatted output.
5726Writing to Prolog data structures such as atoms or code-lists is
5727supported by with_output_to/2 and format/3.
5728
5729Reading is sensitive to the Prolog flag \prologflag{character_escapes},
5730which controls the interpretation of the \chr{\} character in quoted
5731atoms and strings.
5732
5733\begin{description}
5734    \predicate[ISO]{write_term}{2}{+Term, +Options}
5735The predicate write_term/2 is the generic form of all Prolog term-write
5736predicates.  Valid options are:
5737
5738\begin{description}
5739    \termitem{attributes}{Atom}
5740Define how attributed variables (see \secref{attvar}) are written. The
5741default is determined by the Prolog flag \prologflag{write_attributes}.
5742Defined values are \const{ignore} (ignore the attribute), \const{dots}
5743(write the attributes as \verb${...}$), \const{write} (simply hand
5744the attributes recursively to write_term/2) and \const{portray}
5745(hand the attributes to attr_portray_hook/2).
5746
5747    \termitem{back_quotes}{Atom}
5748Fulfills the same role as the \prologflag{back_quotes} prolog flag.
5749Notably, the value \const{string} causes string objects to be printed
5750between back quotes and \const{symbol_char} causes the backquote to
5751be printed unquoted.  In all other cases the backquote is printed as
5752a quoted atom.
5753
5754    \termitem{brace_terms}{Bool}
5755If \const{true} (default), write \verb${}(X)$ as \verb${X}$.  See also
5756\const{dotlists} and \const{ignore_ops}.
5757
5758    \termitem{blobs}{Atom}
5759Define how non-text blobs are handled.  By default, this is left to
5760the write handler specified with the blob type.  Using \const{portray},
5761portray/1 is called for each blob encountered.  See \secref{blob}.
5762
5763    \termitem{character_escapes}{Bool}
5764If \const{true} and \term{quoted}{true} is active, special characters
5765in quoted atoms and strings are emitted as ISO escape sequences.
5766Default is taken from the reference module (see below).
5767
5768    \termitem{cycles}{Bool}
5769If \const{true} (default), cyclic terms are written as
5770\term{@}{Template, Substitutions}, where \arg{Substitutions} is a list
5771\mbox{\arg{Var} = \arg{Value}}. If \const{cycles} is \const{false},
5772\const{max_depth} is not given, and \arg{Term} is cyclic, write_term/2
5773raises a \const{domain_error}.\footnote{The cycles option and the cyclic
5774term representation using the @-term are copied from SICStus Prolog.
5775However, the default in SICStus is set to \const{false} and SICStus
5776writes an infinite term if not protected by, e.g., the
5777\const{depth_limit} option.} See also the \const{cycles} option in
5778read_term/2.
5779
5780    \termitem{dotlists}{Bool}
5781If \const{true} (default \const{false}), write lists using the
5782dotted term notation rather than the list notation.\footnote{Copied from
5783ECLiPSe.} Note that as of version~7, the list constructor is
5784\verb$'[|]'$. Using \term{dotlists}{true}, write_term/2 writes a list
5785using `.' as constructor. This is intended for communication with
5786programs such as other Prolog systems, that rely on this notation.
5787See also the option \term{no_lists}{true} to use the actual SWI-Prolog
5788list functor.
5789
5790    \termitem{fullstop}{Bool}
5791If \const{true} (default \const{false}), add a fullstop token to the
5792output.  The dot is preceded by a space if needed and followed by
5793a space (default) or newline if the \term{nl}{true} option is also
5794given.\footnote{Compatible with
5795\href{http://eclipseclp.org/doc/bips/kernel/ioterm/write_term-3.html}{ECLiPSe}}
5796
5797    \termitem{ignore_ops}{Bool}
5798If \const{true}, the generic term representation (<functor>(<args>
5799\ldots)) will be used for all terms.  Otherwise (default), operators
5800will be used where appropriate.\footnote{In traditional systems this
5801flag also stops the syntactic sugar notation for lists and brace terms.
5802In SWI-Prolog, these are controlled by the separate options
5803\const{dotlists} and \const{brace_terms}}.
5804
5805    \termitem{max_depth}{Integer}
5806If the term is nested deeper than \arg{Integer}, print the remainder
5807as ellipses (\ldots).  A 0 (zero) value (default) imposes no depth limit.
5808This option also delimits the number of printed items in a list.  Example:
5809
5810\begin{code}
5811?- write_term(a(s(s(s(s(0)))), [a,b,c,d,e,f]),
5812	      [max_depth(3)]).
5813a(s(s(...)), [a, b|...])
5814true.
5815\end{code}
5816
5817Used by the top level and debugger to limit screen output.  See also
5818the Prolog flags \prologflag{answer_write_options} and
5819\prologflag{debugger_write_options}.
5820
5821    \termitem{module}{Module}
5822Define the reference module (default \const{user}).  This defines
5823the default value for the \prologflag{character_escapes} option as well
5824as the operator definitions to use. If \arg{Module} does not exist it is
5825\emph{not} created and the \const{user} module is used.  See also op/3
5826and read_term/2, providing the same option.
5827
5828    \termitem{nl}{Bool}
5829Add a newline to the output.  See also the \const{fullstop} option.
5830
5831    \termitem{no_lists}{Bool}
5832Do not use list notation.  This is similar to \term{dotlists}{true},
5833but uses the SWI-Prolog list functor, which is by default \verb$'[|]'$
5834instead of the ISO Prolog \verb$'.'$.  Used by display/1.
5835
5836    \termitem{numbervars}{Bool}
5837If \const{true}, terms of the format \verb|$VAR(N)|, where \arg{N} is a
5838non-negative integer, will be written as a variable name. If \arg{N} is
5839an atom it is written without quotes. This extension allows for writing
5840variables with user-provided names. The default is \const{false}. See
5841also numbervars/3 and the option \const{variable_names}.
5842
5843    \termitem{partial}{Bool}
5844If \const{true} (default \const{false}), do not reset the logic that
5845inserts extra spaces that separate tokens where needed. This is intended
5846to solve the problems with the code below.  Calling \term{write_value}{.}
5847writes \verb$..$, which cannot be read.  By adding \term{partial}{true}
5848to the option list, it correctly emits \verb$. .$.  Similar problems appear
5849when emitting operators using multiple calls to write_term/3.
5850
5851\begin{code}
5852write_value(Value) :-
5853	write_term(Value, [partial(true)]),
5854	write('.'), nl.
5855\end{code}
5856
5857    \termitem{portray}{Bool}
5858Same as \term{portrayed}{Bool}.  Deprecated.
5859
5860    \termitem{portray_goal}{:Goal}
5861Implies \term{portray}{true}, but calls \arg{Goal} rather than the
5862predefined hook portray/1.  \arg{Goal} is called through call/3, where
5863the first argument is \arg{Goal}, the second is the term to be
5864printed and the 3rd argument is the current write option list.  The
5865write option list is copied from the write_term call, but the list
5866is guaranteed to hold an option \const{priority} that reflects the
5867current priority.
5868
5869    \termitem{portrayed}{Bool}
5870If \const{true}, the hook portray/1 is called before printing a term
5871that is not a variable.  If portray/1 succeeds, the term is considered
5872printed.  See also print/1.  The default is \const{false}.  This option
5873is an extension to the ISO write_term options.
5874
5875    \termitem{priority}{Integer}
5876An integer between 0 and 1200 representing the `context priority'.
5877Default is 1200.  Can be used to write partial terms appearing as
5878the argument to an operator.  For example:
5879
5880\begin{code}
5881	format('~w = ', [VarName]),
5882	write_term(Value, [quoted(true), priority(699)])
5883\end{code}
5884
5885    \termitem{quoted}{Bool}
5886If \const{true}, atoms and functors that need quotes will be quoted.
5887The default is \const{false}.
5888
5889    \termitem{spacing}{+Spacing}
5890Determines whether and where extra white space is added to enhance
5891readability. The default is \const{standard}, adding only space where
5892needed for proper tokenization by read_term/3.  Currently, the only
5893other value is \const{next_argument}, adding a space after a comma
5894used to separate arguments in a term or list.
5895
5896    \termitem{variable_names}{+List}
5897Assign names to variables in \arg{Term}. \arg{List} is a list of terms
5898\mbox{\arg{Name} = \arg{Var}}, where \arg{Name} is an atom that
5899represents a valid Prolog variable name. Terms where \arg{Var} is bound
5900or is a variable that does not appear in \arg{Term} are ignored. Raises
5901an error if \arg{List} is not a list, one of the members is not a term
5902\mbox{\arg{Name} = \arg{Var}}, \arg{Name} is not an atom or
5903\arg{Name} does not represent a valid Prolog variable name.
5904
5905The implementation binds the variables from \arg{List} to a term
5906\verb"'$VAR'"(\arg{Name}).  Like write_canonical/1, terms that
5907where already bound to \verb"'$VAR'"(\arg{X}) before write_term/2
5908are printed normally, unless the option \term{numbervars}{true} is
5909also provided.  If the option \term{numbervars}{true} is used, the
5910user is responsible for avoiding collisions between assigned names
5911and numbered names. See also the \const{variable_names} option of
5912read_term/2.
5913
5914Possible variable attributes (see \secref{attvar}) are ignored.  In
5915most cases one should use copy_term/3 to obtain a copy that is free
5916of attributed variables and handle the associated constraints as
5917appropriate for the use-case.
5918\end{description}
5919
5920    \predicate[ISO]{write_term}{3}{+Stream, +Term, +Options}
5921As write_term/2, but output is sent to \arg{Stream} rather than the
5922current output.
5923
5924    \predicate[semidet]{write_length}{3}{+Term, -Length, +Options}
5925True when \arg{Length} is the number of characters emitted for
5926\term{write_term}{Term, Options}.  In addition to valid options for
5927write_term/2, it processes the option:
5928
5929    \begin{description}
5930	\termitem{max_length}{+MaxLength}
5931If provided, fail if \arg{Length} would be larger than \arg{MaxLength}.
5932The implementation ensures that the runtime is limited when computing
5933the length of a huge term with a bounded maximum.
5934    \end{description}
5935
5936    \predicate[ISO]{write_canonical}{1}{+Term}
5937Write \arg{Term} on the current output stream using standard
5938parenthesised prefix notation (i.e., ignoring operator declarations).
5939Atoms that need quotes are quoted.  Terms written with this predicate
5940can always be read back, regardless of current operator declarations.
5941Equivalent to write_term/2 using the options \const{ignore_ops},
5942\const{quoted} and \const{numbervars} after numbervars/4 using the
5943\const{singletons} option.
5944
5945Note that due to the use of numbervars/4, non-ground terms must be
5946written using a \emph{single} write_canonical/1 call.  This used to
5947be the case anyhow, as garbage collection between multiple calls
5948to one of the write predicates can change the \verb|_G|<NNN> identity
5949of the variables.
5950
5951    \predicate[ISO]{write_canonical}{2}{+Stream, +Term}
5952Write \arg{Term} in canonical form on \arg{Stream}.
5953
5954    \predicate[ISO]{write}{1}{+Term}
5955Write \arg{Term} to the current output, using brackets and operators
5956where appropriate.
5957
5958    \predicate[ISO]{write}{2}{+Stream, +Term}
5959Write \arg{Term} to \arg{Stream}.
5960
5961    \predicate[ISO]{writeq}{1}{+Term}
5962Write \arg{Term} to the current output, using brackets and operators where
5963appropriate. Atoms that need quotes are quoted. Terms written with this
5964predicate can be read back with read/1 provided the currently active
5965operator declarations are identical.
5966
5967    \predicate[ISO]{writeq}{2}{+Stream, +Term}
5968Write \arg{Term} to \arg{Stream}, inserting quotes.
5969
5970    \predicate{writeln}{1}{+Term}
5971Equivalent to \exam{write(Term), nl.}. The output stream is locked,
5972which implies no output from other threads can appear between the term
5973and newline.
5974
5975    \predicate{writeln}{2}{+Stream, +Term}
5976Equivalent to \exam{write(Stream, Term), nl(Stream).}. The output stream
5977is locked, which implies no output from other threads can appear between
5978the term and newline.
5979
5980    \predicate{print}{1}{+Term}
5981Print a term for debugging purposes.  The predicate print/1 acts as
5982if defined as below.
5983
5984\begin{code}
5985print(Term) :-
5986    current_prolog_flag(print_write_options, Options), !,
5987    write_term(Term, Options).
5988print(Term) :-
5989    write_term(Term, [ portray(true),
5990		       numbervars(true),
5991		       quoted(true)
5992		     ]).
5993\end{code}
5994
5995The print/1 predicate is used primarily through the \verb$~p$ escape
5996sequence of format/2, which is commonly used in the recipes used by
5997print_message/2 to emit messages.
5998
5999The classical definition of this predicate is equivalent to the ISO
6000predicate write_term/2 using the options \term{portray}{true} and
6001\term{numbervars}{true}. The \term{portray}{true} option allows the
6002user to implement application-specific printing of terms printed during
6003debugging to facilitate easy understanding of the output. See also
6004portray/1 and \pllib{portray_text}. SWI-Prolog adds \term{quoted}{true}
6005to (1) facilitate the copying/pasting of terms that are not affected by
6006portray/1 and to (2) allow numbers, atoms and strings to be more easily
6007distinguished, e.g., \verb$42$, \verb$'42'$ and \verb$"42"$.
6008
6009    \predicate{print}{2}{+Stream, +Term}
6010Print \arg{Term} to \arg{Stream}.
6011
6012    \predicate{portray}{1}{+Term}
6013A dynamic predicate, which can be defined by the user to change the
6014behaviour of print/1 on (sub)terms.  For each subterm encountered that
6015is not a variable print/1 first calls portray/1 using the term as
6016argument.  For lists, only the list as a whole is given to portray/1.  If
6017portray/1 succeeds print/1 assumes the term has been written.
6018
6019    \predicate[ISO]{read}{1}{-Term}
6020Read the next \textbf{Prolog term} from the current input stream and
6021unify it with \arg{Term}. On reaching end-of-file \arg{Term} is unified
6022with the atom \const{end_of_file}. This is the same as read_term/2 using
6023an empty option list.
6024
6025\textbf{[NOTE]} You might have found this while looking for a predicate
6026to read input from a file or the user. Quite likely this is not what you
6027need in this case. This predicate is for reading a \textbf{Prolog term}
6028which may span multiple lines and must end in a \emph{full stop} (dot
6029character followed by a layout character). The predicates for reading
6030and writing Prolog terms are particularly useful for storing Prolog
6031data in a file or transferring them over a network communication channel
6032(socket) to another Prolog process. The libraries provide a wealth of
6033predicates to read data in other formats. See e.g., \pllib{readutil},
6034\pllib{pure_input} or libraries from the extension packages to read XML,
6035JSON, YAML, etc.
6036
6037    \predicate[ISO]{read}{2}{+Stream, -Term}
6038Read the next \textbf{Prolog term} from \arg{Stream}.  See read/1 and
6039read_term/2 for details.
6040
6041    \predicate{read_clause}{3}{+Stream, -Term, +Options}
6042Equivalent to read_term/3, but sets options according to the current
6043compilation context and optionally processes comments.  Defined
6044options:
6045
6046    \begin{description}
6047        \termitem{syntax_errors}{+Atom}
6048	See read_term/3, but the default is \const{dec10} (report
6049	and restart).
6050
6051	\termitem{term_position}{-TermPos}
6052	Same as for read_term/3.
6053
6054	\termitem{subterm_positions}{-TermPos}
6055	Same as for read_term/3.
6056
6057	\termitem{variable_names}{-Bindings}
6058	Same as for read_term/3.
6059
6060	\termitem{process_comment}{+Boolean}
6061	If \const{true} (default), call
6062	\term{prolog:comment_hook}{Comments, TermPos, Term} if this
6063	multifile hook is defined (see prolog:comment_hook/3).  This
6064	is used to drive PlDoc.
6065
6066	\termitem{comments}{-Comments}
6067	If provided, unify \arg{Comments} with the comments encountered
6068	while reading \arg{Term}. This option implies
6069	\term{process_comment}{false}.
6070    \end{description}
6071
6072The \const{singletons} option of read_term/3 is initialised from the
6073active style-checking mode.  The \const{module} option is initialised
6074to the current compilation module (see prolog_load_context/2).
6075
6076    \predicate[ISO]{read_term}{2}{-Term, +Options}
6077Read a term from the current input stream and unify the term with
6078\arg{Term}. The reading is controlled by options from the list of
6079\arg{Options}. If this list is empty, the behaviour is the same as for
6080read/1. The options are upward compatible with Quintus Prolog. The
6081argument order is according to the ISO standard.  Syntax errors are
6082always reported using exception-handling (see catch/3). Options:
6083
6084\begin{description}
6085    \termitem{backquoted_string}{Bool}
6086If \const{true}, read \verb$`$\ldots\verb$`$ to a string object (see
6087\secref{strings}).  The default depends on the Prolog flag
6088\prologflag{back_quotes}.
6089
6090    \termitem{character_escapes}{Bool}
6091Defines how to read \verb$\$ escape sequences in quoted atoms.
6092See the Prolog flag \prologflag{character_escapes} in current_prolog_flag/2.
6093(SWI-Prolog).
6094
6095    \termitem{comments}{-Comments}
6096Unify \arg{Comments} with a list of \arg{Position}-\arg{Comment}, where
6097\arg{Position} is a stream position object (see stream_position_data/3)
6098indicating the start of a comment and \arg{Comment} is a string object
6099containing the text including delimiters of a comment.  It returns all
6100comments from where the read_term/2 call started up to the end of the
6101term read.
6102
6103    \termitem{cycles}{Bool}
6104If \const{true} (default \const{false}), re-instantiate templates as
6105produced by the corresponding write_term/2 option. Note that the default
6106is \const{false} to avoid misinterpretation of \term{@}{Template,
6107Substitutions}, while the default of write_term/2 is \const{true} because
6108emitting cyclic terms without using the template construct produces an
6109infinitely large term (read: it will generate an error after producing
6110a huge amount of output).
6111
6112    \termitem{dotlists}{Bool}
6113If \const{true} (default \const{false}), read \verb$.(a,[])$ as a list,
6114even if lists are internally nor constructed using the dot as functor.
6115This is primarily intended to read the output from write_canonical/1
6116from other Prolog systems.  See \secref{ext-lists}.
6117
6118    \termitem{double_quotes}{Atom}
6119Defines how to read "\ldots" strings. See the Prolog flag
6120\prologflag{double_quotes}.  (SWI-Prolog).
6121
6122    \termitem{module}{Module}
6123Specify \arg{Module} for operators, \prologflag{character_escapes} flag
6124and \prologflag{double_quotes} flag. The value of the latter two is
6125overruled if the corresponding read_term/3 option is provided. If no
6126module is specified, the current `source module' is used. If the options
6127is provided but the target module does not exist, module \const{user} is
6128used because new modules by default inherit from \const{user}
6129
6130    \termitem{quasi_quotations}{-List}
6131If present, unify \arg{List} with the quasi quotations (see
6132\secref{quasiquotations}) instead of evaluating quasi quotations.
6133Each quasi quotation is a term \term{quasi_quotation}{+Syntax,
6134+Quotation, +VarDict, -Result}, where \arg{Syntax} is the term in
6135\verb${|Syntax||..|}$, \arg{Quotation} is a list of character codes that
6136represent the quotation, \arg{VarDict} is a list of
6137\arg{Name}=\arg{Variable} and \arg{Result} is a variable that shares
6138with the place where the quotation must be inserted.  This option is
6139intended to support tools that manipulate Prolog source text.
6140
6141    \termitem{singletons}{Vars}
6142As \const{variable_names}, but only reports the variables occurring only
6143once in the \arg{Term} read (ISO). If \arg{Vars} is the constant
6144\const{warning}, singleton variables are reported using print_message/2.
6145The variables appear in the order they have been read. The latter option
6146provides backward compatibility and is used to read terms from source
6147files. Not all singleton variables are reported as a warning.  See
6148\secref{singleton} for the rules that apply for warning about a
6149singleton variable.\footnote{As of version 7.7.17, \emph{all} variables
6150starting with an underscore except for the truly anonymous variable
6151are returned in \arg{Vars}. Older versions only reported those that
6152would have been reported if \const{warning} is used.}
6153
6154    \termitem{syntax_errors}{Atom}
6155If \const{error} (default), throw an exception on a syntax error. Other
6156values are \const{fail}, which causes a message to be printed using
6157print_message/2, after which the predicate fails, \const{quiet} which
6158causes the predicate to fail silently, and \const{dec10} which causes
6159syntax errors to be printed, after which read_term/[2,3] continues
6160reading the next term. Using \const{dec10}, read_term/[2,3] never fails.
6161(Quintus, SICStus).
6162
6163    \termitem{subterm_positions}{TermPos}
6164Describes the detailed layout of the term. The formats for the various
6165types of terms are given below. All positions are character positions. If
6166the input is related to a normal stream, these positions are relative to
6167the start of the input; when reading from the terminal, they are
6168relative to the start of the term.
6169    \begin{description}
6170        \definition{\arg{From}-\arg{To}}
6171    Used for primitive types (atoms, numbers, variables).
6172
6173        \termitem{string_position}{\arg{From}, \arg{To}}
6174    Used to indicate the position of a string enclosed in double
6175    quotes (\chr{"}).
6176
6177        \termitem{brace_term_position}{\arg{From}, \arg{To}, \arg{Arg}}
6178    Term of the form \exam{\{\ldots \}}, as used in DCG rules.  \arg{Arg}
6179    describes the argument.
6180
6181        \termitem{list_position}{\arg{From}, \arg{To},
6182				  \arg{Elms}, \arg{Tail}}
6183A list. \arg{Elms} describes the positions of the elements. If the list
6184specifies the tail as \mbox{\chr{|}<TailTerm>}, \arg{Tail} is unified
6185with the term position of the tail, otherwise with the atom \const{none}.
6186
6187        \termitem{term_position}{\arg{From}, \arg{To},
6188				 \arg{FFrom}, \arg{FTo}, \arg{SubPos}}
6189    Used for a compound term not matching one of the above.  \arg{FFrom}
6190    and \arg{FTo} describe the position of the functor.  \arg{SubPos}
6191    is a list, each element of which describes the term position of the
6192    corresponding subterm.
6193
6194	\termitem{dict_position}{\arg{From}, \arg{To},
6195				 \arg{TagFrom}, \arg{TagTo},
6196				 \arg{KeyValuePosList}}
6197    Used for a dict (see \secref{bidicts}). The position of the
6198    key-value pairs is described by \arg{KeyValuePosList}, which is a
6199    list of \functor{key_value_position}{7} terms. The
6200    \functor{key_value_position}{7} terms appear in the order of the
6201    input. Because maps to not preserve ordering, the key is provided in
6202    the position description.
6203
6204	\termitem{key_value_position}{\arg{From}, \arg{To},
6205				      \arg{SepFrom}, \arg{SepTo},
6206				      \arg{Key},
6207				      \arg{KeyPos}, \arg{ValuePos}}
6208    Used for key-value pairs in a map (see \secref{bidicts}). It is
6209    similar to the \functor{term_position}{5} that would be created,
6210    except that the key and value positions do not need an intermediate
6211    list and the key is provided in \arg{Key} to enable synchronisation
6212    of the file position data with the data structure.
6213
6214	\termitem{parentheses_term_position}{\arg{From}, \arg{To},
6215					     \arg{ContentPos}}
6216    Used for terms between parentheses. This is an extension compared to
6217    the original Quintus specification that was considered necessary for
6218    secure refactoring of terms.
6219
6220	\termitem{quasi_quotation_position}{\arg{From}, \arg{To},
6221					    \arg{SyntaxFrom}, \arg{SyntaxTo},
6222					    \arg{ContentPos}}
6223    Used for quasi quotations.
6224    \end{description}
6225
6226    \termitem{term_position}{Pos}
6227Unifies \arg{Pos} with the starting position of the term read.  \arg{Pos}
6228is of the same format as used by stream_property/2.
6229
6230    \termitem{var_prefix}{Bool}
6231If \const{true}, demand variables to start with an underscore.  See
6232\secref{varprefix}.
6233
6234    \termitem{variables}{Vars}
6235Unify \arg{Vars} with a list of variables in the term. The variables
6236appear in the order they have been read. See also term_variables/2.
6237(ISO).
6238
6239    \termitem{variable_names}{Vars}
6240Unify \arg{Vars} with a list of `\arg{Name} = \arg{Var}', where
6241\arg{Name} is an atom describing the variable name and \arg{Var} is a
6242variable that shares with the corresponding variable in \arg{Term}.
6243(ISO). The variables appear in the order they have been read.
6244\end{description}
6245
6246    \predicate[ISO]{read_term}{3}{+Stream, -Term, +Options}
6247Read term with options from \arg{Stream}.  See read_term/2.
6248
6249    \predicate{read_term_from_atom}{3}{+Atom, -Term, +Options}
6250Use read_term/3 to read the next term from \arg{Atom}.  \arg{Atom} is
6251either an atom or a string object (see \secref{strings}).  It is not
6252required for \arg{Atom} to end with a full-stop.  This predicate
6253supersedes atom_to_term/3.
6254
6255    \predicate{read_history}{6}{+Show, +Help, +Special, +Prompt, -Term, -Bindings}
6256Similar to read_term/2 using the option \const{variable_names}, but
6257allows for history substitutions. read_history/6 is used by the top level
6258to read the user's actions. \arg{Show} is the command the user
6259should type to show the saved events. \arg{Help} is the command to get
6260an overview of the capabilities. \arg{Special} is a list of commands
6261that are not saved in the history. \arg{Prompt} is the first prompt
6262given. Continuation prompts for more lines are determined by prompt/2. A
6263\verb$~!$ in the prompt is substituted by the event number. See
6264\secref{history} for available substitutions.
6265
6266SWI-Prolog calls read_history/6 as follows:
6267
6268\begin{code}
6269read_history(h, '!h', [trace], '~! ?- ', Goal, Bindings)
6270\end{code}
6271
6272    \predicate{prompt}{2}{-Old, +New}
6273Set prompt associated with reading from the \const{user_input} stream.
6274\arg{Old} is first unified with the current prompt. On success the
6275prompt will be set to \arg{New} (an atom). A prompt is printed if data
6276is read from \const{user_input}, the cursor is at the left margin and
6277the \const{user_input} is considered to be connected to a terminal. See
6278the \term{tty}{Bool} property of stream_property/2 and set_stream/2.
6279
6280The default prompt is \verb$'|: '$. Note that the toplevel loop (see
6281prolog/0) sets the prompt for the first prompt (see prompt1/1) to
6282\verb$'?- '$, possibly decorated by the history event number,
6283\jargon{break level} and debug mode. If the first line does not complete
6284the term, subsequent lines are prompted for using the prompt as defined
6285by prompt/2.
6286
6287    \predicate{prompt1}{1}{+Prompt}
6288Sets the prompt for the next line to be read.  Continuation lines will
6289be read using the prompt defined by prompt/2.
6290\end{description}
6291
6292\section{Analysing and Constructing Terms}	\label{sec:manipterm}
6293
6294\begin{description}
6295    \predicate[ISO]{functor}{3}{?Term, ?Name, ?Arity}
6296True when \arg{Term} is a term with functor \arg{Name}/\arg{Arity}. If
6297\arg{Term} is a variable it is unified with a new term whose arguments are all
6298different variables (such a term is called a skeleton). If \arg{Term} is
6299atomic, \arg{Arity} will be unified with the integer 0, and \arg{Name} will be
6300unified with \arg{Term}.  Raises \errorterm{instantiation_error}{} if \arg{Term}
6301is unbound and \arg{Name}/\arg{Arity} is insufficiently instantiated.
6302
6303SWI-Prolog also supports terms with arity 0, as in \exam{a()} (see
6304\secref{extensions}. Such terms must be processed using
6305compound_name_arity/3. The predicate functor/3 and \predref{=..}{2}
6306raise a \const{domain_error} when faced with these terms. Without this
6307precaution a \jargon{round trip} of a term with arity 0 over functor/3
6308would create an atom.
6309
6310    \predicate[ISO]{arg}{3}{?Arg, +Term, ?Value}
6311\arg{Term} should be instantiated to a term, \arg{Arg} to an integer
6312between 1 and the arity of \arg{Term}. \arg{Value} is unified with the
6313\arg{Arg}-th argument of \arg{Term}.  \arg{Arg} may also be unbound.
6314In this case \arg{Value} will be unified with the successive arguments
6315of the term. On successful unification, \arg{Arg} is unified with the
6316argument number. Backtracking yields alternative solutions.%
6317    \footnote{The instantiation pattern (-, +, ?) is an extension to
6318              `standard' Prolog. Some systems provide
6319	      \nopredref{genarg}{3} that covers this pattern.}
6320The predicate arg/3 fails silently if $\arg{Arg} = 0$ or
6321$\arg{Arg} > \mbox{\em arity}$ and raises the exception
6322\errorterm{domain_error}{not_less_than_zero, \arg{Arg}} if $\arg{Arg} <
63230$.
6324
6325    \infixop[ISO]{=..}{?Term}{?List}
6326\arg{List} is a list whose head is the functor of \arg{Term} and the
6327remaining arguments are the arguments of the term. Either side of the
6328predicate may be a variable, but not both.  This predicate is called
6329`Univ'.
6330
6331\begin{code}
6332?- foo(hello, X) =.. List.
6333List = [foo, hello, X]
6334
6335?- Term =.. [baz, foo(1)].
6336Term = baz(foo(1))
6337\end{code}
6338
6339SWI-Prolog also supports terms with arity 0, as in \exam{a()} (see
6340\secref{extensions}. Such terms must be processed using
6341compound_name_arguments/3. This predicate raises a domain error as shown
6342below. See also functor/3.
6343
6344\begin{code}
6345?- a() =.. L.
6346ERROR: Domain error: `compound_non_zero_arity' expected, found `a()'
6347\end{code}
6348
6349    \predicate{compound_name_arity}{3}{?Compound, ?Name, ?Arity}
6350Rationalized version of functor/3 that only works for compound terms
6351and can examine and create compound terms with zero arguments (e.g,
6352\exam{name()}).  See also compound_name_arguments/3.
6353
6354    \predicate{compound_name_arguments}{3}{?Compound, ?Name, ?Arguments}
6355Rationalized version of \predref{=..}{2} that can compose and decompose
6356compound terms with zero arguments. See also compound_name_arity/3.
6357
6358    \predicate{numbervars}{3}{+Term, +Start, -End}
6359Unify the free variables in \arg{Term} with a term \term{\$VAR}{N},
6360where \arg{N} is the number of the variable. Counting starts at
6361\arg{Start}. \arg{End} is unified with the number that should be given
6362to the next variable.\bug{Only \jargon{tagged integers} are supported
6363(see the Prolog flag \prologflag{max_tagged_integer}). This suffices to
6364count all variables that can appear in the largest term that can be
6365represented, but does not support arbitrary large integer values for
6366\arg{Start}. On overflow, a \term{representation_error}{tagged_integer}
6367exception is raised.} The example below illustrates this. Note that the
6368toplevel prints \verb!'$VAR'(0)! as \arg{A} due to the
6369\term{numbervars}{true} option used to print answers.
6370
6371\begin{code}
6372?- Term = f(X,Y,X),
6373   numbervars(Term, 0, End),
6374   write_canonical(Term), nl.
6375f('$VAR'(0),'$VAR'(1),'$VAR'(0))
6376Term = f(A, B, A),
6377X = A,
6378Y = B,
6379End = 2.
6380\end{code}
6381
6382See also the \const{numbervars} option to write_term/3 and numbervars/4.
6383
6384    \predicate{numbervars}{4}{+Term, +Start, -End, +Options}
6385As numbervars/3, providing the following options:
6386
6387    \begin{description}
6388        \termitem{functor_name}{+Atom}
6389Name of the functor to use instead of \verb|$VAR|.
6390
6391	\termitem{attvar}{+Action}
6392What to do if an attributed variable is encountered.  Options are
6393\const{skip}, which causes numbervars/3 to ignore the attributed
6394variable, \const{bind} which causes it to treat it as a normal
6395variable and assign the next \verb|'$VAR'|(N) term to it, or (default)
6396\const{error} which raises a \const{type_error} exception.%
6397	\footnote{This behaviour was decided after a long discussion
6398		  between David Reitter, Richard O'Keefe, Bart Demoen
6399		  and Tom Schrijvers.}
6400
6401	\termitem{singletons}{+Bool}
6402If \const{true} (default \const{false}), numbervars/4 does singleton
6403detection.  Singleton variables are unified with \verb|'$VAR'('_')|,
6404causing them to be printed as \verb|_| by write_term/2 using the
6405numbervars option.  This option is exploited by portray_clause/2
6406and write_canonical/2.%
6407	\bug{Currently this option is ignored for cyclic terms.}
6408    \end{description}
6409
6410    \predicate{var_number}{2}{@Term, -VarNumber}
6411True if \arg{Term} is numbered by numbervars/3 and \arg{VarNumber} is
6412the number given to this variable.  This predicate avoids the need for
6413unification with \verb!'$VAR'(X)! and opens the path for replacing this
6414valid Prolog term by an internal representation that has no textual
6415equivalent.
6416
6417    \predicate[ISO]{term_variables}{2}{+Term, -List}
6418Unify \arg{List} with a list of variables, each sharing with a unique variable
6419of \arg{Term}.%
6420	\footnote{This predicate used to be called
6421	\nopredref{free_variables}{2}. The name term_variables/2 is more
6422	widely used. The old predicate is still available from the
6423	library \pllib{backcomp}.}
6424The variables in \arg{List} are ordered in order of appearance
6425traversing \arg{Term} depth-first and left-to-right. See also
6426term_variables/3 and nonground/2. For example:
6427
6428\begin{code}
6429?- term_variables(a(X, b(Y, X), Z), L).
6430L = [X, Y, Z].
6431\end{code}
6432
6433    \predicate[semidet]{nonground}{2}{+Term, -Var}
6434True when \arg{Var} is a variable in \arg{Term}.  Fails if \arg{Term}
6435is \jargon{ground} (see ground/1).  This predicate is intended for
6436coroutining to trigger a wakeup if \arg{Term} becomes ground, e.g.,
6437using when/2.  The current implementation always returns the first
6438variable in depth-first left-right search.  Ideally it should return
6439a random member of the set of variables (see term_variables/2) to
6440realise logarithmic complexity for the ground trigger.  Compatible
6441with ECLiPSe and hProlog.
6442
6443    \predicate{term_variables}{3}{+Term, -List, ?Tail}
6444Difference list version of term_variables/2.  That is, \arg{Tail} is the
6445tail of the variable list \arg{List}.
6446
6447    \predicate{term_singletons}{2}{+Term, -List}
6448Unify \arg{List} with a list of variables, each sharing with a variable
6449that appears only once in \arg{Term}.\bug{In the current implementation
6450\arg{Term} must be acyclic.  If not, a \const{representation_error} is
6451raised.}  Note that, if a variable appears
6452in a shared subterm, it is \emph{not} considered singleton. Thus,
6453\arg{A} is \emph{not} a singleton in the example below.  See also
6454the \const{singleton} option of numbervars/4.
6455
6456\begin{code}
6457
6458?- S = a(A), term_singletons(t(S,S), L).
6459L = [].
6460\end{code}
6461
6462    \predicate{is_most_general_term}{1}{@Term}
6463True if \arg{Term} is a callable term where all arguments are
6464non-sharing variables or \arg{Term} is a list whose members are
6465all non-sharing variables.  This predicate is used to reason about
6466call subsumption for tabling and is compatible with XSB. See
6467also subsumes_term/2.  Examples:
6468
6469\begin{quote}
6470\begin{tabular}{rlc}
64711 & \tt	is_most_general_term(1)	     & false \\
64722 & \tt	is_most_general_term(p)	     & true  \\
64733 & \tt	is_most_general_term(p(_))   & true  \\
64744 & \tt	is_most_general_term(p(_,a)) & false \\
64755 & \tt	is_most_general_term(p(X,X)) & false \\
64766 & \tt	is_most_general_term([])     & true  \\
64777 & \tt	is_most_general_term([_|_])  & false \\
64788 & \tt	is_most_general_term([_,_])  & true  \\
64799 & \tt	is_most_general_term([X,X])  & false \\
6480\end{tabular}
6481\end{quote}
6482
6483    \predicate[ISO]{copy_term}{2}{+In, -Out}
6484Create a version of \arg{In} with renamed (fresh) variables and unify it
6485to \arg{Out}.  Attributed variables (see \secref{attvar}) have their
6486attributes copied.  The implementation of copy_term/2 can deal with
6487infinite trees (cyclic terms). As pure Prolog cannot distinguish a
6488ground term from another ground term with exactly the same structure,
6489ground sub-terms are \emph{shared} between \arg{In} and \arg{Out}.
6490Sharing ground terms does affect setarg/3.  SWI-Prolog provides
6491duplicate_term/2 to create a true copy of a term.
6492\end{description}
6493
6494
6495\subsection{Non-logical operations on terms}	\label{sec:setarg}
6496
6497Prolog is not able to \emph{modify} instantiated parts of a term.
6498Lacking that capability makes the language much safer, but
6499unfortunately there are problems that suffer severely in terms of
6500time and/or memory usage.  Always try hard to avoid the use of
6501these primitives, but they can be a good alternative to using
6502dynamic predicates.  See also \secref{gvar}, discussing the use
6503of global variables.
6504
6505\begin{description}
6506    \predicate{setarg}{3}{+Arg, +Term, +Value}
6507Extra-logical predicate.  Assigns the \arg{Arg}-th argument of the
6508compound term \arg{Term} with the given \arg{Value}.  The assignment
6509is undone if backtracking brings the state back into a position before
6510the setarg/3 call.  See also nb_setarg/3.
6511
6512This predicate may be used for destructive assignment to terms, using
6513them as an extra-logical storage bin. Always try hard to avoid the use
6514of setarg/3 as it is not supported by many Prolog systems and one has to
6515be very careful about unexpected copying as well as unexpected
6516noncopying of terms. A good practice to improve somewhat on this situation
6517is to make sure that terms whose arguments are subject to setarg/3 have
6518one unused and unshared variable in addition to the used arguments. This
6519variable avoids unwanted sharing in, e.g., copy_term/2, and causes the
6520term to be considered as non-ground. An alternative is to use put_attr/3
6521to attach information to attributed variables (see~\secref{attvar}).
6522
6523    \predicate{nb_setarg}{3}{+Arg, +Term, +Value}
6524Assigns the \arg{Arg}-th argument of the compound term \arg{Term} with
6525the given \arg{Value} as setarg/3, but on backtracking the assignment
6526is \emph{not} reversed.  If \arg{Value} is not atomic, it is duplicated
6527using duplicate_term/2. This predicate uses the same technique as
6528nb_setval/2.  We therefore refer to the description of nb_setval/2
6529for details on non-backtrackable assignment of terms.  This predicate
6530is compatible with GNU-Prolog \term{setarg}{A,T,V,false}, removing the
6531type restriction on \arg{Value}.  See also nb_linkarg/3.  Below
6532is an example for counting the number of solutions of a goal.  Note
6533that this implementation is thread-safe, reentrant and capable of
6534handling exceptions.  Realising these features with a traditional
6535implementation based on assert/retract or flag/3 is much more
6536complicated.
6537
6538\begin{code}
6539:- meta_predicate
6540	succeeds_n_times(0, -).
6541
6542succeeds_n_times(Goal, Times) :-
6543	Counter = counter(0),
6544	(   Goal,
6545	    arg(1, Counter, N0),
6546	    N is N0 + 1,
6547	    nb_setarg(1, Counter, N),
6548	    fail
6549	;   arg(1, Counter, Times)
6550	).
6551\end{code}
6552
6553    \predicate{nb_linkarg}{3}{+Arg, +Term, +Value}
6554As nb_setarg/3, but like nb_linkval/2 it does \emph{not} duplicate
6555\arg{Value}.  Use with extreme care and consult the documentation
6556of nb_linkval/2 before use.
6557
6558    \predicate{duplicate_term}{2}{+In, -Out}
6559Version of copy_term/2 that also copies ground terms and therefore
6560ensures that destructive modification using setarg/3 does not affect the
6561copy.  See also nb_setval/2, nb_linkval/2, nb_setarg/3 and nb_linkarg/3.
6562
6563    \predicate[semidet]{same_term}{2}{@T1, @T2}
6564True if \arg{T1} and \arg{T2} are equivalent and will remain
6565equivalent, even if setarg/3 is used on either of them.   This means
6566\arg{T1} and \arg{T2} are the same variable, equivalent atomic data
6567or a compound term allocated at the same address.
6568\end{description}
6569
6570
6571\section{Analysing and Constructing Atoms}	\label{sec:manipatom}
6572
6573These predicates convert between certain Prolog atomic values on one
6574hand and lists of \jargon{character codes} (or, for atom_chars/2,
6575\jargon{characters}) on the other. The Prolog atomic values can be
6576atoms, \jargon{character}s (which are atoms of length 1), SWI-Prolog
6577strings, as well as numbers (integers, floats and non-integer
6578rationals).
6579
6580The \jargon{character codes}, also known as \jargon{code values}, are
6581integers. In SWI-Prolog, these integers are Unicode code points.\bug{On
6582Windows the range is limited to UCS-2, 0..65535.}
6583
6584To ease the pain of all text representation variations in the Prolog
6585community, all SWI-Prolog predicates behave as \emph{flexible as
6586possible}. This implies the `list-side' accepts both a
6587character-code-list and a character-list and the `atom-side' accepts all
6588atomic types (atom, number and string). For example, the predicates
6589atom_codes/2, number_codes/2 and name/2 behave the same in mode (+,-),
6590i.e., `listwards', from a constant to a list of character codes. When
6591converting the other way around:
6592
6593\begin{itemize}
6594   \item atom_codes/2 will generate an atom;
6595   \item number_codes/2 will generate a number or throw an exception;
6596   \item name/2 will generate a number if possible and an atom otherwise.
6597\end{itemize}
6598
6599\begin{description}
6600    \predicate[ISO]{atom_codes}{2}{?Atom, ?CodeList}
6601Convert between an atom and a list of \jargon{character codes} (integers
6602denoting characters).
6603
6604\begin{itemize}
6605   \item If \arg{Atom} is instantiated, it will be translated into a list of
6606character codes, which are unified with \arg{CodeList}.
6607   \item If \arg{Atom} is uninstantiated and \arg{CodeList} is a list of
6608character codes, then \arg{Atom} will be unified with an atom constructed
6609from this list.
6610\end{itemize}
6611
6612\begin{code}
6613?- atom_codes(hello, X).
6614X = [104, 101, 108, 108, 111].
6615\end{code}
6616
6617The `listwards' call to atom_codes/2 can also be written
6618(functionally) using backquotes instead:
6619
6620\begin{code}
6621?- Cs = `hello`.
6622Cs = [104, 101, 108, 108, 111].
6623\end{code}
6624
6625Backquoted strings can be mostly found in the body of DCG rules that
6626process lists of character codes.
6627
6628Note that this is the default interpretation for backquotes. It can be
6629changed on a per-module basis by setting the value of the Prolog flag
6630\prologflag{back_quotes}.
6631
6632    \predicate[ISO]{atom_chars}{2}{?Atom, ?CharList}
6633Similar to atom_codes/2, but \arg{CharList} is a list of \jargon{character}s
6634(atoms of length 1) rather than a list of \jargon{character codes} (integers
6635denoting characters).
6636
6637\begin{code}
6638?- atom_chars(hello, X).
6639X = [h, e, l, l, o]
6640\end{code}
6641
6642    \predicate[ISO]{char_code}{2}{?Atom, ?Code}
6643Convert between a single \jargon{character} (an atom of length 1), and its
6644\jargon{character code} (an integer denoting the corresponding character).
6645The predicate alternatively accepts an SWI-Prolog string of
6646length 1 at \arg{Atom} place.
6647
6648    \predicate[ISO]{number_chars}{2}{?Number, ?CharList}
6649Similar to atom_chars/2, but converts between a number and its
6650representation as a list of \jargon{characters} (atoms of length 1).
6651
6652\begin{itemize}
6653   \item If \arg{CharList} is a
6654\jargon{proper list}, i.e., not unbound or a \jargon{partial list},
6655\arg{CharList} is parsed according to the Prolog syntax for numbers and
6656the resulting number is unified with \arg{Number}. A \except{syntax_error}
6657exception is raised if \arg{CharList} is instantiated to a ground, proper
6658list but does not represent a valid Prolog number.
6659   \item Otherwise, if \arg{Number} is indeed a number, \arg{Number} is
6660serialized and the result is unified with \arg{CharList}.
6661\end{itemize}
6662
6663Following the ISO standard, the Prolog syntax for number allows for
6664\emph{leading} white space (including newlines) and does not allow for
6665\emph{trailing} white space.\footnote{ISO also allows for Prolog
6666comments in leading white space. We--and most other
6667implementations--believe this is incorrect. We also believe it would
6668have been better not to allow for white space, or to allow for both
6669leading and trailing white space.}
6670
6671Prolog syntax-based conversion can also be achieved using format/3 and
6672read_from_chars/2.
6673
6674    \predicate[ISO]{number_codes}{2}{?Number, ?CodeList}
6675As number_chars/2, but converts to a list of character codes
6676rather than characters.  In the mode (-,+), both predicates
6677behave identically to improve handling of non-ISO source.
6678
6679    \predicate{atom_number}{2}{?Atom, ?Number}
6680Realises the popular combination of atom_codes/2 and number_codes/2 to
6681convert between atom and number (integer, float or non-integer rational)
6682in one predicate, avoiding the intermediate list. Unlike the ISO
6683standard number_codes/2 predicates, atom_number/2 fails silently in mode
6684(+,-) if \arg{Atom} does not represent a number.
6685
6686    \predicate{name}{2}{?Atomic, ?CodeList}
6687\arg{CodeList} is a list of character codes representing the same text
6688as \arg{Atomic}. Each of the arguments may be a variable, but not both.
6689
6690\begin{itemize}
6691   \item When \arg{CodeList} describes an integer or floating point number and
6692\arg{Atomic} is a variable, \arg{Atomic} will be unified with the numeric
6693value described by \arg{CodeList} (e.g., \exam{name(N, "300"), 400 is N +
6694100} succeeds).
6695   \item If \arg{CodeList} is not a representation of a number,
6696\arg{Atomic} will be unified with the atom with the name given by the
6697character code list.
6698   \item If \arg{Atomic} is an atom or number, the
6699unquoted print representation of it as a character code list is
6700unified with \arg{CodeList}.
6701\end{itemize}
6702
6703This predicate is part of the Edinburgh tradition. It should be
6704considered \jargon{deprecated} although, given its long tradition, it is
6705unlikely to be removed from the system. It still has some value for
6706converting input to a number or an atom (depending on the syntax). New code
6707should consider the ISO predicates atom_codes/2, number_codes/2 or the
6708SWI-Prolog predicate atom_number/2.
6709
6710    \predicate{term_to_atom}{2}{?Term, ?Atom}
6711True if \arg{Atom} describes a term that unifies with \arg{Term}. When
6712\arg{Atom} is instantiated, \arg{Atom} is parsed and the result unified
6713with \arg{Term}. If \arg{Atom} has no valid syntax, a
6714\except{syntax_error} exception is raised. Otherwise \arg{Term} is
6715``written'' on \arg{Atom} using write_term/2 with the option
6716\term{quoted}{true}. See also format/3, with_output_to/2 and
6717term_string/2.
6718
6719    \predicate[deprecated]{atom_to_term}{3}{+Atom, -Term, -Bindings}
6720Use \arg{Atom} as input to read_term/2 using the option
6721\const{variable_names} and return the read term in \arg{Term} and the
6722variable bindings in \arg{Bindings}. \arg{Bindings} is a list of
6723$\arg{Name} = \arg{Var}$ couples, thus providing access to the actual
6724variable names. See also read_term/2. If \arg{Atom} has no valid syntax,
6725a \except{syntax_error} exception is raised.  New code should use
6726read_term_from_atom/3.
6727
6728    \predicate[ISO]{atom_concat}{3}{?Atom1, ?Atom2, ?Atom3}
6729\arg{Atom3} forms the concatenation of \arg{Atom1} and \arg{Atom2}. At
6730least two of the arguments must be instantiated to atoms. This predicate
6731also allows for the mode (-,-,+), non-deterministically splitting the
67323rd argument into two parts (as append/3 does for lists).  SWI-Prolog
6733allows for atomic arguments.  Portable code must use atomic_concat/3
6734if non-atom arguments are involved.
6735
6736    \predicate{atomic_concat}{3}{+Atomic1, +Atomic2, -Atom}
6737\arg{Atom} represents the text after converting \arg{Atomic1} and
6738\arg{Atomic2} to text and concatenating the result:
6739
6740\begin{code}
6741?- atomic_concat(name, 42, X).
6742X = name42.
6743\end{code}
6744
6745    \predicate[commons]{atomic_list_concat}{2}{+List, -Atom}
6746\arg{List} is a list of strings, atoms, integers, floating point numbers
6747or non-integer rationals. Succeeds if \arg{Atom} can be unified with the
6748concatenated elements of \arg{List}. Equivalent to
6749\term{atomic_list_concat}{List, '', Atom}.
6750
6751    \predicate[commons]{atomic_list_concat}{3}{+List, +Separator, -Atom}
6752Creates an atom just like atomic_list_concat/2, but inserts \arg{Separator}
6753between each pair of inputs. For example:
6754\begin{code}
6755?- atomic_list_concat([gnu, gnat], ', ', A).
6756
6757A = 'gnu, gnat'
6758\end{code}
6759
6760The `atomwards` transformation is usually called a \jargon{string join}
6761operation in other programming languages.
6762
6763The SWI-Prolog version of this predicate can also be used to split atoms
6764by instantiating \arg{Separator} and \arg{Atom} as shown below.  We kept
6765this functionality to simplify porting old SWI-Prolog code where this
6766predicate was called concat_atom/3.  When used in mode (-,+,+),
6767\arg{Separator} must be a non-empty atom.  See also split_string/4.
6768
6769\begin{code}
6770?- atomic_list_concat(L, -, 'gnu-gnat').
6771
6772L = [gnu, gnat]
6773\end{code}
6774
6775    \predicate[ISO]{atom_length}{2}{+Atom, -Length}
6776True if \arg{Atom} is an atom of \arg{Length} characters. The
6777SWI-Prolog version accepts all atomic types, as well as code-lists and
6778character-lists. New code should avoid this feature and use
6779write_length/3 to get the number of characters that would be written if
6780the argument was handed to write_term/3.
6781
6782    \predicate[deprecated]{atom_prefix}{2}{+Atom, +Prefix}
6783True if \arg{Atom} starts with the characters from \arg{Prefix}.
6784Its behaviour is equivalent to
6785\exam{?- sub_atom(\arg{Atom}, 0, _, _, \arg{Prefix})}.  Deprecated.
6786
6787    \predicate[ISO]{sub_atom}{5}{+Atom, ?Before, ?Len, ?After, ?Sub}
6788ISO predicate for breaking atoms.  It maintains the following relation:
6789\arg{Sub} is a sub-atom of \arg{Atom} that starts at \arg{Before}, has
6790\arg{Len} characters, and \arg{Atom} contains \arg{After} characters
6791after the match.
6792
6793\begin{code}
6794?- sub_atom(abc, 1, 1, A, S).
6795
6796A = 1, S = b
6797\end{code}
6798
6799The implementation minimises non-determinism and creation of atoms.
6800This is a flexible predicate that can do search, prefix- and
6801suffix-matching, etc.
6802
6803    \predicate[semidet]{sub_atom_icasechk}{3}{+Haystack, ?Start, +Needle}
6804True when \arg{Needle} is a sub atom of \arg{Haystack} starting at
6805\arg{Start}. The match is `half case insensitive', i.e., uppercase
6806letters in \arg{Needle} only match themselves, while lowercase letters
6807in \arg{Needle} match case insensitively.  \arg{Start} is the first
68080-based offset inside \arg{Haystack} where \arg{Needle}
6809matches.\footnote{This predicate replaces \$apropos_match/2, used by the
6810help system, while extending it with locating the (first) match and
6811performing case insensitive prefix matching. We are still not happy
6812with the name and interface.}
6813\end{description}
6814
6815
6816\section{Localization (locale) support}		\label{sec:locale}
6817
6818SWI-Prolog provides (currently limited) support for localized
6819applications.
6820
6821\begin{itemize}
6822    \item
6823The predicates char_type/2 and code_type/2 query character classes
6824depending on the locale.
6825    \item
6826The predicates collation_key/2 and locale_sort/2 can be used for
6827locale dependent sorting of atoms.
6828    \item
6829The predicate format_time/3 can be used to format time and date
6830representations, where some of the specifiers are locale dependent.
6831    \item
6832The predicate format/2 provides locale-specific formatting of numbers.
6833This functionality is based on a more fine-grained localization model
6834that is the subject of this section.
6835\end{itemize}
6836
6837A locale is a (optionally named) read-only object that provides
6838information to locale specific functions.\footnote{The locale interface
6839described in this section and its effect on format/2 and reading
6840integers from digit groups was discussed on the SWI-Prolog mailinglist.
6841Most input in this discussion is from Ulrich Neumerkel and Richard
6842O'Keefe. The predicates in this section were designed by Jan
6843Wielemaker.} The system creates a default locale object named
6844\const{default} from the system locale. This locale is used as the
6845initial locale for the three standard streams as well as the
6846\const{main} thread. Locale sensitive output predicates such as format/3
6847get their locale from the stream to which they deliver their output. New
6848streams get their locale from the thread that created the stream.
6849Threads get their locale from the thread that created them.
6850
6851\begin{description}
6852    \predicate{locale_create}{3}{-Locale, +Default, +Options}
6853Create a new locale object.  \arg{Default} is either an existing
6854locale or a string that denotes the name of a locale provided by
6855the system, such as \verb$"en_EN.UTF-8"$.  The values read from
6856the default locale can be modified using \arg{Options}.  \arg{Options}
6857provided are:
6858
6859    \begin{description}
6860	\termitem{alias}{+Atom}
6861    Give the locale a name.
6862	\termitem{decimal_point}{+Atom}
6863    Specify the decimal point to use.
6864	\termitem{thousands_sep}{+Atom}
6865    Specify the string that delimits digit groups.  Only
6866    effective is \const{grouping} is also specified.
6867	\termitem{grouping}{+List}
6868    Specify the grouping of digits.  Groups are created from
6869    the right (least significant) digits, left of the decimal
6870    point.  \arg{List} is a list of integers, specifying the
6871    number of digits in each group, counting from the right.
6872    If the last element is \term{repeat}{Count}, the remaining
6873    digits are grouped in groups of size \arg{Count}.  If the
6874    last element is a normal integer, digits further to the left
6875    are not grouped.
6876    \end{description}
6877
6878For example, the English locale uses
6879\begin{code}
6880[ decimal_point('.'), thousands_sep(','), grouping([repeat(3)]) ]
6881\end{code}
6882
6883Named locales exists until they are destroyed using locale_destroy/1
6884and they are no longer referenced.  Unnamed locales are subject to
6885(atom) garbage collection.
6886
6887    \predicate{locale_destroy}{1}{+Locale}
6888Destroy a locale.  If the locale is named, this removes the name
6889association from the locale, after which the locale is left to be
6890reclaimed by garbage collection.
6891
6892    \predicate{locale_property}{2}{?Locale, ?Property}
6893True when \arg{Locale} has \arg{Property}.  Properties are the same
6894as the \arg{Options} described with locale_create/3.
6895
6896    \predicate{set_locale}{1}{+Locale}
6897Set the default locale for the current thread, as well as the locale
6898for the standard streams (\const{user_input}, \const{user_output},
6899\const{user_error}, \const{current_output} and \const{current_input}.
6900This locale is used for new streams, unless overruled using the
6901\term{locale}{Locale} option of open/4 or set_stream/2.
6902
6903    \predicate{current_locale}{1}{-Locale}
6904True when \arg{Locale} is the locale of the calling thread.
6905\end{description}
6906
6907
6908\section{Character properties}		\label{sec:chartype}
6909
6910SWI-Prolog offers two comprehensive predicates for classifying
6911characters and character codes. These predicates are defined as built-in
6912predicates to exploit the C-character classification's handling of
6913\jargon{locale} (handling of local character sets). These predicates are
6914fast, logical and deterministic if applicable.
6915
6916In addition, there is the library \pllib{ctypes} providing compatibility
6917with some other Prolog systems. The predicates of this library are defined
6918in terms of code_type/2.
6919
6920\begin{description}
6921    \predicate{char_type}{2}{?Char, ?Type}
6922Tests or generates alternative \arg{Type}s or \arg{Char}s. The character
6923types are inspired by the standard C \file{<ctype.h>} primitives. The
6924types are sensititve to the active \jargon{locale}, see setlocale/3.
6925Most of the \arg{Type}s are mapped to the Unicode classification
6926functions from \file{<wctype.h>}, e.g., \const{alnum} uses iswalnum().
6927The types \const{prolog_var_start}, \const{prolog_atom_start},
6928\const{prolog_identifier_continue} and \const{prolog_symbol} are based
6929on the locale-independent built-in classification routines that are
6930also used by read/1 and friends.
6931
6932Note that the mode (-,+) is only efficient if the \arg{Type} has a
6933parameter, e.g., \term{char_type}{C, digit(8)}. If \arg{Type} is a
6934atomic, the whole unicode range (0..0x1ffff) is generated and tested
6935against the character classification function.
6936
6937\begin{description}
6938    \termitem{alnum}{}
6939\arg{Char} is a letter (upper- or lowercase) or digit.
6940    \termitem{alpha}{}
6941\arg{Char} is a letter (upper- or lowercase).
6942    \termitem{csym}{}
6943\arg{Char} is a letter (upper- or lowercase), digit or the underscore
6944(\verb$_$).  These are valid C and Prolog symbol characters.
6945    \termitem{csymf}{}
6946\arg{Char} is a letter (upper- or lowercase) or the underscore
6947(\verb$_$). These are valid first characters for C and Prolog symbols.
6948    \termitem{ascii}{}
6949\arg{Char} is a 7-bit ASCII character (0..127).
6950    \termitem{white}{}
6951\arg{Char} is a space or tab, i.e.\ white space inside a line.
6952    \termitem{cntrl}{}
6953\arg{Char} is an ASCII control character (0..31), ASCII DEL character
6954(127), or non-ASCII character in the range 128..159 or 8232..8233.
6955    \termitem{digit}{}
6956\arg{Char} is a digit.
6957    \termitem{digit}{Weight}
6958\arg{Char} is a digit with value \arg{Weight}. I.e.\ \exam{char_type(X,
6959digit(6))} yields \arg{X} = \exam{'6'}.  Useful for parsing numbers.
6960    \termitem{xdigit}{Weight}
6961\arg{Char} is a hexadecimal digit with value \arg{Weight}. I.e.\
6962\exam{char_type(a, xdigit(X))} yields \arg{X} = \exam{'10'}. Useful for
6963parsing numbers.
6964    \termitem{graph}{}
6965\arg{Char} produces a visible mark on a page when printed. Note that
6966the space is not included!
6967    \termitem{lower}{}
6968\arg{Char} is a lowercase letter.
6969    \termitem{lower}{Upper}
6970\arg{Char} is a lowercase version of \arg{Upper}. Only true if
6971\arg{Char} is lowercase and \arg{Upper} uppercase.
6972    \termitem{to_lower}{Upper}
6973\arg{Char} is a lowercase version of \arg{Upper}. For non-letters,
6974or letter without case, \arg{Char} and \arg{Lower} are the same.
6975See also upcase_atom/2 and downcase_atom/2.
6976    \termitem{upper}{}
6977\arg{Char} is an uppercase letter.
6978    \termitem{upper}{Lower}
6979\arg{Char} is an uppercase version of \arg{Lower}. Only true if
6980\arg{Char} is uppercase and \arg{Lower} lowercase.
6981    \termitem{to_upper}{Lower}
6982\arg{Char} is an uppercase version of \arg{Lower}.  For non-letters,
6983or letter without case, \arg{Char} and \arg{Lower} are the same.
6984See also upcase_atom/2 and downcase_atom/2.
6985    \termitem{punct}{}
6986\arg{Char} is a punctuation character. This is a \const{graph} character
6987that is not a letter or digit.
6988    \termitem{space}{}
6989\arg{Char} is some form of layout character (tab, vertical tab, newline,
6990etc.).
6991    \termitem{end_of_file}{}
6992\arg{Char} is -1.
6993    \termitem{end_of_line}{}
6994\arg{Char} ends a line (ASCII: 10..13).
6995    \termitem{newline}{}
6996\arg{Char} is a newline character (10).
6997    \termitem{period}{}
6998\arg{Char} counts as the end of a sentence (.,!,?).
6999    \termitem{quote}{}
7000\arg{Char} is a quote character (\verb$"$, \verb$'$, \verb$`$).
7001    \termitem{paren}{Close}
7002\arg{Char} is an open parenthesis and \arg{Close} is the corresponding
7003close parenthesis.
7004    \termitem{prolog_var_start}{}
7005\arg{Char} can start a Prolog variable name.
7006    \termitem{prolog_atom_start}{}
7007\arg{Char} can start a unquoted Prolog atom that is not a symbol.
7008    \termitem{prolog_identifier_continue}{}
7009\arg{Char} can continue a Prolog variable name or atom.
7010    \termitem{prolog_symbol}{}
7011\arg{Char} is a Prolog symbol character.  Sequences of Prolog
7012symbol characters glue together to form an unquoted atom.  Examples
7013are \const{=..}, \const{\=}, etc.
7014\end{description}
7015
7016    \predicate{code_type}{2}{?Code, ?Type}
7017As char_type/2, but uses character codes rather than one-character
7018atoms.  Please note that both predicates are as flexible as possible.
7019They handle either representation if the argument is instantiated
7020and will instantiate only with an integer code or a one-character atom,
7021depending of the version used. See also the Prolog flag
7022\prologflag{double_quotes}, atom_chars/2 and atom_codes/2.
7023\end{description}
7024
7025
7026\subsection{Case conversion}
7027\label{sec:case}
7028
7029There is nothing in the Prolog standard for converting case in textual
7030data.  The SWI-Prolog predicates code_type/2 and char_type/2 can be used
7031to test and convert individual characters. We have started some
7032additional support:
7033
7034\begin{description}
7035    \predicate{downcase_atom}{2}{+AnyCase, -LowerCase}
7036Converts the characters of \arg{AnyCase} into lowercase as char_type/2
7037does (i.e.\ based on the defined \jargon{locale} if Prolog provides
7038locale support on the hosting platform) and unifies the lowercase atom
7039with \arg{LowerCase}.
7040
7041    \predicate{upcase_atom}{2}{+AnyCase, -UpperCase}
7042Converts, similar to downcase_atom/2, an atom to uppercase.
7043\end{description}
7044
7045
7046\subsection{White space normalization}
7047\label{sec:whitespace}
7048
7049\begin{description}
7050    \predicate{normalize_space}{2}{-Out, +In}
7051Normalize white space in \arg{In}. All leading and trailing white space
7052is removed. All non-empty sequences for Unicode white space characters
7053are replaced by a single space (\verb$\u0020$) character.  \arg{Out}
7054uses the same conventions as with_output_to/2 and format/3.
7055\end{description}
7056
7057
7058\subsection{Language-specific comparison}
7059\label{sec:collate}
7060
7061\index{locale}\index{collate}\index{compare,language-specific}%
7062This section deals with predicates for language-specific string
7063comparison operations.
7064
7065\begin{description}
7066    \predicate{collation_key}{2}{+Atom, -Key}
7067Create a \arg{Key} from \arg{Atom} for locale-specific comparison.
7068The key is defined such that if the key of atom $A$ precedes the key
7069of atom $B$ in the standard order of terms, $A$ is alphabetically
7070smaller than $B$ using the sort order of the current locale.
7071
7072The predicate collation_key/2 is used by locale_sort/2 from
7073library(sort).  Please examine the implementation of locale_sort/2
7074as an example of using this call.
7075
7076The \arg{Key} is an implementation-defined and generally unreadable
7077string.  On systems that do not support locale handling, \arg{Key}
7078is simply unified with \arg{Atom}.
7079
7080    \predicate{locale_sort}{2}{+List, -Sorted}
7081Sort a list of atoms using the current locale.  \arg{List} is a list
7082of atoms or string objects (see \secref{strings}).  \arg{Sorted} is
7083unified with a list containing all atoms of \arg{List}, sorted to
7084the rules of the current locale.  See also collation_key/2 and
7085setlocale/3.
7086\end{description}
7087
7088
7089\section{Operators}			\label{sec:operators}
7090
7091Operators are defined to improve the readability of source code.
7092For example, without operators, to write \exam{2*3+4*5} one would have
7093to write \exam{+(*(2,3),*(4,5))}.  In Prolog, a number of operators have
7094been predefined. All operators, except for the comma (,) can be
7095redefined by the user.
7096
7097\index{operator,and modules}%
7098Some care has to be taken before defining new operators. Defining too
7099many operators might make your source `natural' looking, but at the same
7100time using many operators can make it hard to understand the limits of
7101your syntax.
7102
7103In SWI-Prolog, operators are local to the module in which they are
7104defined. Operators can be exported from modules using a term
7105\term{op}{Precedence, Type, Name} in the export list as specified by
7106module/2. Many modern Prolog systems have module specific operators.
7107Unfortunately, there is no established interface for exporting and
7108importing operators. SWI-Prolog's convention has been adopted by YAP.
7109
7110The module table of the module \const{user} acts as default table for
7111all modules and can be modified explicitly from inside a module to
7112achieve compatibility with other Prolog that do not have module-local
7113operators:
7114
7115\begin{code}
7116:- module(prove,
7117	  [ prove/1
7118	  ]).
7119
7120:- op(900, xfx, user:(=>)).
7121\end{code}
7122
7123Although operators are module-specific and the predicates that define
7124them (op/3) or rely on them such as current_op/3, read/1 and write/1 are
7125module sensitive, they are not proper meta-predicates. If they were
7126proper meta predicates read/1 and write/1 would use the module from
7127which they are called, breaking compatibility with other Prolog systems.
7128The following rules apply:
7129
7130\begin{enumerate}
7131    \item If the module is explicitly specified by qualifying the
7132          third argument (op/3, current_op/3) or specifying a
7133	  \term{module}{Module} option (read_term/3, write_term/3),
7134	  this module is used.
7135    \item While compiling, the module into which the compiled code
7136          is loaded applies.
7137    \item Otherwise, the \jargon{typein module} applies.  This is
7138          normally \const{user} and may be changed using module/1.
7139\end{enumerate}
7140
7141In SWI-Prolog, a \emph{quoted atom} never acts as an operator.  Note
7142that the portable way to stop an atom acting as an operator is to
7143enclose it in parentheses like this: (myop). See also
7144\secref{ext-syntax-op}.
7145
7146\begin{description}
7147    \predicate[ISO]{op}{3}{+Precedence, +Type, :Name}
7148Declare \arg{Name} to be an operator of type \arg{Type} with precedence
7149\arg{Precedence}. \arg{Name} can also be a list of names, in which case
7150all elements of the list are declared to be identical operators.
7151\arg{Precedence} is an integer between 0 and 1200. Precedence 0 removes
7152the declaration. \arg{Type} is one of: \const{xf}, \const{yf},
7153\const{xfx}, \const{xfy}, \const{yfx}, \const{fy} or
7154\const{fx}. The `\chr{f}' indicates the position of the functor, while
7155\chr{x} and \chr{y} indicate the position of the arguments. `\chr{y}'
7156should be interpreted as ``on this position a term with precedence lower
7157or equal to the precedence of the functor should occur''. For `\chr{x}'
7158the precedence of the argument must be strictly lower. The precedence of
7159a term is 0, unless its principal functor is an operator, in which case
7160the precedence is the precedence of this operator. A term enclosed in
7161parentheses \exam{(\ldots)} has precedence 0.
7162
7163The predefined operators are shown in \tabref{operators}. Operators can
7164be redefined, unless prohibited by one of the limitations below.
7165Applications must be careful with (re-)defining operators because
7166changing operators may cause (other) files to be interpreted
7167\textbf{differently}. Often this will lead to a syntax error. In other
7168cases, text is read silently into a different term which may lead to
7169subtle and difficult to track errors.
7170
7171\begin{itemize}
7172    \item It is not allowed to redefine the comma (\verb$','$).
7173    \item The bar (\verb$|$) can only be (re-)defined as infix
7174          operator with priority not less than 1001.
7175    \item It is not allowed to define the empty list (\verb$[]$) or the
7176	  curly-bracket pair (\verb${}$) as operators.
7177\end{itemize}
7178
7179In SWI-Prolog, operators are \emph{local} to a module (see also
7180\secref{moduleop}). Keeping operators in modules and using controlled
7181import/export of operators as described with the module/2 directive keep
7182the issues manageable. The module \const{system} provides the operators
7183from \tabref{operators} and these operators cannot be modified. Files
7184that are loaded from the SWI-Prolog directories resolve operators and
7185predicates from this \const{system} module rather than \const{user},
7186which makes the semantics of the library and development system modules
7187independent of operator changes to the \const{user} module.
7188See \secref{operators} for details about the relation between operators
7189and modules.
7190
7191\begin{table}
7192\begin{center}
7193\begin{tabular}{|r|D{f}{f}{-1}|p{4in}|}
7194\hline
71951200 & xfx & \op{-->}, \op{:-} \\
71961200 & fx & \op{:-}, \op{?-} \\
71971150 & fx & \op{dynamic}, \op{discontiguous}, \op{initialization},
7198	    \op{meta_predicate},
7199	    \op{module_transparent}, \op{multifile}, \op{public},
7200	    \op{thread_local}, \op{thread_initialization}, \op{volatile} \\
72011105 & xfy & \op{|} \\
72021100 & xfy & \op{;} \\
72031050 & xfy & \op{->}, \op{*->} \\
72041000 & xfy & \op{,} \\
7205990 & xfx & \op{:=} \\
7206900 & fy & \op{\+} \\
7207700 & xfx & \op{<}, \op{=}, \op{=..}, \op{=@=}, \op{\=@=},
7208	    \op{=:=}, \op{=<}, \op{==},
7209            \op{=\=}, \op{>}, \op{>=}, \op{@<}, \op{@=<}, \op{@>},
7210            \op{@>=}, \op{\=}, \op{\==}, \op{as}, \op{is},
7211	    \op{>:<}, \op{:<}
7212	    \\
7213600 & xfy & \op{:} \\
7214500 & yfx & \op{+}, \op{-}, \op{/\}, \op{\/}, \op{xor} \\
7215500 & fx & \op{?} \\
7216400 & yfx & \op{*}, \op{/}, \op{//}, \op{div}, \op{rdiv},
7217            \op{<<}, \op{>>}, \op{mod}, \op{rem} \\
7218200 & xfx & \op{**} \\
7219200 & xfy & \op{^} \\
7220200 & fy  & \op{+}, \op{-}, \op{\} \\
7221100 & yfx & \op{.} \\
72221   & fx  & \op{$} \\
7223\hline
7224\end{tabular}
7225\end{center}
7226    \caption{System operators}
7227    \label{tab:operators}
7228\end{table}
7229
7230    \predicate[ISO]{current_op}{3}{?Precedence, ?Type, ?:Name}
7231True if \arg{Name} is currently defined as an operator of type \arg{Type}
7232with precedence \arg{Precedence}. See also op/3.  Note that an
7233\jargon{unqualified} \arg{Name} does \textbf{not} resolve to the
7234calling context but, when compiling, to the compiler's target
7235module and otherwise to the \jargon{typein module}. See
7236\secref{operators} for details.
7237\end{description}
7238
7239
7240\section{Character Conversion}		\label{sec:charconv}
7241
7242Although I wouldn't really know why you would like to use these
7243features, they are provided for ISO compliance.
7244
7245\begin{description}
7246    \predicate[ISO]{char_conversion}{2}{+CharIn, +CharOut}
7247Define that term input (see read_term/3) maps each character read as
7248\arg{CharIn} to the character \arg{CharOut}. Character conversion is
7249only executed if the Prolog flag \prologflag{char_conversion} is set to
7250\const{true} and not inside quoted atoms or strings. The initial table
7251maps each character onto itself. See also current_char_conversion/2.
7252    \predicate[ISO]{current_char_conversion}{2}{?CharIn, ?CharOut}
7253Queries the current character conversion table.  See char_conversion/2
7254for details.
7255\end{description}
7256
7257
7258\section{Arithmetic}				\label{sec:arith}
7259
7260Arithmetic can be divided into some special purpose integer predicates
7261and a series of general predicates for integer, floating point and
7262rational arithmetic as appropriate. The general arithmetic predicates
7263all handle \arg{expressions}. An expression is either a simple number or
7264a \arg{function}. The arguments of a function are expressions. The
7265functions are described in \secref{functions}.
7266
7267
7268\subsection{Special purpose integer arithmetic}
7269\label{sec:logic-int-arith}
7270
7271The predicates in this section provide more logical operations between
7272integers. They are not covered by the ISO standard, although they are
7273`part of the community' and found as either library or built-in in many
7274other Prolog systems.
7275
7276\begin{description}
7277    \predicate{between}{3}{+Low, +High, ?Value}
7278\arg{Low} and \arg{High} are integers, $\arg{High} \geq \arg{Low}$. If
7279\arg{Value} is an integer, $\arg{Low} \leq \arg{Value} \leq \arg{High}$.
7280When \arg{Value} is a variable it is successively bound to all integers
7281between \arg{Low} and \arg{High}.  If \arg{High} is \const{inf} or
7282\const{infinite}%
7283	\footnote{We prefer \const{infinite}, but some other Prolog
7284		  systems already use \const{inf} for infinity; we
7285		  accept both for the time being.}
7286between/3 is true iff $\arg{Value} \geq \arg{Low}$, a feature that
7287is particularly interesting for generating integers from a certain
7288value.
7289
7290    \predicate{succ}{2}{?Int1, ?Int2}
7291True if $\arg{Int2} = \arg{Int1} + 1$ and $\arg{Int1} \geq 0$.
7292At least one of the arguments must be instantiated to a natural number.
7293This predicate raises the domain error \const{not_less_than_zero} if
7294called with a negative integer.  E.g.\ \term{succ}{X, 0} fails silently
7295and \term{succ}{X, -1} raises a domain error.%
7296	\footnote{The behaviour to deal with natural numbers only was
7297		  defined by Richard O'Keefe to support
7298		  the common count-down-to-zero in a natural way.  Up to
7299		  5.1.8, succ/2 also accepted negative integers.}
7300
7301    \predicate{plus}{3}{?Int1, ?Int2, ?Int3}
7302True if $\arg{Int3} = \arg{Int1} + \arg{Int2}$. At least two of the
7303three arguments must be instantiated to integers.
7304
7305    \predicate{divmod}{4}{+Dividend, +Divisor, -Quotient, -Remainder}
7306This predicate is a shorthand for computing both the \arg{Quotient} and
7307\arg{Remainder} of two integers in a single operation. This allows for
7308exploiting the fact that the low level implementation for computing the
7309quotient also produces the remainder. Timing confirms that this
7310predicate is almost twice as fast as performing the steps independently.
7311Semantically, divmod/4 is defined as below.
7312
7313\begin{code}
7314divmod(Dividend, Divisor, Quotient, Remainder) :-
7315	Quotient  is Dividend div Divisor,
7316	Remainder is Dividend mod Divisor.
7317\end{code}
7318
7319Note that this predicate is only available if SWI-Prolog is compiled
7320with unbounded integer support.  This is the case for all packaged
7321versions.
7322
7323    \predicate{nth_integer_root_and_remainder}{4}{+N, +I, -Root, -Remainder}
7324True when $\pow{Root}{N} + Remainder = I$. \arg{N} and \arg{I} must be
7325integers.\footnote{This predicate was suggested by Markus Triska.  The
7326final name and argument order is by Richard O'Keefe.  The decision to
7327include the remainder is by Jan Wielemaker.  Including the remainder
7328makes this predicate about twice as slow if \arg{Root} is not exact.}
7329\arg{N} must be one or more. If \arg{I} is negative and
7330\arg{N} is \jargon{odd}, \arg{Root} and \arg{Remainder} are negative,
7331i.e., the following holds for $\arg{I} < 0$:
7332
7333\begin{code}
7334%   I < 0,
7335%   N mod 2 =\= 0,
7336    nth_integer_root_and_remainder(
7337	N, I, Root, Remainder),
7338    IPos is -I,
7339    nth_integer_root_and_remainder(
7340	N, IPos, RootPos, RemainderPos),
7341    Root =:= -RootPos,
7342    Remainder =:= -RemainderPos.
7343\end{code}
7344\end{description}
7345
7346
7347\subsection{General purpose arithmetic}		\label{sec:arithpreds}
7348
7349The general arithmetic predicates are optionally compiled (see
7350set_prolog_flag/2 and the \cmdlineoption{-O} command line option).
7351Compiled arithmetic reduces global stack requirements and improves
7352performance. Unfortunately compiled arithmetic cannot be traced, which
7353is why it is optional.
7354
7355\begin{description}
7356    \infixop[ISO]{>}{+Expr1}{+Expr2}
7357True if expression \arg{Expr1} evaluates to a larger number than \arg{Expr2}.
7358
7359\infixop[ISO]{<}{+Expr1}{+Expr2}
7360True if expression \arg{Expr1} evaluates to a smaller number than \arg{Expr2}.
7361
7362\infixop[ISO]{=<}{+Expr1}{+Expr2}
7363True if expression \arg{Expr1} evaluates to a smaller or equal number
7364to \arg{Expr2}.
7365
7366\infixop[ISO]{>=}{+Expr1}{+Expr2}
7367True if expression \arg{Expr1} evaluates to a larger or equal number
7368to \arg{Expr2}.
7369
7370\infixop[ISO]{=\=}{+Expr1}{+Expr2}
7371True if expression \arg{Expr1} evaluates to a number non-equal to
7372\arg{Expr2}.
7373
7374\infixop[ISO]{=:=}{+Expr1}{+Expr2}
7375True if expression \arg{Expr1} evaluates to a number equal to \arg{
7376Expr2}.
7377
7378\infixop[ISO]{is}{-Number}{+Expr}
7379True when \arg{Number} is the value to which \arg{Expr} evaluates.
7380Typically, is/2 should be used with unbound left operand. If equality is
7381to be tested, \predref{=:=}{2} should be used. For example:
7382
7383\begin{center}\begin{tabular}{lp{2.5in}}
7384\exam{?- 1 is sin({pi}/2).}        & Fails!  sin({pi}/2) evaluates to the
7385				     float 1.0, which does not unify with
7386				     the integer 1. \\
7387\exam{?- 1 =:= sin({pi}/2).}       & Succeeds as expected.
7388\end{tabular}\end{center}
7389\end{description}
7390
7391
7392\subsubsection{Arithmetic types}	\label{sec:artypes}
7393
7394\index{integer,unbounded}\index{rational,number}\index{number,rational}%
7395SWI-Prolog defines the following numeric types:
7396
7397\begin{itemlist}
7398    \item [integer]
7399If SWI-Prolog is built using the \emph{GNU multiple precision arithmetic
7400library} \index{GMP}(GMP), integer arithmetic is \emph{unbounded}, which
7401means that the size of integers is limited by available memory only.
7402Without GMP, SWI-Prolog integers are 64-bits, regardless of the native
7403integer size of the platform. The type of integer support can be
7404detected using the Prolog flags \prologflag{bounded}, \prologflag{min_integer} and
7405\prologflag{max_integer}. As the use of GMP is default, most of the following
7406descriptions assume unbounded integer arithmetic.
7407
7408Internally, SWI-Prolog has three integer representations. Small integers
7409(defined by the Prolog flag \prologflag{max_tagged_integer}) are encoded
7410directly. Larger integers are represented as 64-bit values on the
7411global stack. Integers that do not fit in 64 bits are represented as
7412serialised GNU MPZ structures on the global stack.
7413
7414    \item [rational number]
7415Rational numbers ($Q$) are quotients of two integers ($N/M$). Rational
7416arithmetic is only provided if GMP is used (see above). Rational numbers
7417satisfy the type tests rational/1, number/1 and atomic/1 and may satisfy
7418the type test integer/1, i.e., integers are considered rational numbers.
7419Rational numbers are always kept in \emph{canonical representation},
7420which means $M$ is positive and $N$ and $M$ have no common divisors.
7421Rational numbers are introduced into the computation using the functions
7422\funcref{rational}{1}, \funcref{rationalize}{1} or the \funcref{rdiv}{2}
7423(rational division) function. If the Prolog flag
7424\prologflag{prefer_rationals} is \const{true} (default), division
7425(\funcref{/}{2}) and integer power (\funcref{^}{2}) also produce a
7426rational number.
7427
7428    \item [float]
7429Floating point numbers are represented using the C type \const{double}.
7430On most of today's platforms these are 64-bit IEEE floating point numbers.
7431\end{itemlist}
7432
7433Arithmetic functions that require integer arguments accept, in addition
7434to integers, rational numbers with (canonical) denominator `1'. If the
7435required argument is a float the argument is converted to float. Note
7436that conversion of integers to floating point numbers may raise an
7437overflow exception. In all other cases, arguments are converted to the
7438same type using the order below.
7439
7440\begin{quote}
7441integer $\rightarrow$ rational number $\rightarrow$ floating point number
7442\end{quote}
7443
7444
7445\subsubsection{Rational number examples}	\label{sec:rational}
7446
7447The use of rational numbers with unbounded integers allows for exact
7448integer or \jargon{fixed point} arithmetic under addition, subtraction,
7449multiplication, division and exponentiation (\funcref{^}{2}). Support
7450for rational numbers depends on the Prolog flag
7451\prologflag{prefer_rationals}. If this is \const{true} (default), the
7452number division function (\funcref{/}{2}) and exponentiation function
7453(\funcref{^}{2}) generate a rational number on integer and rational
7454arguments and read/1 and friends read \verb$[-+][0-9_ ]+/[0-9_ ]+$ into
7455a rational number. See also \secref{syntax-rational-numbers}. Here are
7456some examples.
7457
7458\begin{center}
7459\begin{tabular}{ll}
7460A is 2/6		     & A = 1/3 \\
7461A is 4/3 + 1		     & A = 7/3 \\
7462A is 4/3 + 1.5		     & A = 2.83333 \\
7463A is 4/3 + rationalize(1.5)  & A = 17/6 \\
7464\end{tabular}
7465\end{center}
7466
7467Note that floats cannot represent all decimal numbers exactly.  The
7468function \funcref{rational}{1} creates an \emph{exact} equivalent of the
7469float, while \funcref{rationalize}{1} creates a rational number that is
7470within the float rounding error from the original float. Please check
7471the documentation of these functions for details and examples.
7472
7473Rational numbers can be printed as decimal numbers with arbitrary
7474precision using the format/3 floating point conversion:
7475
7476\begin{code}
7477?- A is 4/3 + rational(1.5),
7478   format('~50f~n', [A]).
74792.83333333333333333333333333333333333333333333333333
7480
7481A = 17/6
7482\end{code}
7483
7484
7485\subsubsection{Rational numbers or floats}
7486\label{sec:rational-or-float}
7487
7488SWI-Prolog uses rational number arithmetic if the Prolog flag
7489\prologflag{prefer_rationals} is \const{true} and if this is defined for
7490a function on the given operants. This results in perfectly precise
7491answers. Unfortunately rational numbers can get really large and, if a
7492precise answer is not needed, a big waste of memory and CPU time. In
7493such cases one should use floating point arithmetic.  The Prolog flag
7494\prologflag{max_rational_size} provides a \jargon{tripwire} to detect
7495cases where rational numbers get big and react on these events.
7496
7497Floating point arithmetic can be forced by forcing a float into an
7498argument at any point, i.e., the result of a function with at least one
7499float is always float except for the float-to-integer rounding and
7500truncating functions such as \funcref{round}{1}, \funcref{rational}{1}
7501or \funcref{float_integer_part}{1}.
7502
7503Float arithmetic is typically forced by using a floating point constant
7504as initial value or operant. Alternatively, the \funcref{float}{1}
7505function forces conversion of the argument.
7506
7507\subsubsection{IEEE 754 floating point arithmetic}
7508\label{sec:ieee-float}
7509
7510The Prolog ISO standard defines that floating point arithmetic returns a
7511valid floating point number or raises an exception. IEEE floating point
7512arithmetic defines two modes: raising exceptions and propagating the
7513special float values \const{NaN}, \const{Inf}, \const{-Inf} and
7514\const{-0.0}. SWI-Prolog implements a part of the
7515\href{http://eclipseclp.org/Specs/core_update_float.html}{ECLiPSe
7516proposal} to support non-exception based processing of floating point
7517numbers. There are four flags that define handling the four exceptional
7518events in floating point arithmetic, providing the choice between
7519\const{error} and returning the IEEE special value. Note that these
7520flags \emph{only} apply for floating point arithmetic. For example
7521rational division by zero always raises an exception.
7522
7523\begin{center}\begin{tabular}{lcc}
7524\textbf{Flag} & \textbf{Default} & \textbf{Alternative} \\
7525\prologflag{float_overflow}   & error   & infinity \\
7526\prologflag{float_zero_div}   & error   & infinity \\
7527\prologflag{float_undefined}  & error   & nan \\
7528\prologflag{float_underflow}  & ignore  & error \\
7529\end{tabular}\end{center}
7530
7531The Prolog flag \prologflag{float_rounding} and the function
7532\funcref{roundtoward}{2} control the rounding mode for floating point
7533arithmetic. The default rounding is \const{to_nearest} and the following
7534alternatives are provided: \const{to_positive}, \const{to_negative} and
7535\const{to_zero}.
7536
7537\begin{description}
7538    \predicate[det]{float_class}{2}{+Float, -Class}
7539Wraps C99 fpclassify() to access the class of a floating point number.
7540Raises a type error if \arg{Float} is not a float.  Defined classes
7541are below.
7542
7543\begin{description}
7544    \termitem{nan}{}
7545\arg{Float} is ``Not a number''. See \funcref{nan}{0}. May be produced
7546if the Prolog flag \prologflag{float_undefined} is set to \const{nan}.
7547Although IEEE 754 allows NaN to carry a \jargon{payload} and have a
7548sign, SWI-Prolog has only a single NaN values.  Note that two NaN
7549\jargon{terms} compare equal in the standard order of terms
7550(\predref{==}{2}, etc.), they compare non-equal for arithmetic
7551(\predref{=:=}{2}, etc.).
7552
7553    \termitem{infinite}{}
7554\arg{Float} is positive or negative infinity.  See \funcref{inf}{0}.
7555May be produced if the Prolog flag \prologflag{float_overflow} or
7556the flag \prologflag{float_zero_div} is set to \const{infinity}.
7557    \termitem{zero}{}
7558\arg{Float} is zero (0.0 or -0.0)
7559    \termitem{subnormal}{}
7560\arg{Float} is too small to be represented in normalized format.
7561May \textbf{not} be produced if the Prolog flag
7562\prologflag{float_underflow} is set to \const{error}.
7563
7564    \termitem{normal}{}
7565\arg{Float} is a normal floating point number.
7566\end{description}
7567
7568    \predicate[det]{float_parts}{4}{+Float, -Mantissa, -Base, -Exponent}
7569True when \arg{Mantissa} is the normalized fraction of \arg{Float},
7570\arg{Base} is the \jargon{radix} and \arg{Exponent} is the exponent.
7571This uses the C function frexp().  If \arg{Float} is NaN or $\pm$Inf
7572\arg{Mantissa} has the same value and \arg{Exponent} is 0 (zero).
7573In the current implementation \arg{Base} is always 2.
7574The following relation is always true: $$Float =:= Mantissa \times
7575Base^{Exponent}$$
7576
7577    \predicate[det]{bounded_number}{3}{?Low, ?High, +Num}
7578True if \arg{Low} < \arg{Num} < \arg{High}. Raises a type error if \arg{Num}
7579is not a number. This predicate can be used both to check and generate bounds across the various numeric types. Note that a number cannot be bounded by itself and \const{NaN}, \const{Inf},
7580and \const{-Inf} are not bounded numbers.
7581
7582If \arg{Low} and/or \arg{High} are variables they will be unified with \jargon{tightest} values that still meet the bounds criteria. The generated bounds will be integers if \arg{Num} is an integer; otherwise they will be floats (also see \funcref{nexttoward}{2} for generating float bounds). Some examples:
7583\begin{code}
7584?- bounded_number(0,10,1).
7585true.
7586
7587?- bounded_number(0.0,1.0,1r2).
7588true.
7589
7590?- bounded_number(L,H,1.0).
7591L = 0.9999999999999999,
7592H = 1.0000000000000002.
7593
7594?- bounded_number(L,H,-1).
7595L = -2,
7596H = 0.
7597
7598?- bounded_number(0,1r2,1).
7599false.
7600
7601?- bounded_number(L,H,1.0Inf).
7602false.
7603\end{code}
7604\end{description}
7605
7606\subsubsection{Arithmetic Functions}	\label{sec:functions}
7607
7608Arithmetic functions are terms which are evaluated by the arithmetic
7609predicates described in \secref{arithpreds}. There are four types of
7610arguments to functions:
7611
7612\begin{center}\begin{tabular}{lp{4in}}
7613\arg{Expr}	& Arbitrary expression, returning either a floating
7614		  point value or an integer. \\
7615\arg{IntExpr}   & Arbitrary expression that must evaluate to
7616                  an integer. \\
7617\arg{RatExpr}   & Arbitrary expression that must evaluate to
7618                  a rational number. \\
7619\arg{FloatExpr} & Arbitrary expression that must evaluate to
7620                  a floating point.
7621\end{tabular}\end{center}
7622
7623For systems using bounded integer arithmetic (default is unbounded,
7624see \secref{artypes} for details), integer operations that would cause
7625overflow automatically convert to floating point arithmetic.
7626
7627SWI-Prolog provides many extensions to the set of floating point
7628functions defined by the ISO standard. The current policy is to provide
7629such functions on `as-needed' basis if the function is widely supported
7630elsewhere and notably if it is part of the
7631\href{http://www.open-std.org/jtc1/sc22/wg14/www/docs/n1124.pdf}{C99}
7632mathematical library.  In addition, we try to maintain compatibility
7633with \href{http://www.dcc.fc.up.pt/~vsc/Yap/}{YAP}.
7634
7635\begin{description}
7636    \prefixfunction[ISO]{-}{+Expr}
7637$\arg{Result} = -\arg{Expr}$
7638
7639    \prefixfunction[ISO]{+}{+Expr}
7640$\arg{Result} = \arg{Expr}$.  Note that if \chr{+} is followed by a number,
7641the parser discards the \chr{+}.  I.e.\ \verb$?- integer(+1)$ succeeds.
7642
7643    \infixfunction[ISO]{+}{+Expr1}{+Expr2}
7644$\arg{Result} = \arg{Expr1} + \arg{Expr2}$
7645
7646    \infixfunction[ISO]{-}{+Expr1}{+Expr2}
7647$\arg{Result} = \arg{Expr1} - \arg{Expr2}$
7648
7649    \infixfunction[ISO]{*}{+Expr1}{+Expr2}
7650$\arg{Result} = \arg{Expr1} \times \arg{Expr2}$
7651
7652    \infixfunction[ISO]{/}{+Expr1}{+Expr2}
7653$\arg{Result} = \frac{\arg{Expr1}}{\arg{Expr2}}$.
7654If the flag \prologflag{iso} is \const{true} or one of the arguments is
7655a float, both arguments are converted to float and the return value is a
7656float.  Otherwise the result type depends on the Prolog flag
7657\prologflag{prefer_rationals}. If \const{true}, the result is always a
7658rational number.  If \const{false} the result is rational if at least
7659one of the arguments is rational. Otherwise (both arguments are integer)
7660the result is integer if the division is exact and float otherwise.
7661See also \secref{rational}, \funcref{//}{2}, and \funcref{rdiv}{2}.
7662
7663The current default for the Prolog flag \prologflag{prefer_rationals} is
7664\const{false}. Future version may switch this to \const{true}, providing
7665precise results when possible. The pitfall is that in general rational
7666arithmetic is slower and can become very slow and produce huge numbers
7667that require a lot of (global stack) memory. Code for which the exact
7668results provided by rational numbers is not needed should force float
7669results by making one of the operants float, for example by dividing by
7670\exam{10.0} rather than \exam{10} or by using \funcref{float}{1}. Note
7671that when one of the arguments is forced to a float the division is a
7672float operation while if the result is forced to the float the division
7673is done using rational arithmetic.
7674
7675    \infixfunction[ISO]{mod}{+IntExpr1}{+IntExpr2}
7676Modulo, defined as \mbox{\arg{Result} = \arg{IntExpr1} - (\arg{IntExpr1}
7677div \arg{IntExpr2}) $\times$ \arg{IntExpr2}}, where \const{div} is
7678\jargon{floored} division.
7679
7680    \infixfunction[ISO]{rem}{+IntExpr1}{+IntExpr2}
7681Remainder of integer division.  Behaves as if defined by
7682\mbox{\arg{Result} is \arg{IntExpr1} -
7683(\arg{IntExpr1} // \arg{IntExpr2}) $\times$ \arg{IntExpr2}}
7684
7685    \infixfunction[ISO]{//}{+IntExpr1}{+IntExpr2}
7686Integer division, defined as \mbox{\arg{Result} is
7687$rnd_I$(\arg{Expr1}/\arg{Expr2})}. The function $rnd_I$ is the default
7688rounding used by the C compiler and available through the Prolog flag
7689\prologflag{integer_rounding_function}. In the C99 standard, C-rounding
7690is defined as \const{towards_zero}.\footnote{Future versions might
7691guarantee rounding towards zero.}
7692
7693    \function[ISO]{div}{2}{+IntExpr1, +IntExpr2}
7694Integer division, defined as \mbox{\arg{Result} is
7695(\arg{IntExpr1} - \arg{IntExpr1} $mod$ \arg{IntExpr2}) // \arg{IntExpr2}}.
7696In other words, this is integer division that rounds towards -infinity.
7697This function guarantees behaviour that is consistent with
7698\funcref{mod}{2}, i.e., the following holds for every pair of integers
7699$X,Y$ where \verb$Y =\= 0$.
7700
7701\begin{code}
7702	Q is div(X, Y),
7703	M is mod(X, Y),
7704	X =:= Y*Q+M.
7705\end{code}
7706
7707    \infixfunction{rdiv}{+RatExpr}{+RatExpr}
7708Rational number division. This function is only available if
7709SWI-Prolog has been compiled with rational number support. See
7710\secref{rational} for details.
7711
7712    \infixfunction{gcd}{+IntExpr1}{+IntExpr2}
7713Result is the greatest common divisor of \arg{IntExpr1} and
7714\arg{IntExpr2}. The GCD is always a positive integer. If either
7715expression evaluates to zero the GCD is the result of the other
7716expression.
7717
7718    \infixfunction{lcm}{+IntExpr1}{+IntExpr2}
7719Result is the least common multiple of \arg{IntExpr1},
7720\arg{IntExpr2}.\bug{If the system is compiled for bounded integers only
7721\funcref{lcm}{2} produces an integer overflow if the product of the two
7722expressions does not fit in a 64 bit signed integer. The default build
7723with unbounded integer support has no such limit.} If either expression
7724evaluates to zero the LCM is zero.
7725
7726    \function[ISO]{abs}{1}{+Expr}
7727Evaluate \arg{Expr} and return the absolute value of it.
7728
7729    \function[ISO]{sign}{1}{+Expr}
7730Evaluate to -1 if $\arg{Expr} < 0$, 1 if $\arg{Expr} > 0$ and 0 if
7731$\arg{Expr} = 0$.  If \arg{Expr} evaluates to a float, the return value
7732is a float (e.g., -1.0, 0.0 or 1.0). In particular, note that sign(-0.0)
7733evaluates to 0.0.  See also \funcref{copysign}{2}.
7734
7735    \function[ISO]{copysign}{2}{+Expr1, +Expr2}
7736Evaluate to \arg{X}, where the absolute value of \arg{X} equals the
7737absolute value of \arg{Expr1} and the sign of \arg{X} matches the sign
7738of \arg{Expr2}. This function is based on copysign() from C99, which
7739works on double precision floats and deals with handling the sign of
7740special floating point values such as -0.0. Our implementation follows
7741C99 if both arguments are floats.  Otherwise, \funcref{copysign}{2}
7742evaluates to \arg{Expr1} if the sign of both expressions matches or
7743-\arg{Expr1} if the signs do not match.  Here, we use the extended
7744notion of signs for floating point numbers, where the sign of -0.0
7745and other special floats is negative.
7746
7747    \function{nexttoward}{2}{+Expr1, +Expr2}
7748Evaluates to floating point number following \arg{Expr1} in the
7749direction of \arg{Expr2}. This relates to \funcref{epsilon}{0} in the
7750following way:
7751
7752\begin{code}
7753?- epsilon =:= nexttoward(1,2)-1.
7754true.
7755\end{code}
7756
7757    \function{roundtoward}{2}{+Expr1, +RoundMode}
7758Evaluate \arg{Expr1} using the floating point rounding mode
7759\arg{RoundMode}. This provides a local alternative to the Prolog flag
7760\prologflag{float_rounding}. This function can be nested. The supported
7761values for \arg{RoundMode} are the same as the flag values:
7762\const{to_nearest}, \const{to_positive}, \const{to_negative} or
7763\const{to_zero}.
7764
7765    \function[ISO]{max}{2}{+Expr1, +Expr2}
7766Evaluate to the larger of \arg{Expr1} and \arg{Expr2}.  Both
7767arguments are compared after converting to the same type, but the
7768return value is in the original type.  For example, max(2.5, 3) compares
7769the two values after converting to float, but returns the integer 3.
7770
7771    \function[ISO]{min}{2}{+Expr1, +Expr2}
7772Evaluate to the smaller of \arg{Expr1} and \arg{Expr2}. See
7773\funcref{max}{2} for a description of type handling.
7774
7775    \function{.}{2}{+Int, []}
7776A list of one element evaluates to the element. This implies \exam{"a"}
7777evaluates to the character code of the letter `a' (97) using the
7778traditional mapping of double quoted string to a list of character
7779codes. Arithmetic evaluation also translates a string object (see
7780\secref{strings}) of one character length into the character code for
7781that character. This implies that expression \exam{"a"} also works of
7782the Prolog flag \prologflag{double_quotes} is set to \const{string}. The
7783recommended way to specify the character code of the letter `a' is
7784\exam{0'a}.
7785
7786    \function{random}{1}{+IntExpr}
7787Evaluate to a random integer \arg{i} for which $0 \leq i <
7788\arg{IntExpr}$. The system has two implementations. If it is compiled
7789with support for unbounded arithmetic (default) it uses the GMP library
7790random functions. In this case, each thread keeps its own random state.
7791The default algorithm is the \jargon{Mersenne Twister} algorithm. The
7792seed is set when the first random number in a thread is generated. If
7793available, it is set from \file{/dev/random}.\footnote{On Windows the
7794state is initialised from CryptGenRandom().} Otherwise it is set from
7795the system clock. If unbounded arithmetic is not supported, random
7796numbers are shared between threads and the seed is initialised from the
7797clock when SWI-Prolog was started. The predicate set_random/1 can be
7798used to control the random number generator.
7799
7800\textbf{Warning!} Although properly seeded (if supported on the OS), the
7801Mersenne Twister algorithm does \emph{not} produce cryptographically
7802secure random numbers. To generate cryptographically secure random
7803numbers, use crypto_n_random_bytes/2 from library \pllib{crypto}
7804provided by the \const{ssl} package.
7805
7806    \function{random_float}{0}{}
7807Evaluate to a random float $I$ for which $0.0 < i < 1.0$. This function
7808shares the random state with \funcref{random}{1}. All remarks with the
7809function \funcref{random}{1} also apply for \funcref{random_float}{0}.
7810Note that both sides of the domain are \jargon{open}. This avoids
7811evaluation errors on, e.g., \funcref{log}{1} or \funcref{/}{2} while no
7812practical application can expect 0.0.\footnote{Richard O'Keefe said:
7813``If you \emph{are} generating IEEE doubles with the claimed
7814uniformity, then 0 has a 1 in $2^{53} = 1 in 9,007,199,254,740,992$
7815chance of turning up. No program that expects [0.0,1.0) is going to be
7816surprised when 0.0 fails to turn up in a few millions of millions of
7817trials, now is it? But a program that expects (0.0,1.0) could be
7818devastated if 0.0 did turn up.''}
7819
7820    \function[ISO]{round}{1}{+Expr}
7821Evaluate \arg{Expr} and round the result to the nearest integer.
7822According to ISO, \funcref{round}{1} is defined as
7823\term{floor}{Expr+1/2}, i.e., rounding \emph{down}.  This is an
7824unconventional choice under which the relation
7825\verb$round(Expr) == -round(-Expr)$ does not hold.  SWI-Prolog
7826rounds \emph{outward}, e.g., \exam{round(1.5) =:= 2} and
7827\exam{round(-1.5) =:= -2}.
7828
7829    \function{integer}{1}{+Expr}
7830Same as \funcref{round}{1} (backward compatibility).
7831
7832    \function[ISO]{float}{1}{+Expr}
7833Translate the result to a floating point number.  Normally, Prolog will
7834use integers whenever possible.  When used around the 2nd argument of
7835is/2, the result will be returned as a floating point number.  In other
7836contexts, the operation has no effect.
7837
7838    \function{rational}{1}{+Expr}
7839Convert the \arg{Expr} to a rational number or integer.  The function
7840returns the input on integers and rational numbers.  For floating point
7841numbers, the returned rational number \emph{exactly} represents the
7842float.  As floats cannot exactly represent all decimal numbers the
7843results may be surprising.  In the examples below, doubles can
7844represent 0.25 and the result is as expected, in contrast to the
7845result of \term{rational}{0.1}. The function \funcref{rationalize}{1}
7846remedies this. See \secref{rational} for more information on rational
7847number support.
7848
7849\begin{code}
7850?- A is rational(0.25).
7851
7852A is 1 rdiv 4
7853?- A is rational(0.1).
7854A = 3602879701896397 rdiv 36028797018963968
7855\end{code}
7856
7857For every \jargon{normal} float \arg{X} the relation
7858\mbox{\arg{X} \const{=:=} rational(\arg{X})} holds.
7859
7860This function raises an \term{evaluation_error}{undefined} if \arg{Expr}
7861is NaN and \term{evaluation_error}{rational_overflow} if \arg{Expr} is
7862Inf.
7863
7864    \function{rationalize}{1}{+Expr}
7865Convert the \arg{Expr} to a rational number or integer. The function is
7866similar to \funcref{rational}{1}, but the result is only accurate within
7867the rounding error of floating point numbers, generally producing a much
7868smaller denominator.\footnote{The names \funcref{rational}{1} and
7869\funcref{rationalize}{1} as well as their semantics are inspired by
7870Common Lisp.}\footnote{The implementation of rationalize as well as
7871converting a rational number into a float is copied from ECLiPSe and
7872covered by the \textit{Cisco-style Mozilla Public License Version 1.1}.}
7873
7874\begin{code}
7875?- A is rationalize(0.25).
7876
7877A = 1 rdiv 4
7878?- A is rationalize(0.1).
7879
7880A = 1 rdiv 10
7881\end{code}
7882
7883For every \jargon{normal} float \arg{X} the relation
7884\mbox{\arg{X} \const{=:=} rationalize(\arg{X})} holds.
7885
7886This function raises the same exceptions as \funcref{rational}{1} on
7887non-normal floating point numbers.
7888
7889    \function{numerator}{1}{+RationalExpr}
7890If \arg{RationalExpr} evaluates to a rational number or integer,
7891evaluate to the top/left value. Evaluates to itself if
7892\arg{RationalExpr} evaluates to an integer. See also
7893\funcref{denominator}{1}. The following is true for any rational
7894\arg{X}.
7895
7896\begin{code}
7897X =:= numerator(X)/denominator(X).
7898\end{code}
7899
7900    \function{denominator}{1}{+RationalExpr}
7901If \arg{RationalExpr} evaluates to a rational number or integer,
7902evaluate to the bottom/right value. Evaluates to 1 (one) if
7903\arg{RationalExpr} evaluates to an integer. See also
7904\funcref{numerator}{1}. The following is true for any rational \arg{X}.
7905
7906\begin{code}
7907X =:= numerator(X)/denominator(X).
7908\end{code}
7909
7910    \function[ISO]{float_fractional_part}{1}{+Expr}
7911Fractional part of a floating point number.  Negative if \arg{Expr} is
7912negative, rational if \arg{Expr} is rational and 0 if \arg{Expr} is
7913integer.  The following relation is always true:
7914$X is float_fractional_part(X) + float_integer_part(X)$.
7915
7916    \function[ISO]{float_integer_part}{1}{+Expr}
7917Integer part of floating point number. Negative if \arg{Expr} is
7918negative, \arg{Expr} if \arg{Expr} is integer.
7919
7920    \function[ISO]{truncate}{1}{+Expr}
7921Truncate \arg{Expr} to an integer.  If $\arg{Expr} \geq 0$ this is the
7922same as \term{floor}{Expr}.  For $\arg{Expr} < 0$ this is the same as
7923\term{ceil}{Expr}.  That is, \funcref{truncate}{1} rounds towards zero.
7924
7925    \function[ISO]{floor}{1}{+Expr}
7926Evaluate \arg{Expr} and return the largest integer smaller or equal
7927to the result of the evaluation.
7928
7929    \function[ISO]{ceiling}{1}{+Expr}
7930Evaluate \arg{Expr} and return the smallest integer larger or equal
7931to the result of the evaluation.
7932
7933    \function{ceil}{1}{+Expr}
7934Same as \funcref{ceiling}{1} (backward compatibility).
7935
7936    \infixfunction[ISO]{>>}{+IntExpr1}{+IntExpr2}
7937Bitwise shift \arg{IntExpr1} by \arg{IntExpr2} bits to the right.  The
7938operation performs \jargon{arithmetic shift}, which implies that the
7939inserted most significant bits are copies of the original most
7940significant bits.
7941
7942    \infixfunction[ISO]{<<}{+IntExpr1}{+IntExpr2}
7943Bitwise shift \arg{IntExpr1} by \arg{IntExpr2} bits to the left.
7944
7945    \infixfunction[ISO]{\/}{+IntExpr1}{+IntExpr2}
7946Bitwise `or' \arg{IntExpr1} and \arg{IntExpr2}.
7947
7948    \infixfunction[ISO]{/\}{+IntExpr1}{+IntExpr2}
7949Bitwise `and' \arg{IntExpr1} and \arg{IntExpr2}.
7950
7951    \infixfunction[ISO]{xor}{+IntExpr1}{+IntExpr2}
7952Bitwise `exclusive or' \arg{IntExpr1} and \arg{IntExpr2}.
7953
7954    \prefixfunction[ISO]{\}{+IntExpr}
7955Bitwise negation.  The returned value is the one's complement of
7956\arg{IntExpr}.
7957
7958    \function[ISO]{sqrt}{1}{+Expr}
7959$\arg{Result} = \sqrt{\arg{Expr}}$.
7960    \function[ISO]{sin}{1}{+Expr}
7961$\arg{Result} = \sin{\arg{Expr}}$. \arg{Expr} is the angle in radians.
7962    \function[ISO]{cos}{1}{+Expr}
7963$\arg{Result} = \cos{\arg{Expr}}$. \arg{Expr} is the angle in radians.
7964    \function[ISO]{tan}{1}{+Expr}
7965$\arg{Result} = \tan{\arg{Expr}}$. \arg{Expr} is the angle in radians.
7966    \function[ISO]{asin}{1}{+Expr}
7967$\arg{Result} = \arcsin{\arg{Expr}}$. \arg{Result} is the angle in radians.
7968    \function[ISO]{acos}{1}{+Expr}
7969$\arg{Result} = \arccos{\arg{Expr}}$. \arg{Result} is the angle in radians.
7970    \function[ISO]{atan}{1}{+Expr}
7971$\arg{Result} = \arctan{\arg{Expr}}$. \arg{Result} is the angle in radians.
7972    \function[ISO]{atan2}{2}{+YExpr, +XExpr}
7973$\arg{Result} = \arctan{\frac{\arg{YExpr}}{\arg{XExpr}}}$. \arg{Result} is the
7974angle in radians.  The return value is in the range $[-\pi\ldots\pi]$.
7975Used to convert between rectangular and polar coordinate system.
7976
7977Note that the ISO Prolog standard demands \term{atan2}{0.0,0.0} to raise
7978an evaluation error, whereas the C99 and POSIX standards demand this to
7979evaluate to 0.0.  SWI-Prolog follows C99 and POSIX.
7980    \function{atan}{2}{+YExpr, +XExpr}
7981Same as \funcref{atan2}{2} (backward compatibility).
7982
7983    \function{sinh}{1}{+Expr}
7984$\arg{Result} = \sinh{\arg{Expr}}$. The hyperbolic sine of $X$ is
7985defined as $\frac{\pow{e}{X} - \pow{e}{-X}}{2}$.
7986    \function{cosh}{1}{+Expr}
7987$\arg{Result} = \cosh{\arg{Expr}}$. The hyperbolic cosine of $X$ is
7988defined as $\frac{\pow{e}{X} + \pow{e}{-X}}{2}$.
7989    \function{tanh}{1}{+Expr}
7990$\arg{Result} = \tanh{\arg{Expr}}$. The hyperbolic tangent of $X$ is
7991defined as $\frac{\sinh{X}}{\cosh{X}}$.
7992
7993    \function{asinh}{1}{+Expr}
7994$\arg{Result} = arcsinh(\arg{Expr})$ (inverse hyperbolic sine).
7995    \function{acosh}{1}{+Expr}
7996$\arg{Result} = arccosh(\arg{Expr})$ (inverse hyperbolic cosine).
7997    \function{atanh}{1}{+Expr}
7998$\arg{Result} = arctanh(\arg{Expr})$. (inverse hyperbolic tangent).
7999
8000    \function[ISO]{log}{1}{+Expr}
8001Natural logarithm.  $\arg{Result} = \ln{\arg{Expr}}$
8002    \function{log10}{1}{+Expr}
8003Base-10 logarithm.  $\arg{Result} = \lg{\arg{Expr}}$
8004    \function[ISO]{exp}{1}{+Expr}
8005$\arg{Result} = \pow{e}{\arg{Expr}}$
8006
8007    \infixfunction[ISO]{**}{+Expr1}{+Expr2}
8008$\arg{Result} = \pow{\arg{Expr1}}{\arg{Expr2}}$. The result is a float,
8009unless SWI-Prolog is compiled with unbounded integer support and the
8010inputs are integers and produce an integer result. The integer
8011expressions $\pow{0}{I}$, $\pow{1}{I}$ and $\pow{-1}{I}$ are guaranteed
8012to work for any integer $I$. Other integer base values generate a
8013\const{resource} error if the result does not fit in memory.
8014
8015The ISO standard demands a float result for all inputs and introduces
8016\funcref{^}{2} for integer exponentiation. The function
8017\funcref{float}{1} can be used on one or both arguments to force a
8018floating point result. Note that casting the \emph{input} result in a
8019floating point computation, while casting the \emph{output} performs
8020integer exponentiation followed by a conversion to float.
8021
8022    \infixfunction[ISO]{^}{+Expr1}{+Expr2}
8023
8024In SWI-Prolog, \funcref{^}{2} is equivalent to \funcref{**}{2}. The ISO
8025version is similar, except that it produces a evaluation error if both
8026\arg{Expr1} and \arg{Expr2} are integers and the result is not an
8027integer. The table below illustrates the behaviour of the exponentiation
8028functions in ISO and SWI. Note that if the exponent is negative the
8029behavior of \mbox{\arg{Int}\chr{^}\arg{Int}} depends on the flag
8030\prologflag{prefer_rationals}, producing either a rational number or a
8031floating point number.
8032
8033\begin{center}
8034\begin{tabular}{|ll|l|l|l|}
8035\hline
8036\arg{Expr1}   & \arg{Expr2}  & Function &  SWI          & ISO \\
8037\hline
8038Int	      & Int	     & \funcref{**}{2} &  Int or Rational & Float \\
8039Int	      & Float	     & \funcref{**}{2} &  Float           & Float \\
8040Rational      & Int	     & \funcref{**}{2} &  Rational        & - \\
8041Float	      & Int	     & \funcref{**}{2} &  Float           & Float \\
8042Float         & Float        & \funcref{**}{2} &  Float           & Float \\
8043\hline
8044Int	      & Int	     & \funcref{^}{2}  &  Int or Rational & Int or error \\
8045Int	      & Float	     & \funcref{^}{2}  &  Float           & Float \\
8046Rational      & Int          & \funcref{^}{2}  &  Rational        & - \\
8047Float	      & Int	     & \funcref{^}{2}  &  Float           & Float \\
8048Float         & Float        & \funcref{^}{2}  &  Float           & Float \\
8049\hline
8050\end{tabular}
8051\end{center}
8052
8053    \function{powm}{3}{+IntExprBase, +IntExprExp, +IntExprMod}
8054$\arg{Result} = (\pow{\arg{IntExprBase}}{\arg{IntExprExp}})
8055 \mbox{ modulo } \arg{IntExprMod}$.
8056Only available when compiled with unbounded integer support. This
8057formula is required for Diffie-Hellman key-exchange, a technique where
8058two parties can establish a secret key over a public network.
8059\arg{IntExprBase} and \arg{IntExprExp} must be non-negative ($>=0$),
8060\arg{IntExprMod} must be positive ($>0$).\footnote{The underlying GMP
8061mpz_powm() function allows negative values under some conditions.  As
8062the conditions are expensive to pre-compute, error handling from GMP is
8063non-trivial and negative values are not needed for Diffie-Hellman
8064key-exchange we do not support these.}
8065
8066    \function{lgamma}{1}{+Expr}
8067Return the natural logarithm of the absolute value of the Gamma
8068function.\footnote{Some interfaces also provide the sign of the Gamma
8069function. We cannot do that in an arithmetic function. Future versions
8070may provide a \emph{predicate} \nopredref{lgamma}{3} that returns both
8071the value and the sign.}
8072
8073    \function{erf}{1}{+Expr}
8074\href{https://en.wikipedia.org/wiki/Error_function}{Wikipedia}: ``In
8075mathematics, the error function (also called the Gauss error function)
8076is a special function (non-elementary) of sigmoid shape which occurs in
8077probability, statistics and partial differential equations.''
8078
8079    \function{erfc}{1}{+Expr}
8080\href{https://en.wikipedia.org/wiki/Error_function}{Wikipedia}: ``The
8081complementary error function.''
8082
8083    \function[ISO]{pi}{0}{}
8084Evaluate to the mathematical constant $\pi$ (3.14159\ldots).
8085
8086    \function{e}{0}{}
8087Evaluate to the mathematical constant $e$ (2.71828\ldots).
8088
8089    \function{epsilon}{0}{}
8090Evaluate to the difference between the float 1.0 and the first larger
8091floating point number. Deprecated. The function \funcref{nexttoward}{2}
8092provides a better alternative.
8093
8094    \function{inf}{0}{}
8095Evaluate to positive infinity. See \secref{floatsyntax} and
8096\secref{ieee-float}. This value can be negated using \funcref{-}{1}.
8097
8098    \function{nan}{0}{}
8099Evaluate to \emph{Not a Number}. See \secref{floatsyntax} and
8100\secref{ieee-float}.
8101
8102    \function{cputime}{0}{}
8103Evaluate to a floating point number expressing the {\sc cpu} time (in seconds)
8104used by Prolog up till now. See also statistics/2 and time/1.
8105
8106    \function{eval}{1}{+Expr}
8107Evaluate \arg{Expr}. Although ISO standard dictates that `$A$=1+2, $B$ is
8108$A$' works and unifies $B$ to 3, it is widely felt that source level
8109variables in arithmetic expressions should have been limited to numbers.
8110In this view the eval function can be used to evaluate arbitrary
8111expressions.\footnote{The \funcref{eval}{1} function was first
8112introduced by ECLiPSe and is under consideration for YAP.}
8113\end{description}
8114
8115
8116\paragraph{Bitvector functions}
8117
8118The functions below are not covered by the standard. The
8119\funcref{msb}{1} function also appears in hProlog and SICStus Prolog.
8120The \funcref{getbit}{2} function also appears in ECLiPSe, which also
8121provides \term{setbit}{Vector,Index} and \term{clrbit}{Vector,Index}.
8122The others are SWI-Prolog extensions that improve handling of
8123---unbounded--- integers as bit-vectors.
8124
8125\begin{description}
8126    \function{msb}{1}{+IntExpr}
8127Return the largest integer $N$ such that \verb$(IntExpr >> N) /\ 1 =:= 1$.
8128This is the (zero-origin) index of the most significant 1 bit in the
8129value of \arg{IntExpr}, which must evaluate to a positive integer.
8130Errors for 0, negative integers, and non-integers.
8131
8132    \function{lsb}{1}{+IntExpr}
8133Return the smallest integer $N$ such that \verb$(IntExpr >> N) /\ 1 =:= 1$.
8134This is the (zero-origin) index of the least significant 1 bit in the
8135value of \arg{IntExpr}, which must evaluate to a positive integer. Errors for
81360, negative integers, and non-integers.
8137
8138    \function{popcount}{1}{+IntExpr}
8139Return the number of 1s in the binary representation of the
8140non-negative integer \arg{IntExpr}.
8141
8142    \function{getbit}{2}{+IntExprV, +IntExprI}
8143Evaluates to the bit value (0 or 1) of the \arg{IntExprI}-th bit of
8144\arg{IntExprV}. Both arguments must evaluate to non-negative integers.
8145The result is equivalent to \verb$(IntExprV >> IntExprI)/\1$, but more
8146efficient because materialization of the shifted value is avoided.
8147Future versions will optimise \verb$(IntExprV >> IntExprI)/\1$ to a call
8148to \funcref{getbit}{2}, providing both portability and
8149performance.\footnote{This issue was fiercely debated at the ISO
8150standard mailinglist. The name \textit{getbit} was selected for
8151compatibility with ECLiPSe, the only system providing this support.
8152Richard O'Keefe disliked the name and argued that efficient handling of
8153the above implementation is the best choice for this functionality.}
8154\end{description}
8155
8156
8157\section{Misc arithmetic support predicates}   \label{sec:miscarith}
8158
8159\begin{description}
8160    \predicate{set_random}{1}{+Option}
8161Controls the random number generator accessible through the
8162\emph{functions} \funcref{random}{1} and \funcref{random_float}{0}. Note
8163that the library \pllib{random} provides an alternative API to the same
8164random primitives.
8165
8166    \begin{description}
8167	\termitem{seed}{+Seed}
8168Set the seed of the random generator for this thread.  \arg{Seed} is
8169an integer or the atom \const{random}.  If \const{random}, repeat the
8170initialization procedure described with the function
8171\funcref{random}{1}. Here is an example:
8172
8173\begin{code}
8174?- set_random(seed(111)), A is random(6).
8175A = 5.
8176?- set_random(seed(111)), A is random(6).
8177A = 5.
8178\end{code}
8179	\termitem{state}{+State}
8180Set the generator to a state fetched using the state
8181property of random_property/1.  Using other values may lead to undefined
8182behaviour.\footnote{The limitations of the underlying (GMP) library are
8183unknown, which makes it impossible to validate the \arg{State}.}
8184    \end{description}
8185
8186    \predicate{random_property}{1}{?Option}
8187True when \arg{Option} is a current property of the random generator.
8188Currently, this predicate provides access to the state.  This predicate
8189is not present on systems where the state is inaccessible.
8190
8191    \begin{description}
8192	\termitem{state}{-State}
8193Describes the current state of the random generator. State is a normal
8194Prolog term that can be asserted or written to a file. Applications
8195should make no other assumptions about its representation. The only
8196meaningful operation is to use as argument to set_random/1 using the
8197\term{state}{State} option.\bug{GMP provides no portable mechanism to
8198fetch and restore the state.  The current implementation works, but the
8199state depends on the platform.  I.e., it is generally not possible to
8200reuse the state with another version of GMP or on a CPU with different
8201datasizes or endian-ness.}
8202    \end{description}
8203
8204    \predicate{current_arithmetic_function}{1}{?Head}
8205True when \arg{Head} is an evaluable function.  For example:
8206
8207\begin{code}
8208?- current_arithmetic_function(sin(_)).
8209true.
8210\end{code}
8211\end{description}
8212
8213
8214\section{Built-in list operations}		\label{sec:builtinlist}
8215
8216Most list operations are defined in the library \pllib{lists} described
8217in \secref{lists}. Some that are implemented with more low-level
8218primitives are built-in and described here.
8219
8220
8221\begin{description}
8222    \predicate{is_list}{1}{+Term}
8223True if \arg{Term} is bound to the empty list (\exam{[]}) or a term with
8224functor `\const{'[|]'}'\footnote{The traditional list functor is the dot
8225(\const{'.'}). This is still the case of the command line option
8226\cmdlineoption{--traditional} is given. See also \secref{ext-lists}.}
8227and arity~2 and the second argument is a list.%
8228	\footnote{In versions before 5.0.1, is_list/1 just checked for
8229		  \const{[]} or \exam{[_|_]} and
8230		  \nopredref{proper_list}{1} had the role of the current
8231		  is_list/1. The current definition conforms to the
8232		  de facto standard. Assuming proper coding standards,
8233		  there should only be very few cases where a
8234		  quick-and-dirty is_list/1 is a good choice. Richard
8235		  O'Keefe pointed at this issue.}
8236This predicate acts as if defined by the definition below on
8237\jargon{acyclic} terms. The implementation \emph{fails} safely if
8238\arg{Term} represents a cyclic list.
8239
8240\begin{code}
8241is_list(X) :-
8242	var(X), !,
8243	fail.
8244is_list([]).
8245is_list([_|T]) :-
8246	is_list(T).
8247\end{code}
8248
8249    \predicate[semidet]{memberchk}{2}{?Elem, +List}
8250True when \arg{Elem} is an element of \arg{List}. This `chk' variant of
8251member/2 is semi deterministic and typically used to test membership of
8252a list. Raises a \const{type} error if scanning \arg{List} encounters a
8253non-list. Note that memberchk/2 does \emph{not} perform a full list
8254typecheck. For example, \exam{memberchk(a, [a|b])} succeeds without
8255error. If \arg{List} is cyclic and \arg{Elem} is not a member of
8256\arg{List}, memberchk/2 eventually raises a \const{type}
8257error.\footnote{\textit{Eventually} here means it will scan as many
8258elements as the longest list that may exist given the current stack
8259usage before raising the exception.}
8260
8261    \predicate[ISO]{length}{2}{?List, ?Int}
8262True if \arg{Int} represents the number of elements in \arg{List}.
8263This predicate is a true relation and can be used to find the length of
8264a list or produce a list (holding variables) of length \arg{Int}.  The
8265predicate is non-deterministic, producing lists of increasing length if
8266\arg{List} is a \jargon{partial list} and \arg{Int} is unbound. It
8267raises errors if
8268
8269    \begin{itemize}
8270    \item \arg{Int} is bound to a non-integer.
8271    \item \arg{Int} is a negative integer.
8272    \item \arg{List} is neither a list nor a partial list.  This
8273	  error condition includes cyclic lists.\footnote{ISO
8274	  demands failure here. We think an error is more appropriate.}
8275    \end{itemize}
8276
8277This predicate fails if the tail of \arg{List} is equivalent to
8278\arg{Int} (e.g., \exam{length(L,L)}).\footnote{This is logically
8279correct. An exception would be more appropriate, but to our best
8280knowledge, current practice in Prolog does not describe a suitable
8281candidate exception term.}
8282
8283    \predicate[ISO]{sort}{2}{+List, -Sorted}
8284True if \arg{Sorted} can be unified with a list holding the
8285elements of \arg{List}, sorted to the standard order of terms (see
8286\secref{compare}).  Duplicates are removed.  The implementation is
8287in C, using \jargon{natural merge sort}.%
8288	\footnote{Contributed by Richard O'Keefe.}
8289The sort/2 predicate can sort a cyclic list, returning a non-cyclic
8290version with the same elements.
8291
8292Note that \arg{List} may contain non-ground terms. If \arg{Sorted} is
8293unbound at call-time, for each consecutive pair of elements in
8294\arg{Sorted}, the relation \verb$E1 @< E2$ will hold. However, unifying
8295a variable in \arg{Sorted} may cause this relation to become invalid,
8296\emph{even} unifying a variable in \arg{Sorted} with another (older)
8297variable.  See also \secref{standardorder}.
8298
8299    \predicate{sort}{4}{+Key, +Order, +List, -Sorted}
8300True when \arg{Sorted} can be unified with a list holding the element of
8301\arg{List}. \arg{Key} determines which part of each element in
8302\arg{List} is used for comparing two term and \arg{Order} describes the
8303relation between each set of consecutive elements in
8304\arg{Sorted}.\footnote{The definition of this predicate was established
8305after discussion with Joachim Schimpf from the ECLiPSe team. ECLiPSe
8306currently only accepts \const{<}, \const{=<}, \const{>} and \const{>=}
8307for the \arg{Order} argument but this is likely to change. SWI-Prolog
8308extends this predicate to deal with dicts.}
8309
8310If \arg{Key} is the integer zero (0), the entire term is used to compare
8311two elements. Using \arg{Key}=0 can be used to sort arbitrary Prolog
8312terms. Other values for \arg{Key} can only be used with compound terms
8313or dicts (see \secref{bidicts}). An integer key extracts the
8314\arg{Key}-th argument from a compound term. An integer or atom key
8315extracts the value from a dict that is associated with the given key. A
8316type_error is raised if the list element is of the wrong type and an
8317existence_error is raised if the compound has not enough argument or the
8318dict does not contain the requested key.
8319
8320Deeper nested elements of structures can be selected by using a list
8321of keys for the \arg{Key} argument.
8322
8323The \arg{Order} argument is described in the table below:\footnote{For
8324compatibility with ECLiPSe, the values \const{<}, \const{=<}, \const{>}
8325and \const{>=} are allowed as synonyms.}
8326
8327\begin{center}
8328\begin{tabular}{lll}
8329Order & Ordering & Duplicate handling \\
8330\hline
8331\const{@<}  & ascending  & remove \\
8332\const{@=<} & ascending  & keep \\
8333\const{@>}  & descending & remove \\
8334\const{@>=} & descending & keep \\
8335\end{tabular}
8336\end{center}
8337
8338The sort is \jargon{stable}, which implies that, if duplicates are kept,
8339the order of duplicates is not changed. If duplicates are removed, only
8340the first element of a sequence of duplicates appears in \arg{Sorted}.
8341
8342This predicate supersedes most of the other sorting primitives, for
8343example:
8344
8345\begin{code}
8346sort(List, Sorted)     :- sort(0,  @<, List,  Sorted).
8347msort(List, Sorted)    :- sort(0, @=<, List,  Sorted).
8348keysort(Pairs, Sorted) :- sort(1, @=<, Pairs, Sorted).
8349\end{code}
8350
8351The following example sorts a list of rows, for example resulting from
8352csv_read_file/2) ascending on the 3th column and descending on the 4th
8353column:
8354
8355\begin{code}
8356    sort(4, @>=, Rows0, Rows1),
8357    sort(3, @=<, Rows1, Sorted).
8358\end{code}
8359
8360See also sort/2 (ISO), msort/2, keysort/2, predsort/3 and order_by/2.
8361
8362    \predicate{msort}{2}{+List, -Sorted}
8363Equivalent to sort/2, but does not remove duplicates. Raises a
8364\except{type_error} if \arg{List} is a cyclic list or not a list.
8365
8366    \predicate[ISO]{keysort}{2}{+List, -Sorted}
8367Sort a list of \jargon{pairs}. \arg{List} must be a list of
8368\exam{\arg{Key}-\arg{Value}} pairs, terms whose principal functor is
8369(-)/2. \arg{List} is sorted on \arg{Key} according to the standard order
8370of terms (see \secref{standardorder}). Duplicates are \emph{not}
8371removed. Sorting is \jargon{stable} with regard to the order of the
8372\arg{Values}, i.e., the order of multiple elements that have the same
8373\arg{Key} is not changed.
8374
8375The keysort/2 predicate is often used together with library
8376\pllib{pairs}. It can be used to sort lists on different or multiple
8377criteria. For example, the following predicates sorts a list of atoms
8378according to their length, maintaining the initial order for atoms that
8379have the same length.
8380
8381\begin{code}
8382:- use_module(library(pairs)).
8383
8384sort_atoms_by_length(Atoms, ByLength) :-
8385	map_list_to_pairs(atom_length, Atoms, Pairs),
8386	keysort(Pairs, Sorted),
8387	pairs_values(Sorted, ByLength).
8388\end{code}
8389
8390    \predicate{predsort}{3}{+Pred, +List, -Sorted}
8391Sorts similar to sort/2, but determines the order of two terms by
8392calling \mbox{\arg{Pred}(-\arg{Delta}, +\arg{E1}, +\arg{E2})}.  This
8393call must unify \arg{Delta} with one of \const{<}, \const{>} or
8394\const{=}.  If the built-in predicate compare/3 is used, the result is
8395the same as sort/2.  See also keysort/2.
8396\end{description}
8397
8398
8399\section{Finding all Solutions to a Goal}	\label{sec:allsolutions}
8400
8401\begin{description}
8402    \predicate[ISO]{findall}{3}{+Template, :Goal, -Bag}
8403Create a list of the instantiations \arg{Template} gets successively on
8404backtracking over \arg{Goal} and unify the result with \arg{Bag}.
8405Succeeds with an empty list if \arg{Goal} has no solutions.\\
8406
8407findall/3 is equivalent to bagof/3 with all \jargon{free} variables
8408appearing in \arg{Goal} scoped to the \arg{Goal} with an existential
8409(caret) operator (\op{^}), except that bagof/3 fails when \arg{Goal}
8410has no solutions.
8411
8412    \predicate{findall}{4}{+Template, :Goal, -Bag, +Tail}
8413As findall/3, but returns the result as the difference list
8414\arg{Bag}-\arg{Tail}.   The 3-argument version is defined as
8415
8416\begin{code}
8417findall(Templ, Goal, Bag) :-
8418	findall(Templ, Goal, Bag, [])
8419\end{code}
8420
8421    \predicate[nondet]{findnsols}{4}{+N, @Template, :Goal, -List}
8422    \nodescription
8423    \predicate[nondet]{findnsols}{5}{+N, @Template, :Goal, -List, ?Tail}
8424As findall/3 and findall/4, but generates at most \arg{N} solutions. If
8425\arg{N} solutions are returned, this predicate succeeds with a choice
8426point if \arg{Goal} has a choice point. Backtracking returns the next
8427chunk of (at most) \arg{N} solutions. In addition to passing a plain
8428integer for \arg{N}, a term of the form \term{count}{N} is accepted.
8429Using \term{count}{N}, the size of the next chunk can be controlled
8430using nb_setarg/3. The non-deterministic behaviour used to implement the
8431\jargon{chunk} option in \pllib{pengines}. Based on Ciao, but the Ciao
8432version is deterministic. Portability can be achieved by wrapping the
8433goal in once/1. Below are three examples. The first illustrates standard
8434chunking of answers.  The second illustrates that the chunk size can be
8435adjusted dynamically and the last illustrates that no choice point is
8436left if \arg{Goal} leaves no choice-point after the last solution.
8437
8438\begin{code}
8439?- findnsols(5, I, between(1, 12, I), L).
8440L = [1, 2, 3, 4, 5] ;
8441L = [6, 7, 8, 9, 10] ;
8442L = [11, 12].
8443
8444?- State = count(2),
8445   findnsols(State, I, between(1, 12, I), L),
8446   nb_setarg(1, State, 5).
8447State = count(5), L = [1, 2] ;
8448State = count(5), L = [3, 4, 5, 6, 7] ;
8449State = count(5), L = [8, 9, 10, 11, 12].
8450
8451?- findnsols(4, I, between(1, 4, I), L).
8452L = [1, 2, 3, 4].
8453\end{code}
8454
8455    \predicate[ISO]{bagof}{3}{+Template, :Goal, -Bag}
8456Unify \arg{Bag} with the alternatives of \arg{Template}. If \arg{Goal}
8457has free variables besides the one sharing with \arg{Template}, bagof/3
8458will backtrack over the alternatives of these free variables, unifying
8459\arg{Bag} with the corresponding alternatives of \arg{Template}. The
8460construct \exam{+\arg{Var}{^}\arg{Goal}} tells bagof/3 not to bind
8461\arg{Var} in \arg{Goal}. bagof/3 fails if \arg{Goal} has no solutions.
8462
8463The example below illustrates bagof/3 and the \op{^} operator. The
8464variable bindings are printed together on one line to save paper.
8465\begin{code}
84662 ?- listing(foo).
8467foo(a, b, c).
8468foo(a, b, d).
8469foo(b, c, e).
8470foo(b, c, f).
8471foo(c, c, g).
8472true.
8473
84743 ?- bagof(C, foo(A, B, C), Cs).
8475A = a, B = b, C = G308, Cs = [c, d] ;
8476A = b, B = c, C = G308, Cs = [e, f] ;
8477A = c, B = c, C = G308, Cs = [g].
8478
84794 ?- bagof(C, A^foo(A, B, C), Cs).
8480A = G324, B = b, C = G326, Cs = [c, d] ;
8481A = G324, B = c, C = G326, Cs = [e, f, g].
8482
84835 ?-
8484\end{code}
8485
8486    \predicate[ISO]{setof}{3}{+Template, +Goal, -Set}
8487Equivalent to bagof/3, but sorts the result using sort/2 to get a sorted
8488list of alternatives without duplicates.
8489\end{description}
8490
8491\section{Forall}			\label{sec:forall2}
8492
8493\begin{description}
8494    \predicate[semidet]{forall}{2}{:Cond, :Action}
8495For all alternative bindings of \arg{Cond}, \arg{Action} can be proven.
8496The example verifies that all arithmetic statements in the given list
8497are correct. It does not say which is wrong if one proves wrong.
8498
8499\begin{code}
8500?- forall(member(Result = Formula, [2 = 1 + 1, 4 = 2 * 2]),
8501                 Result =:= Formula).
8502\end{code}
8503
8504The predicate forall/2 is implemented as \verb$\+ ( Cond, \+ Action)$,
8505i.e., \textit{There is no instantiation of \arg{Cond} for which
8506\arg{Action} is false.}. The use of double negation implies that
8507forall/2 \emph{does not change any variable bindings}. It proves a
8508relation. The forall/2 control structure can be used for its
8509side-effects. E.g., the following asserts relations in a list into the
8510dynamic database:
8511
8512\begin{code}
8513?- forall(member(Child-Parent, ChildPairs),
8514	  assertz(child_of(Child, Parent))).
8515\end{code}
8516
8517Using forall/2 as \term{forall}{Generator, SideEffect} is preferred over
8518the classical \jargon{failure driven loop} as shown below because it
8519makes it explicit which part of the construct is the generator and which
8520part creates the side effects. Also, unexpected failure of the side
8521effect causes the construct to fail. Failure makes it evident that there
8522is an issue with the code, while a failure driven loop would succeed
8523with an erroneous result.
8524
8525\begin{code}
8526	...,
8527	(   Generator,
8528	    SideEffect,
8529	    fail
8530	;   true
8531	)
8532\end{code}
8533
8534If your intent is to create variable bindings, the forall/2 control
8535structure is inadequate.  Possibly you are looking for maplist/2,
8536findall/3 or foreach/2.
8537\end{description}
8538
8539
8540\section{Formatted Write}		\label{sec:format}
8541
8542The current version of SWI-Prolog provides two formatted write
8543predicates. The `writef' family (writef/1, writef/2, swritef/3), is
8544compatible with Edinburgh C-Prolog and should be considered
8545\emph{deprecated}. The `format' family (format/1, format/2, format/3),
8546was defined by Quintus Prolog and currently available in many Prolog
8547systems, although the details vary.
8548
8549\subsection{Writef}
8550\label{sec:writef}
8551
8552\begin{description}
8553    \predicate[deprecated]{writef}{1}{+Atom}
8554Equivalent to \exam{writef(Atom, []).}  See writef/2 for details.
8555    \predicate[deprecated]{writef}{2}{+Format, +Arguments}
8556Formatted write.  \arg{Format} is an atom whose characters will be printed.
8557\arg{Format} may contain certain special character sequences which specify
8558certain formatting and substitution actions.  \arg{Arguments} provides
8559all the terms required to be output.
8560
8561Escape sequences to generate a single special character:
8562
8563\begin{center}
8564\begin{tabular}{|l|p{3.5in}|}
8565\hline
8566\fmtseq{\n}   &  Output a newline character (see also nl/[0,1]) \\
8567\fmtseq{\l}   &  Output a line separator (same as \fmtseq{\n}) \\
8568\fmtseq{\r}   &  Output a carriage return character (ASCII 13) \\
8569\fmtseq{\t}   &  Output the ASCII character TAB (9) \\
8570\fmtseq{\\}   &  The character \chr{\} is output \\
8571\fmtseq{\%}   &  The character \chr{%} is output \\
8572\fmtseq{\nnn} &  where <nnn> is an integer (1-3 digits); the
8573		 character with code <nnn> is output
8574		 (NB : <nnn> is read as \strong{decimal}) \\
8575\hline
8576\end{tabular}
8577\end{center}
8578
8579Note that \fmtseq{\l}, \fmtseq{\nnn} and \fmtseq{\\}
8580are interpreted differently when character escapes are in effect. See
8581\secref{charescapes}.
8582
8583Escape sequences to include arguments from \arg{Arguments}. Each time a
8584\% escape sequence is found in \arg{Format} the next argument from \arg{Arguments} is formatted according to the specification.
8585
8586\begin{center}
8587\begin{tabular}{|l|p{3.5in}|}
8588\hline
8589\fmtseq{%t}  &  print/1 the next item (mnemonic: term) \\
8590\fmtseq{%w}  &  write/1 the next item \\
8591\fmtseq{%q}  &  writeq/1 the next item \\
8592\fmtseq{%d}  &  Write the term, ignoring operators.  See also
8593		write_term/2.  Mnemonic: old Edinburgh display/1 \\
8594\fmtseq{%p}  &  print/1 the next item (identical to \fmtseq{%t}) \\
8595\fmtseq{%n}  &  Put the next item as a character (i.e., it is
8596                a character code) \\
8597\fmtseq{%r}  &  Write the next item N times where N is the
8598                second item (an integer) \\
8599\fmtseq{%s}  &  Write the next item as a String (so it must
8600                be a list of characters) \\
8601\fmtseq{%f}  &  Perform a ttyflush/0 (no items used) \\
8602\fmtseq{%Nc} &  Write the next item Centered in $N$ columns \\
8603\fmtseq{%Nl} &  Write the next item Left justified in $N$ columns \\
8604\fmtseq{%Nr} &  Write the next item Right justified in $N$ columns.
8605                $N$ is a decimal number with at least one digit.
8606                The item must be an atom, integer, float or string. \\
8607\hline
8608\end{tabular}
8609\end{center}
8610    \predicate[deprecated]{swritef}{3}{-String, +Format, +Arguments}
8611Equivalent to writef/2, but ``writes'' the result on \arg{String} instead
8612of the current output stream. Example:
8613\begin{code}
8614?- swritef(S, '%15L%w', ['Hello', 'World']).
8615
8616S = "Hello          World"
8617\end{code}
8618    \predicate[deprecated]{swritef}{2}{-String, +Format}
8619Equivalent to \exam{swritef(String, Format, []).}
8620\end{description}
8621
8622\subsection{Format}
8623\label{sec:format-predicates}
8624
8625The format family of predicates is the most versatile and
8626portable\footnote{Unfortunately not covered by any standard.} way to
8627produce textual output.
8628
8629\begin{description}
8630    \predicate{format}{1}{+Format}
8631Defined as `\exam{format(Format) :- format(Format, []).}'.  See
8632format/2 for details.
8633
8634    \predicate{format}{2}{+Format, :Arguments}
8635\arg{Format} is an atom, list of character codes, or a Prolog string.
8636\arg{Arguments} provides the arguments required by the format
8637specification. If only one argument is required and this single argument
8638is not a list, the argument need not be put in a list. Otherwise the
8639arguments are put in a list.
8640
8641Special sequences start with the tilde (\chr{~}), followed by an
8642optional numeric argument, optionally followed by a colon modifier (:),
8643\footnote{The colon modifiers is a SWI-Prolog extension, proposed by
8644Richard O'Keefe.} followed by a character describing the action to be
8645undertaken. A numeric argument is either a sequence of digits,
8646representing a positive decimal number, a sequence \exam{`<character>},
8647representing the character code value of the character (only useful for
8648\fmtseq{~t}) or a asterisk (\chr{*}), in which case the numeric argument
8649is taken from the next argument of the argument list, which should be a
8650positive integer. E.g., the following three examples all pass 46
8651(\chr{.}) to \verb$~t$:
8652
8653\begin{code}
8654?- format('~w ~46t ~w~72|~n', ['Title', 'Page']).
8655?- format('~w ~`.t ~w~72|~n', ['Title', 'Page']).
8656?- format('~w ~*t ~w~72|~n', ['Title', 46, 'Page']).
8657\end{code}
8658
8659Numeric conversion (\chr{d}, \chr{D}, \chr{e}, \chr{E}, \chr{f}, \chr{g}
8660and \chr{G}) accept an arithmetic expression as argument. This is
8661introduced to handle rational numbers transparently (see
8662\secref{rational}).  The floating point conversions allow for unlimited
8663precision for printing rational numbers in decimal form.  E.g., the
8664following will write as many 3's as you want by changing the `50'.
8665
8666\begin{code}
8667?- format('~50f', [10 rdiv 3]).
86683.33333333333333333333333333333333333333333333333333
8669\end{code}
8670
8671
8672\begin{itemize}
8673    \fmtchar{~}
8674Output the tilde itself.
8675
8676    \fmtchar{a}
8677Output the next argument, which must be an atom. This option is
8678equivalent to {\bf w}, except that it requires the argument to be an
8679atom.
8680
8681    \fmtchar{c}
8682Interpret the next argument as a character code and add it to the
8683output. This argument must be a valid Unicode character code. Note that
8684the actually emitted bytes are defined by the character encoding of the
8685output stream and an exception may be raised if the output stream is not
8686capable of representing the requested Unicode character. See
8687\secref{encoding} for details.
8688
8689    \fmtchar{d}
8690Output next argument as a decimal number.  It should be an integer.  If
8691a numeric argument is specified, a dot is inserted \arg{argument}
8692positions from the right (useful for doing fixed point arithmetic with
8693integers, such as handling amounts of money).
8694
8695The colon modifier (e.g., \verb$~:d$) causes the number to be printed
8696according to the locale of the output stream.  See \secref{locale}.
8697
8698    \fmtchar{D}
8699Same as {\bf d}, but makes large values easier to read by inserting a
8700comma every three digits left or right of the dot.  This is the same
8701as \verb$~:d$, but using the fixed English locale.
8702
8703    \fmtchar{e}
8704Output next argument as a floating point number in exponential
8705notation.  The numeric argument specifies the precision.  Default is 6
8706digits.  Exact representation depends on the C library function
8707printf(). This function is invoked with the format
8708\mbox{\tt\%.<precision>e}.
8709
8710    \fmtchar{E}
8711Equivalent to {\bf e}, but outputs a capital E to indicate the exponent.
8712
8713    \fmtchar{f}
8714Floating point in non-exponential notation. The numeric argument defines
8715the number of digits right of the decimal point.  If the colon modifier
8716(:) is used, the float is formatted using conventions from the current
8717locale, which may define the decimal point as well as grouping of digits
8718left of the decimal point.
8719
8720    \fmtchar{g}
8721Floating point in {\bf e} or {\bf f} notation, whichever is shorter.
8722
8723    \fmtchar{G}
8724Floating point in {\bf E} or {\bf f} notation, whichever is shorter.
8725
8726    \fmtchar{i}
8727Ignore next argument of the argument list. Produces no output.
8728
8729    \fmtchar{I}
8730Emit a decimal number using Prolog digit grouping (the underscore,
8731\verb$_$).  The argument describes the size of each digit group.
8732The default is 3.  See also \secref{digitgroupsyntax}.  For example:
8733
8734\begin{code}
8735?- A is 1<<100, format('~10I', [A]).
87361_2676506002_2822940149_6703205376
8737\end{code}
8738
8739    \fmtchar{k}
8740Give the next argument to write_canonical/1.
8741    \fmtchar{n}
8742Output a newline character.
8743    \fmtchar{N}
8744Only output a newline if the last character output on this stream was
8745not a newline. Not properly implemented yet.
8746    \fmtchar{p}
8747Give the next argument to print/1.
8748    \fmtchar{q}
8749Give the next argument to writeq/1.
8750
8751    \fmtchar{r}
8752Print integer in radix numeric argument notation. Thus
8753\fmtseq{~16r} prints its argument hexadecimal. The argument should
8754be in the range $[2, \ldots, 36]$. Lowercase letters are used for
8755digits above 9.  The colon modifier may be used to form locale-specific
8756digit groups.
8757
8758    \fmtchar{R}
8759Same as {\bf r}, but uses uppercase letters for digits above 9.
8760    \fmtchar{s}
8761Output text from a list of character codes or a string (see string/1 and
8762\secref{strings}) from the next argument.\footnote{The \textbf{s}
8763modifier also accepts an atom for compatibility.  This is deprecated
8764due to the ambiguity of \texttt{[]}.}
8765    \fmtchar{@}
8766Interpret the next argument as a goal and execute it.  Output written
8767to the \const{current_output} stream is inserted at this place.  Goal
8768is called in the module calling format/3.  This option is not present
8769in the original definition by Quintus, but supported by some other
8770Prolog systems.
8771    \fmtchar{t}
8772All remaining space between 2 tab stops is distributed equally over
8773\fmtseq{~t} statements between the tab stops. This space is padded
8774with spaces by default. If an argument is supplied, it is taken to be
8775the character code of the character used for padding. This can be
8776used to do left or right alignment, centering, distributing, etc. See
8777also \fmtseq{~|} and \fmtseq{~+} to set tab stops. A tab stop is
8778assumed at the start of each line.
8779    \fmtchar{|}
8780Set a tab stop on the current position. If an argument is supplied set
8781a tab stop on the position of that argument. This will cause all
8782\fmtseq{~t}'s to be distributed between the previous and this tab stop.
8783
8784    \fmtchar{+}
8785Set a tab stop (as \fmtseq{~|}) relative to the last tab stop or the
8786beginning of the line if no tab stops are set before the \fmtseq{~+}.
8787This constructs can be used to fill fields. The partial format sequence
8788below prints an integer right-aligned and padded with zeros in 6
8789columns.  The \ldots{} sequences in the example illustrate that the
8790integer is aligned in 6 columns regardless of the remainder of the
8791format specification.
8792
8793\begin{code}
8794	format('...~|~`0t~d~6+...', [..., Integer, ...])
8795\end{code}
8796
8797    \fmtchar{w}
8798Give the next argument to write/1.
8799    \fmtchar{W}
8800Give the next two arguments to write_term/2.  For example,
8801\verb$format('~W', [Term, [numbervars(true)]])$.
8802This option is SWI-Prolog specific.
8803\end{itemize}
8804
8805Example:
8806
8807\begin{code}
8808simple_statistics :-
8809    <obtain statistics>         % left to the user
8810    format('~tStatistics~t~72|~n~n'),
8811    format('Runtime: ~`.t ~2f~34|  Inferences: ~`.t ~D~72|~n',
8812                                            [RunT, Inf]),
8813    ....
8814\end{code}
8815
8816will output
8817
8818\begin{code}
8819                             Statistics
8820
8821Runtime: .................. 3.45  Inferences: .......... 60,345
8822\end{code}
8823
8824    \predicate{format}{3}{+Output, +Format, :Arguments}
8825As format/2, but write the output on the given \arg{Output}. The
8826de-facto standard only allows \arg{Output} to be a stream. The
8827SWI-Prolog implementation allows all valid arguments for
8828with_output_to/2.%
8829	\footnote{Earlier versions defined \nopredref{sformat}{3}.
8830	These predicates have been moved to the library
8831	\pllib{backcomp}.}
8832For example:
8833
8834\begin{code}
8835?- format(atom(A), '~D', [1000000]).
8836A = '1,000,000'
8837\end{code}
8838\end{description}
8839
8840
8841\subsection{Programming Format}
8842\label{sec:format-hook}
8843
8844\begin{description}
8845    \predicate{format_predicate}{2}{+Char, +Head}
8846If a sequence \fmtseq{~c} (tilde, followed by some character) is
8847found, the format/3 and friends first check whether the user has
8848defined a predicate to handle the format. If not, the built-in
8849formatting rules described above are used. \arg{Char} is either a
8850character code or a one-character atom, specifying the letter to
8851be (re)defined. \arg{Head} is a term, whose name and arity are used to
8852determine the predicate to call for the redefined formatting character.
8853The first argument to the predicate is the numeric argument of the
8854format command, or the atom \const{default} if no argument is specified.
8855The remaining arguments are filled from the argument list. The example
8856below defines \fmtseq{~T} to print a timestamp in ISO8601 format (see
8857format_time/3).  The subsequent block illustrates a possible call.
8858
8859\begin{code}
8860:- format_predicate('T', format_time(_Arg,_Time)).
8861
8862format_time(_Arg, Stamp) :-
8863	must_be(number, Stamp),
8864	format_time(current_output, '%FT%T%z', Stamp).
8865\end{code}
8866
8867\begin{code}
8868?- get_time(Now),
8869   format('Now, it is ~T~n', [Now]).
8870Now, it is 2012-06-04T19:02:01+0200
8871Now = 1338829321.6620328.
8872\end{code}
8873
8874    \predicate{current_format_predicate}{2}{?Code, ?:Head}
8875True when \chr{~}\arg{Code} is handled by the user-defined predicate
8876specified by \arg{Head}.
8877\end{description}
8878
8879\section{Global variables}			\label{sec:gvar}
8880
8881Global variables are associations between names (atoms) and terms.
8882They differ in various ways from storing information using assert/1
8883or recorda/3.
8884
8885\begin{itemize}
8886    \item The value lives on the Prolog (global) stack.  This implies
8887          that lookup time is independent of the size of the term.
8888	  This is particularly interesting for large data structures
8889	  such as parsed XML documents or the CHR global constraint
8890	  store.
8891
8892    \item They support both global assignment using nb_setval/2 and
8893          backtrackable assignment using b_setval/2.
8894
8895    \item Only one value (which can be an arbitrary complex Prolog
8896	  term) can be associated to a variable at a time.
8897
8898    \item Their value cannot be shared among threads.  Each thread
8899          has its own namespace and values for global variables.
8900
8901    \item Currently global variables are scoped globally.  We may
8902          consider module scoping in future versions.
8903\end{itemize}
8904
8905Both b_setval/2 and nb_setval/2 implicitly create a variable if the
8906referenced name does not already refer to a variable.
8907
8908Global variables may be initialised from directives to make them
8909available during the program lifetime, but some considerations are
8910necessary for saved states and threads. Saved states do not store global
8911variables, which implies they have to be declared with initialization/1
8912to recreate them after loading the saved state.  Each thread has
8913its own set of global variables, starting with an empty set.  Using
8914thread_initialization/1 to define a global variable it will be
8915defined, restored after reloading a saved state and created in all
8916threads that are created \emph{after} the registration.  Finally,
8917global variables can be initialised using the exception hook
8918exception/3.  The latter technique is used by CHR (see \chapref{chr}).
8919
8920
8921\begin{description}
8922    \predicate{b_setval}{2}{+Name, +Value}
8923Associate the term \arg{Value} with the atom \arg{Name} or replace
8924the currently associated value with \arg{Value}.  If \arg{Name} does
8925not refer to an existing global variable, a variable with initial value
8926\const{[]} is created (the empty list).  On backtracking the
8927assignment is reversed.
8928
8929    \predicate{b_getval}{2}{+Name, -Value}
8930Get the value associated with the global variable \arg{Name} and unify
8931it with \arg{Value}. Note that this unification may further instantiate
8932the value of the global variable. If this is undesirable the normal
8933precautions (double negation or copy_term/2) must be taken. The
8934b_getval/2 predicate generates errors if \arg{Name} is not an atom or
8935the requested variable does not exist.
8936\end{description}
8937
8938\begin{description}
8939    \predicate{nb_setval}{2}{+Name, +Value}
8940Associates a copy of \arg{Value} created with duplicate_term/2
8941with the atom \arg{Name}.  Note that this can be used to set an
8942initial value other than \const{[]} prior to backtrackable assignment.
8943
8944    \predicate{nb_getval}{2}{+Name, -Value}
8945The nb_getval/2 predicate is a synonym for b_getval/2, introduced for
8946compatibility and symmetry.  As most scenarios will use a particular
8947global variable using either non-backtrackable or backtrackable
8948assignment, using nb_getval/2 can be used to document that the
8949variable is non-backtrackable. Raises \term{existence_error}{variable,
8950Name} if the variable does not exist.  Alternatively, nb_current/2 can
8951used to query a global variable.  This version \emph{fails} if the
8952variable does not exist rather than raising an exception.
8953
8954    \predicate{nb_linkval}{2}{+Name, +Value}
8955Associates the term \arg{Value} with the atom \arg{Name} without copying
8956it. This is a fast special-purpose variation of nb_setval/2 intended for
8957expert users only because the semantics on backtracking to a point
8958before creating the link are poorly defined for compound terms. The
8959principal term is always left untouched, but backtracking behaviour on
8960arguments is undone if the original assignment was \jargon{trailed} and
8961left alone otherwise, which implies that the history that created the
8962term affects the behaviour on backtracking. Consider the
8963following example:
8964
8965\begin{code}
8966demo_nb_linkval :-
8967	T = nice(N),
8968	(   N = world,
8969	    nb_linkval(myvar, T),
8970	    fail
8971	;   nb_getval(myvar, V),
8972	    writeln(V)
8973	).
8974\end{code}
8975
8976    \predicate{nb_current}{2}{?Name, ?Value}
8977Enumerate all defined variables with their value. The order of
8978enumeration is undefined. Note that nb_current/2 can be used as an
8979alternative for nb_getval/2 to request the value of a variable and fail
8980silently if the variable does not exists.
8981
8982    \predicate{nb_delete}{1}{+Name}
8983Delete the named global variable.  Succeeds also if the named variable
8984does not exist.
8985\end{description}
8986
8987
8988\subsection{Compatibility of SWI-Prolog Global Variables}
8989\label{sec:gvars-compat}
8990
8991Global variables have been introduced by various Prolog implementations
8992recently.  The implementation of them in SWI-Prolog is based on hProlog
8993by Bart Demoen. In discussion with Bart it was decided that the
8994semantics of hProlog nb_setval/2, which is equivalent to nb_linkval/2,
8995is not acceptable for normal Prolog users as the behaviour is influenced
8996by how built-in predicates that construct terms (read/1, =../2, etc.) are
8997implemented.
8998
8999GNU-Prolog provides a rich set of global variables, including arrays.
9000Arrays can be implemented easily in SWI-Prolog using functor/3 and
9001setarg/3 due to the unrestricted arity of compound terms.
9002
9003\section{Terminal Control}		\label{sec:tty}
9004
9005The following predicates form a simple access mechanism to the Unix termcap
9006library to provide terminal-independent I/O for screen terminals. These
9007predicates are only available on Unix machines.  The SWI-Prolog Windows
9008console accepts the ANSI escape sequences.
9009
9010\begin{description}
9011    \predicate{tty_get_capability}{3}{+Name, +Type, -Result}
9012Get the capability named \arg{Name} from the termcap library.  See
9013termcap(5) for the capability names. \arg{Type} specifies the type of
9014the expected result, and is one of \const{string}, \const{number} or
9015\const{bool}.  String results are returned as an atom, number results as
9016an integer, and bool results as the atom \const{on} or \const{off}.  If
9017an option cannot be found, this predicate fails silently.  The
9018results are only computed once. Successive queries on the same
9019capability are fast.
9020    \predicate{tty_goto}{2}{+X, +Y}
9021Goto position \mbox{(\arg{X}, \arg{Y})} on the screen.  Note that the predicates
9022line_count/2 and line_position/2 will not have a well-defined
9023behaviour while using this predicate.
9024    \predicate{tty_put}{2}{+Atom, +Lines}
9025Put an atom via the termcap library function tputs().  This function
9026decodes padding information in the strings returned by tty_get_capability/3
9027and should be used to output these strings. \arg{Lines} is the
9028number of lines affected by the operation, or 1 if not applicable (as
9029in almost all cases).
9030    \predicate{tty_size}{2}{-Rows, -Columns}
9031Determine the size of the terminal.  Platforms:
9032
9033\begin{description}
9034    \item[Unix]
9035If the system provides \jargon{ioctl} calls for this, these are
9036used and tty_size/2 properly reflects the actual size after a user
9037resize of the window.   The \jargon{ioctl} is issued on the file
9038descriptor associated with the \const{user_input} stream. As a fallback,
9039the system uses tty_get_capability/3 using \const{li} and \const{co}
9040capabilities. In this case the reported size reflects the size at the
9041first call and is not updated after a user-initiated resize of the
9042terminal.
9043
9044    \item[Windows]
9045Getting the size of the terminal is provided for \program{swipl-win.exe}.
9046The requested value reflects the current size. For the
9047multithreaded version the console that is associated with the
9048\const{user_input} stream is used.
9049\end{description}
9050\end{description}
9051
9052\section{Operating System Interaction}	\label{sec:system}
9053
9054The predicates in this section provide basic access to the operating
9055system that has been part of the Prolog legacy tradition. Note that more
9056advanced access to low-level OS features is provided by several libraries
9057from the \const{clib} package, notably library \pllib{process},
9058\pllib{socket}, \pllib{unix} and \pllib{filesex}.
9059
9060
9061\begin{description}
9062    \predicate{shell}{1}{+Command}
9063Equivalent to `\exam{shell(Command, 0)}'.  See shell/2 for details.
9064
9065    \predicate{shell}{2}{+Command, -Status}
9066Execute \arg{Command} on the operating system. \arg{Command} is given to the
9067Bourne shell (/bin/sh). \arg{Status} is unified with the exit status of
9068the command.
9069
9070On Windows, shell/[1,2] executes the command using the CreateProcess()
9071API and waits for the command to terminate. If the command ends with a
9072\chr{\&} sign, the command is handed to the WinExec() API, which does
9073not wait for the new task to terminate. See also win_exec/2 and
9074win_shell/2. Please note that the CreateProcess() API does {\bf not}
9075imply the Windows command interpreter (\program{cmd.exe} and therefore
9076commands that are built in the command interpreter can only be activated
9077using the command interpreter. For example, a file can be copied using
9078the command below.
9079
9080\begin{code}
9081?- shell('cmd.exe /C copy file1.txt file2.txt').
9082\end{code}
9083
9084Note that many of the operations that can be achieved using the shell
9085built-in commands can easily be achieved using Prolog primitives. See
9086make_directory/1, delete_file/1, rename_file/2, etc. The clib package
9087provides \pllib{filesex}, implementing various high level file
9088operations such as copy_file/2.  Using Prolog primitives instead of
9089shell commands improves the portability of your program.
9090
9091The library \pllib{process} provides process_create/3 and several
9092related primitives that support more fine-grained interaction with
9093processes, including I/O redirection and management of asynchronous
9094processes.
9095
9096    \predicate{getenv}{2}{+Name, -Value}
9097Get environment variable. Fails silently if the variable does not exist.
9098Please note that environment variable names are case-sensitive on Unix
9099systems and case-insensitive on Windows.
9100
9101    \predicate{setenv}{2}{+Name, +Value}
9102Set an environment variable.  \arg{Name} and \arg{Value} must be
9103instantiated to atoms or integers.  The environment variable will be
9104passed to shell/[0-2] and can be requested using getenv/2.  They also
9105influence expand_file_name/2.  Environment variables are shared between
9106threads.  Depending on the underlying C library, setenv/2 and unsetenv/1
9107may not be thread-safe and may cause memory leaks.  Only changing the
9108environment once and before starting threads is safe in all versions
9109of SWI-Prolog.
9110
9111    \predicate{unsetenv}{1}{+Name}
9112Remove an environment variable from the environment. Some systems lack
9113the underlying unsetenv() library function. On these systems unsetenv/1
9114sets the variable to the empty string.
9115
9116    \predicate{setlocale}{3}{+Category, -Old, +New}
9117Set/Query the \jargon{locale} setting which tells the C library how to
9118interpret text files, write numbers, dates, etc. Category is one of
9119\const{all}, \const{collate}, \const{ctype}, \const{messages},
9120\const{monetary}, \const{numeric} or \const{time}. For details, please
9121consult the C library locale documentation. See also \secref{encoding}.
9122Please note that the locale is shared between all threads and
9123thread-safe usage of setlocale/3 is in general not possible. Do locale
9124operations before starting threads or thoroughly study threading aspects
9125of locale support in your environment before using in multithreaded
9126environments. Locale settings are used by format_time/3, collation_key/2
9127and locale_sort/2.
9128\end{description}
9129
9130\subsection{Windows-specific Operating System Interaction}
9131\label{sec:winsystem}
9132
9133The predicates in this section are only available on the Windows version
9134of SWI-Prolog. Their use is discouraged if there are portable
9135alternatives. For example, win_exec/2 and win_shell/2 can often be
9136replaced by the more portable shell/2 or the more powerful
9137process_create/3.
9138
9139\begin{description}
9140    \predicate{win_exec}{2}{+Command, +Show}
9141Windows only. Spawns a Windows task without waiting for its
9142completion.  \arg{Show} is one of the Win32 \const{SW_*} constants
9143written in lowercase without the \const{SW_*}:
9144\const{hide}
9145\const{maximize}
9146\const{minimize}
9147\const{restore}
9148\const{show}
9149\const{showdefault}
9150\const{showmaximized}
9151\const{showminimized}
9152\const{showminnoactive}
9153\const{showna}
9154\const{shownoactive}
9155\const{shownormal}.
9156In addition, \const{iconic} is a synonym for \const{minimize} and
9157\const{normal} for \const{shownormal}.
9158
9159    \predicate{win_shell}{3}{+Operation, +File, +Show}
9160Windows only. Opens the document \arg{File} using the Windows shell
9161rules for doing so. \arg{Operation} is one of \const{open},
9162\const{print} or \const{explore} or another operation registered with
9163the shell for the given document type. On modern systems it is also
9164possible to pass a \index{URL}URL as \arg{File}, opening the URL in
9165Windows default browser. This call interfaces to the Win32 API
9166ShellExecute(). The \arg{Show} argument determines the initial state of
9167the opened window (if any). See win_exec/2 for defined values.
9168
9169    \predicate{win_shell}{2}{+Operation, +File}
9170Same as \term{win_shell}{Operation, File, normal}.
9171
9172    \predicate{win_registry_get_value}{3}{+Key, +Name, -Value}
9173Windows only. Fetches the value of a Windows registry key. \arg{Key} is
9174an atom formed as a path name describing the desired registry key.
9175\arg{Name} is the desired attribute name of the key. \arg{Value} is
9176unified with the value. If the value is of type \type{DWORD}, the value
9177is returned as an integer. If the value is a string, it is returned as a
9178Prolog atom. Other types are currently not supported. The default `root'
9179is \const{HKEY_CURRENT_USER}. Other roots can be specified explicitly as
9180\const{HKEY_CLASSES_ROOT}, \const{HKEY_CURRENT_USER},
9181\const{HKEY_LOCAL_MACHINE} or \const{HKEY_USERS}. The example below
9182fetches the extension to use for Prolog files (see \file{README.TXT} on
9183the Windows version):
9184
9185\begin{code}
9186?- win_registry_get_value(
9187       'HKEY_LOCAL_MACHINE/Software/SWI/Prolog',
9188       fileExtension,
9189       Ext).
9190
9191Ext = pl
9192\end{code}
9193
9194    \predicate{win_folder}{2}{?Name, -Directory}
9195True if \arg{Name} is the Windows `CSIDL' of \arg{Directory}.  If
9196\arg{Name} is unbound, all known Windows special paths are generated.
9197\arg{Name} is the CSIDL after deleting the leading \const{CSIDL_} and
9198mapping the constant to lowercase.  Check the Windows documentation
9199for the function SHGetSpecialFolderPath() for a description of the
9200defined constants.  This example extracts the `My Documents' folder:
9201
9202\begin{code}
9203?- win_folder(personal, MyDocuments).
9204
9205MyDocuments = 'C:/Documents and Settings/jan/My Documents'
9206\end{code}
9207
9208    \predicate{win_add_dll_directory}{1}{+AbsDir}
9209This predicate adds a directory to the search path for dependent DLL
9210files.  If possible, this is achieved with win_add_dll_directory/2.
9211Otherwise, \const{\%PATH\%} is extended with the provided directory.
9212\arg{AbsDir} may be specified in the Prolog canonical syntax.  See
9213prolog_to_os_filename/2.  Note that use_foreign_library/1 passes an
9214absolute path to the DLL if the destination DLL can be located from
9215the specification using absolute_file_name/3.
9216
9217    \predicate{win_add_dll_directory}{2}{+AbsDir, -Cookie}
9218This predicate adds a directory to the search path for dependent DLL
9219files. If the call is successful it unifies \arg{Cookie} with a handle
9220that must be passed to win_remove_dll_directory/1 to remove the
9221directory from the search path. Error conditions:
9222
9223    \begin{itemize}
9224    \item This predicate is available in the Windows port of SWI-Prolog
9225	  starting from 6.3.8/6.2.6.
9226    \item This predicate \emph{fails} if Windows does not yet support the
9227          underlying primitives.  These are available in recently
9228	  patched Windows~7 systems and later.
9229    \item This predicate throws an exception if the provided path is
9230          invalid or the underlying Windows API returns an error.
9231    \end{itemize}
9232
9233If open_shared_object/2 is passed an \emph{absolute} path to a DLL on a
9234Windows installation that supports AddDllDirectory() and
9235friends,\footnote{Windows~7 with up-to-date patches or Windows~8.}
9236SWI-Prolog uses LoadLibraryEx() with the flags
9237\const{LOAD_LIBRARY_SEARCH_DLL_LOAD_DIR} and
9238\const{LOAD_LIBRARY_SEARCH_DEFAULT_DIRS}. In this scenario, directories
9239from \const{\%PATH\%} and \emph{not} searched. Additional directories
9240can be added using win_add_dll_directory/2.
9241
9242    \predicate{win_remove_dll_directory}{1}{-Cookie}
9243Remove a DLL search directory installed using win_add_dll_directory/2.
9244\end{description}
9245
9246
9247\subsection{Dealing with time and date}		\label{sec:timedate}
9248
9249Representing time in a computer system is surprisingly complicated.
9250There are a large number of time representations in use, and the correct
9251choice depends on factors such as compactness, resolution and desired
9252operations. Humans tend to think about time in hours, days, months,
9253years or centuries. Physicists think about time in seconds. But, a month
9254does not have a defined number of seconds. Even a day does not have a
9255defined number of seconds as sometimes a leap-second is introduced to
9256synchronise properly with our earth's rotation. At the same time,
9257resolution demands a range from better than pico-seconds to millions of
9258years. Finally, civilizations have a wide range of calendars. Although
9259there exist libraries dealing with most of this complexity, our desire
9260to keep Prolog clean and lean stops us from fully supporting these.
9261
9262For human-oriented tasks, time can be broken into years, months, days,
9263hours, minutes, seconds and a timezone. Physicists prefer to have time
9264in an arithmetic type representing seconds or fraction thereof, so basic
9265arithmetic deals with comparison and durations. An additional advantage
9266of the physicist's approach is that it requires much less space. For
9267these reasons, SWI-Prolog uses an arithmetic type as its prime time
9268representation.
9269
9270Many C libraries deal with time using fixed-point arithmetic, dealing
9271with a large but finite time interval at constant resolution. In our
9272opinion, using a floating point number is a more natural choice as we can
9273use a natural unit and the interface does not need to be changed if
9274a higher resolution is required in the future. Our unit of choice is the
9275second as it is the scientific unit.%
9276	\footnote{Using Julian days is a choice made by the Eclipse
9277		  team.  As conversion to dates is needed for a human
9278		  readable notation of time and Julian days cannot deal
9279		  naturally with leap seconds, we decided for the second as
9280		  our unit.}
9281We have placed our origin at 1970-01-01T0:0:0Z for compatibility with the
9282POSIX notion of time as well as with older time support provided by
9283SWI-Prolog.
9284
9285Where older versions of SWI-Prolog relied on the POSIX conversion
9286functions, the current implementation uses
9287\href{http://cr.yp.to/libtai.html}{libtai} to realise conversion between
9288time-stamps and calendar dates for a period of 10 million years.
9289
9290\subsubsection{Time and date data structures}
9291\label{sec:dattimedata}
9292
9293We use the following time representations
9294
9295\begin{description}
9296    \definition{TimeStamp}
9297A TimeStamp is a floating point number expressing the time in seconds
9298since the Epoch at 1970-01-01.
9299
9300    \termitem{date}{Y,M,D,H,Mn,S,Off,TZ,DST}
9301We call this term a \emph{date-time} structure. The first 5 fields are
9302integers expressing the year, month (1..12), day (1..31), hour (0..23)
9303and minute (0..59). The \arg{S} field holds the seconds as a floating point
9304number between 0.0 and 60.0. \arg{Off} is an integer representing the
9305offset relative to UTC in seconds, where positive values are west of
9306Greenwich.  If converted from local time (see stamp_date_time/3),
9307\arg{TZ} holds the name of the local timezone.  If the timezone is
9308not known, \arg{TZ} is the atom \const{-}.  \arg{DST} is \const{true}
9309if daylight saving time applies to the current time, \const{false}
9310if daylight saving time is relevant but not effective, and \const{-}
9311if unknown or the timezone has no daylight saving time.
9312
9313    \termitem{date}{Y,M,D}
9314Date using the same values as described above.  Extracted using
9315date_time_value/3.
9316
9317    \termitem{time}{H,Mn,S}
9318Time using the same values as described above.  Extracted using
9319date_time_value/3.
9320\end{description}
9321
9322\subsubsection{Time and date predicates}
9323\label{sec:datimepreds}
9324
9325
9326\begin{description}
9327    \predicate{get_time}{1}{-TimeStamp}
9328Return the current time as a \arg{TimeStamp}.  The granularity is system-dependent.  See \secref{dattimedata}.
9329
9330    \predicate{stamp_date_time}{3}{+TimeStamp, -DateTime, +TimeZone}
9331Convert a \arg{TimeStamp} to a \arg{DateTime} in the given timezone.
9332See \secref{dattimedata} for details on the data types.  \arg{TimeZone}
9333describes the timezone for the conversion.  It is one of \const{local}
9334to extract the local time, \const{'UTC'} to extract a UTC time or an
9335integer describing the seconds west of Greenwich.
9336
9337    \predicate{date_time_stamp}{2}{+DateTime, -TimeStamp}
9338Compute the timestamp from a {date}/9 term.  Values for month, day,
9339hour, minute or second need not be normalized.  This flexibility
9340allows for easy computation of the time at any given number of
9341these units from a given timestamp.  Normalization can be achieved
9342following this call with stamp_date_time/3.  This example computes
9343the date 200 days after 2006-07-14:
9344
9345\begin{code}
9346?- date_time_stamp(date(2006,7,214,0,0,0,0,-,-), Stamp),
9347   stamp_date_time(Stamp, D, 0),
9348   date_time_value(date, D, Date).
9349Date = date(2007, 1, 30)
9350\end{code}
9351
9352When computing a time stamp from a local time specification, the UTC
9353offset (arg~7), TZ (arg~8) and DST (arg~9) argument may be left unbound
9354and are unified with the proper information. The example below, executed
9355in Amsterdam, illustrates this behaviour. On the 25th of March at 01:00,
9356DST does not apply. At 02.00, the clock is advanced by one hour and thus
9357both 02:00 and 03:00 represent the same time stamp.
9358
9359\begin{code}
93601 ?- date_time_stamp(date(2012,3,25,1,0,0,UTCOff,TZ,DST),
9361		     Stamp).
9362UTCOff = -3600,
9363TZ = 'CET',
9364DST = false,
9365Stamp = 1332633600.0.
9366
93672 ?- date_time_stamp(date(2012,3,25,2,0,0,UTCOff,TZ,DST),
9368		     Stamp).
9369UTCOff = -7200,
9370TZ = 'CEST',
9371DST = true,
9372Stamp = 1332637200.0.
9373
93743 ?- date_time_stamp(date(2012,3,25,3,0,0,UTCOff,TZ,DST),
9375		     Stamp).
9376UTCOff = -7200,
9377TZ = 'CEST',
9378DST = true,
9379Stamp = 1332637200.0.
9380\end{code}
9381
9382Note that DST and offset calculation are based on the POSIX function
9383mktime().  If mktime() returns an error, a representation_error
9384\const{dst} is generated.
9385
9386    \predicate{date_time_value}{3}{?Key, +DateTime, ?Value}
9387Extract values from a {date}/9 term.  Provided keys are:
9388
9389\begin{center}
9390\begin{tabular}{ll}
9391\hline
9392\bf key & \bf value \\
9393\hline
9394\const{year}	&  Calendar year as an integer \\
9395\const{month}	&  Calendar month as an integer 1..12 \\
9396\const{day}	&  Calendar day as an integer 1..31 \\
9397\const{hour}	&  Clock hour as an integer 0..23 \\
9398\const{minute}	&  Clock minute as an integer 0..59 \\
9399\const{second}	&  Clock second as a float 0.0..60.0 \\
9400\const{utc_offset}	&  Offset to UTC in seconds (positive is west) \\
9401\const{time_zone}	&  Name of timezone; fails if unknown \\
9402\const{daylight_saving}	&  Bool \const(true) if dst is in effect \\
9403\const{date}	&  Term \term{date}{Y,M,D} \\
9404\const{time}	&  Term \term{time}{H,M,S} \\
9405\hline
9406\end{tabular}
9407\end{center}
9408
9409    \predicate{format_time}{3}{+Out, +Format, +StampOrDateTime}
9410Modelled after POSIX strftime(), using GNU extensions.  \arg{Out}
9411is a destination as specified with with_output_to/2.  \arg{Format}
9412is an atom or string with the following conversions.  Conversions
9413start with a percent (\%) character.%
9414	\footnote{Descriptions taken from Linux Programmer's Manual}
9415\arg{StampOrDateTime} is either a numeric time-stamp, a term
9416\term{date}{Y,M,D,H,M,S,O,TZ,DST} or a term \term{date}{Y,M,D}.
9417
9418\begin{itemize}
9419    \fmtchar{a}
9420The abbreviated weekday name according to the current locale.  Use
9421format_time/4 for POSIX locale.
9422    \fmtchar{A}
9423The full weekday name according to the current locale.   Use
9424format_time/4 for POSIX locale.
9425    \fmtchar{b}
9426The abbreviated month name according to the current locale.  Use
9427format_time/4 for POSIX locale.
9428    \fmtchar{B}
9429The full month name according to the current locale.  Use
9430format_time/4 for POSIX locale.
9431    \fmtchar{c}
9432The  preferred  date  and  time  representation  for the current
9433locale.
9434    \fmtchar{C}
9435The century number ({year}/100) as a 2-digit integer.
9436    \fmtchar{d}
9437The day of the month as a decimal number (range 01 to 31).
9438    \fmtchar{D}
9439Equivalent to \%m/\%d/\%y. (For Americans only. Americans should
9440note that in other countries \%d/\%m/\%y is rather common. This means
9441that in an international context this format is ambiguous and should not
9442be used.)
9443    \fmtchar{e}
9444Like \%d, the day of the month as a decimal number, but a leading
9445zero is replaced by a space.
9446    \fmtchar{E}
9447Modifier.  Not implemented.
9448    \fmtchar{f}
9449Number of microseconds.  The \const{f} can be prefixed by an integer
9450to print the desired number of digits.  E.g., \const{\%3f} prints
9451milliseconds.  This format is not covered by any standard, but
9452available with different format specifiers in various incarnations
9453of the strftime() function.
9454    \fmtchar{F}
9455Equivalent to \%Y-\%m-\%d (the ISO 8601 date format).
9456    \fmtchar{g}
9457Like \%G, but without century, i.e., with a 2-digit year (00-99).
9458    \fmtchar{G}
9459The ISO 8601 year with century as a decimal number. The 4-digit year
9460corresponding to the ISO week number (see \%V). This has the same format
9461and value as \%y, except that if the ISO week number belongs to the
9462previous or next year, that year is used instead.
9463    \fmtchar{V}
9464The ISO 8601:1988 week number of the current year as a decimal number,
9465range 01 to 53, where week 1 is the first week that has at least 4 days
9466in the current year, and with Monday as the first day of the week. See
9467also \%U and \%W.
9468    \fmtchar{h}
9469Equivalent to \%b.
9470    \fmtchar{H}
9471The  hour as a decimal number using a 24-hour clock (range 00 to 23).
9472    \fmtchar{I}
9473The hour as a decimal number using a 12-hour clock (range 01  to 12).
9474    \fmtchar{j}
9475The day of the year as a decimal number (range 001 to 366).
9476    \fmtchar{k}
9477The hour (24-hour clock) as a decimal number (range 0 to 23); single
9478digits are preceded by a blank. (See also \%H.)
9479    \fmtchar{l}
9480The hour (12-hour clock) as a decimal number (range  1  to  12);
9481single digits are preceded by a blank. (See also \%I.)
9482    \fmtchar{m}
9483The month as a decimal number (range 01 to 12).
9484    \fmtchar{M}
9485The minute as a decimal number (range 00 to 59).
9486    \fmtchar{n}
9487A newline character.
9488    \fmtchar{O}
9489Modifier to select locale-specific output.  Not implemented.
9490    \fmtchar{p}
9491Either `AM' or `PM' according to the given time value, or the
9492corresponding strings for the current locale. Noon is treated as `pm'
9493and midnight as `am'.\footnote{Despite the above claim, some locales
9494yield \const{am} or \const{pm} in lower case.}
9495    \fmtchar{P}
9496Like \%p but in lowercase: `am' or `pm' or a corresponding string
9497for the current locale.
9498    \fmtchar{r}
9499The time in a.m.\ or p.m.\ notation. In the POSIX locale this is
9500equivalent to `\%I:\%M:\%S \%p'.
9501    \fmtchar{R}
9502The time in 24-hour notation (\%H:\%M).  For a version including the
9503seconds, see \%T below.
9504    \fmtchar{s}
9505The number of seconds since the Epoch,  i.e.,  since  1970-01-01
950600:00:00 UTC.
9507    \fmtchar{S}
9508The  second as a decimal number (range 00 to 60).  (The range is
9509up to 60 to allow for occasional leap seconds.)
9510    \fmtchar{t}
9511A tab character.
9512    \fmtchar{T}
9513The time in 24-hour notation (\%H:\%M:\%S).
9514    \fmtchar{u}
9515The day of the week as a decimal, range 1 to 7, Monday being  1.
9516See also \%w.
9517    \fmtchar{U}
9518The week number of the current year as a decimal number, range 00 to 53,
9519starting with the first Sunday as the first day of week 01. See also \%V
9520and \%W.
9521    \fmtchar{w}
9522The day of the week as a decimal, range 0 to 6, Sunday being  0.
9523See also \%u.
9524    \fmtchar{W}
9525The week number of the current year as a decimal number, range 00 to 53,
9526starting with the first Monday as the first day of week 01.
9527    \fmtchar{x}
9528The preferred date representation for the current locale without
9529the time.
9530    \fmtchar{X}
9531The preferred time representation for the current locale without
9532the date.
9533    \fmtchar{y}
9534The year as a decimal number without a century (range 00 to 99).
9535    \fmtchar{Y}
9536The year as a decimal number including the century.
9537    \fmtchar{z}
9538The timezone as hour offset from GMT using the format HHmm. Required to
9539emit RFC822-conforming dates (using
9540\texttt{'\%a,~\%d~\%b~\%Y~\%T~\%z'}). Our implementation supports
9541\texttt{\%:z}, which modifies the output to HH:mm as required by
9542XML-Schema. Note that both notations are valid in ISO 8601. The
9543sequence \texttt{\%:z} is compatible to the GNU	date(1) command.
9544    \fmtchar{Z}
9545The timezone or name or abbreviation.
9546    \fmtchar{+}
9547The date and time in date(1) format.
9548    \fmtchar{\%}
9549A literal `\%' character.
9550\end{itemize}
9551
9552The table below gives some format strings for popular time
9553representations.  RFC1123 is used by HTTP.  The full implementation of
9554http_timestamp/2 as available from \pllib{http/http_header} is here.
9555
9556\begin{code}
9557http_timestamp(Time, Atom) :-
9558	stamp_date_time(Time, Date, 'UTC'),
9559	format_time(atom(Atom),
9560		    '%a, %d %b %Y %T GMT',
9561		    Date, posix).
9562\end{code}
9563
9564
9565\begin{center}
9566\begin{tabular}{ll}
9567\hline
9568\textbf{Standard} & \textbf{Format string} \\
9569\hline
9570\textbf{xsd} & \texttt{'\%FT\%T\%:z'} \\
9571\textbf{ISO8601} & \texttt{'\%FT\%T\%z'} \\
9572\textbf{RFC822} & \texttt{'\%a, \%d \%b \%Y \%T \%z'} \\
9573\textbf{RFC1123} & \texttt{'\%a, \%d \%b \%Y \%T GMT'} \\
9574\hline
9575\end{tabular}
9576\end{center}
9577
9578
9579    \predicate{format_time}{4}{+Out, +Format, +StampOrDateTime, +Locale}
9580Format time given a specified \arg{Locale}. This predicate is a
9581work-around for lacking proper portable and thread-safe time and locale
9582handling in current C libraries.  In its current implementation the only
9583value allowed for \arg{Locale} is \const{posix}, which currently only
9584modifies the behaviour of the \chr{a}, \chr{A}, \chr{b} and \chr{B}
9585format specifiers.  The predicate is used to be able to emit POSIX
9586locale week and month names for emitting standardised time-stamps
9587such as RFC1123.
9588
9589    \predicate{parse_time}{2}{+Text, -Stamp}
9590Same as \term{parse_time}{Text, _Format, Stamp}.  See parse_time/3.
9591
9592    \predicate{parse_time}{3}{+Text, ?Format, -Stamp}
9593Parse a textual time representation, producing a time-stamp.  Supported
9594formats for \arg{Text} are in the table below.  If the format is known,
9595it may be given to reduce parse time and avoid ambiguities.  Otherwise,
9596\arg{Format} is unified with the format encountered.
9597
9598\begin{center}
9599\begin{tabular}{|l|l|}
9600\hline
9601\bf Name & \bf Example \\
9602\hline
9603rfc_1123 & \tt Fri, 08 Dec 2006 15:29:44 GMT \\
9604         & \tt Fri, 08 Dec 2006 15:29:44 +0000 \\
9605\hline
9606iso_8601 & \tt 2006-12-08T17:29:44+02:00 \\
9607         & \tt 20061208T172944+0200 \\
9608         & \tt 2006-12-08T15:29Z \\
9609         & \tt 2006-12-08 \\
9610         & \tt 20061208 \\
9611         & \tt 2006-12 \\
9612         & \tt 2006-W49-5 \\
9613         & \tt 2006-342 \\
9614\hline
9615\end{tabular}
9616\end{center}
9617
9618    \predicate{day_of_the_week}{2}{+Date,-DayOfTheWeek}
9619Computes the day of the week for a given date.
9620\exam{\arg{Date} = date(\arg{Year},\arg{Month},\arg{Day})}.
9621Days of the week are numbered from one to seven: Monday = 1, Tuesday =
96222, \ldots, Sunday = 7.
9623\end{description}
9624
9625\subsection{Controlling the \program{swipl-win.exe} console window}
9626\label{sec:plwin}
9627
9628The Windows executable \program{swipl-win.exe} console has a number of
9629predicates to control the appearance of the console. Being totally
9630non-portable, we do not advise using it for your own application, but
9631use XPCE or another portable GUI platform instead. We give the
9632predicates for reference here.
9633
9634\begin{description}
9635    \predicate{window_title}{2}{-Old, +New}
9636Unify \arg{Old} with the title displayed in the console and change the
9637title to \arg{New}.%
9638	\bug{This predicate should have been called
9639	\const{win_window_title} for consistent naming.}
9640
9641    \predicate{win_window_pos}{1}{+ListOfOptions}
9642Interface to the MS-Windows SetWindowPos() function, controlling
9643size, position and stacking order of the window.  \arg{ListOfOptions}
9644is a list that may hold any number of the terms below:
9645
9646\begin{description}
9647    \termitem{size}{W, H}
9648Change the size of the window.  \arg{W} and \arg{H} are expressed
9649in character units.
9650    \termitem{position}{X, Y}
9651Change the top-left corner of the window.  The values are expressed
9652in pixel units.
9653    \termitem{zorder}{ZOrder}
9654Change the location in the window stacking order.  Values are
9655\const{bottom}, \const{top}, \const{topmost} and \const{notopmost}.
9656\emph{Topmost} windows are displayed above all other windows.
9657    \termitem{show}{Bool}
9658If \const{true}, show the window, if \const{false} hide the window.
9659    \termitem{activate}{}
9660If present, activate the window.
9661\end{description}
9662
9663    \predicate{win_window_color}{2}{+Which, +RGB}
9664Change the color of the console window.  \arg{Which} is one of
9665\const{foreground}, \const{background}, \const{selection_foreground} or
9666\const{selection_background}. \arg{RGB} is a term
9667\term{rgb}{Red,Green,Blue} where the components are values between 0
9668and 255. The defaults are established using the Windows API
9669GetSysColor().
9670
9671    \predicate{win_has_menu}{0}{}
9672True if win_insert_menu/2 and win_insert_menu_item/4 are present.
9673
9674    \predicate{win_insert_menu}{2}{+Label, +Before}
9675Insert a new entry (pulldown) in the menu.  If the menu already contains
9676this entry, nothing is done.  The \arg{Label} is the label and, using the
9677Windows convention, a letter prefixed with \const{\&} is underlined and
9678defines the associated accelerator key. \arg{Before} is the label before
9679which this one must be inserted. Using \chr{-} adds the new entry at the
9680end (right).  For example, the call below adds an {\sf Application}
9681entry just before the {\sf Help} menu.
9682
9683\begin{code}
9684win_insert_menu('&Application', '&Help')
9685\end{code}
9686
9687    \predicate{win_insert_menu_item}{4}{+Pulldown, +Label, +Before, :Goal}
9688Add an item to the named \arg{Pulldown} menu. \arg{Label} and
9689\arg{Before} are handled as in win_insert_menu/2, but the label \chr{-}
9690inserts a \jargon{separator}.  \arg{Goal} is called if the user selects
9691the item.
9692\end{description}
9693
9694
9695\section{File System Interaction}	\label{sec:files}
9696
9697\begin{description}
9698    \predicate{access_file}{2}{+File, +Mode}
9699True if \arg{File} exists and can be accessed by this Prolog
9700process under mode \arg{Mode}.  \arg{Mode} is one of the atoms
9701\const{read}, \const{write}, \const{append}, \const{exist}, \const{none} or
9702\const{execute}. \arg{File} may also be the name of a directory. Fails
9703silently otherwise.  \exam{access_file(File, none)} simply succeeds
9704without testing anything.
9705
9706If \arg{Mode} is \const{write} or \const{append}, this predicate also succeeds
9707if the file does not exist and the user has write access to the
9708directory of the specified location.
9709
9710The behaviour is backed up by the POSIX access() API. The Windows
9711replacement (_waccess()) returns incorrect results because it does not
9712consider ACLs (Access Control Lists). The Prolog flag
9713\prologflag{win_file_access_check} may be used to control the level of
9714checking performed by Prolog. Please note that checking access never
9715provides a guarantee that a subsequent open succeeds without errors due
9716to inherent concurrency in file operations. It is generally more robust
9717to try and open the file and handle possible exceptions. See open/4 and
9718catch/3.
9719
9720    \predicate{exists_file}{1}{+File}
9721True if \arg{File} exists and is a \jargon{regular} file. This does not
9722imply the user has read or write access to the file. See also
9723exists_directory/1 and access_file/2.
9724
9725    \predicate{file_directory_name}{2}{+File, -Directory}
9726Extracts the directory part of \arg{File}. This predicate removes the
9727longest match for the regular expression \verb|/*[^/]*/*$|. If the
9728result is empty it binds \arg{Directory} to \const{/} if the first
9729character of \arg{File} is \const{/} and \const{.} otherwise. The
9730behaviour is consistent with the POSIX \program{dirname}
9731program.\footnote{Before SWI-Prolog 7.7.13 trailing \const{/} where
9732\emph{not} removed, translation \exam{/a/b/} into \exam{/a/b}. Volker
9733Wysk pointed at this incorrect behaviour.}
9734
9735See also directory_file_path/3 from \pllib{filesex}. The system ensures
9736that for every valid \arg{Path} using the Prolog (POSIX) directory
9737separators, following is true on systems with a sound implementation of
9738same_file/2.\footnote{On some systems, \arg{Path} and \arg{Path2} refer
9739to the same entry in the file system, but same_file/2 may fail.} See
9740also prolog_to_os_filename/2.
9741
9742\begin{code}
9743	...,
9744	file_directory_name(Path, Dir),
9745	file_base_name(Path, File),
9746	directory_file_path(Dir, File, Path2),
9747	same_file(Path, Path2).
9748\end{code}
9749
9750    \predicate{file_base_name}{2}{+Path, -File}
9751Extracts the file name part from a path. Similar to
9752file_directory_name/2 the extraction is based on the regex
9753\verb|/*([^/]*)/*$|, now capturing the non-\const{/} segment. If the
9754segment is empty it unifies \arg{File} with \const{/} if \arg{Path}
9755starts with \const{/} and the empty atom (\verb$''$) otherwise. The
9756behaviour is consistent with the POSIX \program{basename}
9757program.\footnote{Before SWI-Prolog 7.7.13, if arg{Path} ended with
9758a \const{/} \arg{File} was unified with the empty atom.}
9759
9760    \predicate{same_file}{2}{+File1, +File2}
9761True if both filenames refer to the same physical file. That is, if
9762\arg{File1} and \arg{File2} are the same string or both names exist and
9763point to the same file (due to hard or symbolic links and/or relative
9764vs.\ absolute paths). On systems that provide stat() with meaningful
9765values for \const{st_dev} and \const{st_inode}, same_file/2 is
9766implemented by comparing the device and inode identifiers. On Windows,
9767same_file/2 compares the strings returned by the GetFullPathName()
9768system call.
9769
9770    \predicate{exists_directory}{1}{+Directory}
9771True if \arg{Directory} exists and is a directory. This does not
9772imply the user has read, search or write permission for the
9773directory.
9774
9775    \predicate{delete_file}{1}{+File}
9776Remove \arg{File} from the file system.
9777
9778    \predicate{rename_file}{2}{+File1, +File2}
9779Rename \arg{File1} as \arg{File2}. The semantics is compatible to the
9780POSIX semantics of the rename() system call as far as the operating
9781system allows. Notably, if \arg{File2} exists, the operation succeeds
9782(except for possible permission errors) and is \jargon{atomic} (meaning
9783there is no window where \arg{File2} does not exist).
9784
9785    \predicate{size_file}{2}{+File, -Size}
9786Unify \arg{Size} with the size of \arg{File} in bytes.
9787
9788    \predicate{time_file}{2}{+File, -Time}
9789Unify the last modification time of \arg{File} with \arg{Time}.
9790\arg{Time} is a floating point number expressing the seconds elapsed
9791since Jan~1, 1970. See also convert_time/[2,8] and get_time/1.
9792
9793    \predicate{absolute_file_name}{2}{+File, -Absolute}
9794Expand a local filename into an absolute path. The absolute path is
9795canonicalised: references to \file{.} and \file{..} are deleted. This
9796predicate ensures that expanding a filename returns the same
9797absolute path regardless of how the file is addressed. SWI-Prolog uses
9798absolute filenames to register source files independent of the current
9799working directory. See also absolute_file_name/3 and expand_file_name/2.
9800
9801    \predicate{absolute_file_name}{3}{+Spec, -Absolute, +Options}
9802
9803Convert the given file specification into an absolute path. \arg{Spec}
9804is a term Alias(Relative) (e.g., \verb$(library(lists)$), a relative
9805filename or an absolute filename. The primary intention of this
9806predicate is to resolve files specified as Alias(Relative). This
9807predicate \emph{only returns non-directories}, unless the option
9808\term{file_type}{directory} is specified. \arg{Option} is a list of
9809options to guide the conversion:
9810
9811\begin{description}
9812    \termitem{extensions}{ListOfExtensions}
9813List of file extensions to try.  Default is \const{''}.  For each
9814extension, absolute_file_name/3 will first add the extension and then
9815verify the conditions imposed by the other options.  If the condition
9816fails, the next extension on the list is tried.  Extensions may be
9817specified both as \fileext{ext} or plain \const{ext}.
9818
9819    \termitem{relative_to}{+FileOrDir}
9820Resolve the path relative to the given directory or the directory
9821holding the given file.  Without this option, paths are resolved
9822relative to the working directory (see working_directory/2) or,
9823if \arg{Spec} is atomic and absolute_file_name/[2,3] is executed
9824in a directive, it uses the current source file as reference.
9825
9826    \termitem{access}{Mode}
9827Imposes the condition access_file(\arg{File}, \arg{Mode}).  \arg{Mode}
9828is one of \const{read}, \const{write}, \const{append},
9829\const{execute}, \const{exist} or \const{none}. See also access_file/2.
9830
9831    \termitem{file_type}{Type}
9832Defines extensions. Current mapping: \const{txt} implies \const{['']},
9833\const{prolog} implies \const{['.pl', '']}, \const{executable} implies
9834\const{['.so', '']} and \const{qlf} implies \const{['.qlf', '']}. The
9835\arg{Type} \const{directory} implies \const{['']} and causes this
9836predicate to generate (only) directories. The file type \const{source}
9837is an alias for \const{prolog} for compatibility with SICStus Prolog.
9838See also prolog_file_type/2.
9839
9840    \termitem{file_errors}{fail/error}
9841If \const{error} (default), throw an \const{existence_error} exception
9842if the file cannot be found.  If \const{fail}, stay silent.%
9843	\footnote{Silent operation was the default up to version 3.2.6.}
9844
9845    \termitem{solutions}{first/all}
9846If \const{first} (default), the predicate leaves no choice point.
9847Otherwise a choice point will be left and backtracking may yield
9848more solutions.
9849
9850    \termitem{expand}{Boolean}
9851If \const{true} (default is \const{false}) and \arg{Spec} is atomic,
9852call expand_file_name/2 followed by member/2 on \arg{Spec} before
9853proceeding.  This is a SWI-Prolog extension intended to minimise
9854porting effort after SWI-Prolog stopped expanding environment
9855variables and the \chr{~} by default.  This option should be
9856considered deprecated.  In particular the use of \jargon{wildcard}
9857patterns such as \exam{*} should be avoided.
9858\end{description}
9859
9860The Prolog flag \prologflag{verbose_file_search} can be set to \const{true}
9861to help debugging Prolog's search for files.
9862
9863This predicate is derived from Quintus Prolog. In Quintus Prolog, the
9864argument order was \term{absolute_file_name}{+Spec, +Options, -Path}.
9865The argument order has been changed for compatibility with ISO and
9866SICStus.  The Quintus argument order is still accepted.
9867
9868    \predicate{is_absolute_file_name}{1}{+File}
9869True if \arg{File} specifies an absolute path name.  On Unix systems,
9870this implies the path starts with a `/'.  For Microsoft-based systems
9871this implies the path starts with \file{<letter>:}. This predicate is
9872intended to provide platform-independent checking for absolute paths.
9873See also absolute_file_name/2 and prolog_to_os_filename/2.
9874
9875    \predicate{file_name_extension}{3}{?Base, ?Extension, ?Name}
9876This predicate is used to add, remove or test filename extensions. The
9877main reason for its introduction is to deal with different filename
9878properties in a portable manner.  If the file system is case-insensitive,
9879testing for an extension will also be done case-insensitive. \arg{Extension} may be specified with or without a leading dot (\chr{.}).
9880If an \arg{Extension} is generated, it will not have a leading dot.
9881
9882    \predicate{directory_files}{2}{+Directory, -Entries}
9883Unify \arg{Entries} with a list of entries in \arg{Directory}.
9884Each member of \arg{Entries} is an atom denoting an entry relative
9885to \arg{Directory}. \arg{Entries} contains all entries, including hidden
9886files and, if supplied by the OS, the special entries \const{.} and
9887\const{..}.  See also expand_file_name/2.\footnote{This predicate should
9888be considered a misnomer because it returns entries rather than files.
9889We stick to this name for compatibility with, e.g., SICStus, Ciao and
9890YAP.}
9891
9892    \predicate{expand_file_name}{2}{+WildCard, -List}
9893Unify \arg{List} with a sorted list of files or directories matching
9894\arg{WildCard}. The normal Unix wildcard constructs `\const{?}',
9895`\const{*}', `\const{[\ldots]}' and `\const{\{\ldots\}}' are recognised.
9896The interpretation of `\const{\{\ldots\}}' is slightly
9897different from the C shell (csh(1)). The comma-separated argument can be
9898arbitrary patterns, including `\const{\{\ldots\}}' patterns. The empty
9899pattern is legal as well: `\file{\{.pl,\}}' matches either `\file{.pl}'
9900or the empty string.
9901
9902If the pattern contains wildcard characters, only existing files and
9903directories are returned. Expanding a `pattern' without wildcard
9904characters returns the argument, regardless of whether or not it exists.
9905
9906Before expanding wildcards, the construct \file{\$\arg{var}} is expanded
9907to the value of the environment variable \var{var}, and a possible
9908leading \verb$~$ character is expanded to the user's home directory.%
9909    \footnote{On Windows, the home directory is determined as follows:
9910	      if the environment variable \env{HOME} exists, this is
9911	      used.  If the variables \env{HOMEDRIVE} and \env{HOMEPATH}
9912	      exist (Windows-NT), these are used.  At initialisation,
9913	      the system will set the environment variable \env{HOME}
9914	      to point to the SWI-Prolog home directory if neither
9915	      \env{HOME} nor \env{HOMEPATH} and \env{HOMEDRIVE} are
9916	      defined.}
9917
9918    \predicate{prolog_to_os_filename}{2}{?PrologPath, ?OsPath}
9919Convert between the internal Prolog path name conventions and the
9920operating system path name conventions. The internal conventions follow
9921the POSIX standard, which implies that this predicate is equivalent
9922to =/2 (unify) on POSIX (e.g., Unix) systems. On Windows systems it
9923changes the directory separator from \chr{\} into \chr{/}.
9924
9925    \predicate{read_link}{3}{+File, -Link, -Target}
9926If \arg{File} points to a symbolic link, unify \arg{Link} with the
9927value of the link and \arg{Target} to the file the link is pointing to.
9928\arg{Target} points to a file, directory or non-existing entry in the
9929file system, but never to a link.  Fails if \arg{File} is not a link.
9930Fails always on systems that do not support symbolic links.
9931
9932    \predicate[deprecated]{tmp_file}{2}{+Base, -TmpName}
9933Create a name for a temporary file. \arg{Base} is an identifier for the
9934category of file. The \arg{TmpName} is guaranteed to be unique. If the
9935system halts, it will automatically remove all created temporary files.
9936\arg{Base} is used as part of the final filename.  Portable applications
9937should limit themselves to alphanumeric characters.
9938
9939Because it is possible to guess the generated filename, attackers may
9940create the filesystem entry as a link and possibly create a security
9941issue.  New code should use tmp_file_stream/3.
9942
9943    \predicate{tmp_file_stream}{3}{+Encoding, -FileName, -Stream}
9944\nodescription
9945    \predicate{tmp_file_stream}{3}{-FileName, -Stream, +Options}
9946Create a temporary filename \arg{FileName}, open it for writing and
9947unify \arg{Stream} with the output stream. If the OS supports it, the
9948created file is only accessible to the current user and the file is
9949created using the open()-flag \const{O_EXCL}, which guarantees that the
9950file did not exist before this call. The following options are
9951processed:
9952
9953\begin{description}
9954    \termitem{encoding}{+Encoding}
9955Encoding of \arg{Stream}.  Default is the value of the Prolog flag
9956\prologflag{encoding}.  The value \const{binary} opens the file in
9957binary mode.
9958    \termitem{extension}{+Ext}
9959Ensure the created file has the given extension.  Default is no
9960extension.  Using an extension may be necessary to run external
9961programs on the file.
9962\end{description}
9963
9964This predicate is a safe replacement of tmp_file/2. Note that in those
9965cases where the temporary file is needed to store output from an
9966external command, the file must be closed first. E.g., the following
9967downloads a file from a URL to a temporary file and opens the file for
9968reading (on Unix systems you can delete the file for cleanup after
9969opening it for reading):
9970
9971\begin{code}
9972open_url(URL, In) :-
9973	tmp_file_stream(text, File, Stream),
9974	close(Stream),
9975	process_create(curl, ['-o', File, URL], []),
9976	open(File, read, In),
9977	delete_file(File).		% Unix-only
9978\end{code}
9979
9980Temporary files created using this call are removed if the Prolog
9981process terminates \emph{gracefully}. Calling delete_file/1 using
9982\arg{FileName} removes the file and removes the entry from the
9983administration of files-to-be-deleted.
9984
9985    \predicate{make_directory}{1}{+Directory}
9986Create a new directory (folder) on the filesystem.  Raises an exception
9987on failure.  On Unix systems, the directory is created with default
9988permissions (defined by the process \jargon{umask} setting).
9989
9990    \predicate{delete_directory}{1}{+Directory}
9991Delete directory (folder) from the filesystem.  Raises an exception on
9992failure.  Please note that in general it will not be possible to delete
9993a non-empty directory.
9994
9995    \predicate{working_directory}{2}{-Old, +New}
9996Unify \arg{Old} with an absolute path to the current working directory
9997and change working directory to \arg{New}.  Use the pattern
9998\term{working_directory}{CWD, CWD} to get the current directory.  See
9999also absolute_file_name/2 and chdir/1.%
10000	\bug{Some of the file I/O predicates use local filenames.
10001	     Changing directory while file-bound streams are open causes
10002	     wrong results on telling/1, seeing/1 and current_stream/3.}
10003Note that the working directory is shared between all threads.
10004
10005    \predicate{chdir}{1}{+Path}
10006Compatibility predicate.  New code should use working_directory/2.
10007\end{description}
10008
10009\section{User Top-level Manipulation}	\label{sec:toplevel}
10010
10011\begin{description}
10012    \predicate{break}{0}{}
10013Recursively start a new Prolog top level. This Prolog top level shares
10014everything from the environment it was started in. Debugging is switched
10015off on entering a break and restored on leaving one. The break
10016environment is terminated by typing the system's \mbox{end-of-file}
10017character (control-D). If that is somehow not functional, the term
10018\exam{end_of_file.} can be entered to return from the break environment.
10019If the \argoption{-t}{toplevel} command line option is given, this goal
10020is started instead of entering the default interactive top level
10021(prolog/0).
10022
10023Notably the gui based versions (\program{swipl-win} on Windows and
10024MacOS) provide the menu \textsf{Run/New thread} that opens a new
10025toplevel that runs concurrently with the initial toplevel. The
10026concurrent toplevel can be used to examine the program, in particular
10027global dynamic predicates. It can not access \jargon{global variables}
10028or thread-local dynamic predicates (see thread_local/1) of the main
10029thread.
10030
10031    \predicate{abort}{0}{}
10032Abort the Prolog execution and restart the top level. If the
10033\argoption{-t}{toplevel} command line option is given, this goal is
10034restarted instead of entering the default interactive top level.
10035
10036Aborting is implemented by throwing the reserved exception
10037\verb='$aborted'=. This exception can be caught using catch/3, but the
10038recovery goal is wrapped with a predicate that prunes the choice points
10039of the recovery goal (i.e., as once/1) and re-throws the exception.
10040This is illustrated in the example below, where we press control-C
10041and `a'.  See also \secref{urgentexceptions}.
10042
10043\begin{code}
10044?- catch((repeat,fail), E, true).
10045^CAction (h for help) ? abort
10046% Execution Aborted
10047\end{code}
10048
10049    \predicate[ISO]{halt}{0}{}
10050Terminate Prolog execution.  This is the same as \term{halt}{0}. See
10051halt/1 for details.
10052
10053    \predicate[ISO]{halt}{1}{+Status}
10054Terminate Prolog execution with \arg{Status}. This predicate calls
10055PL_halt() which preforms the following steps:
10056
10057    \begin{enumerate}
10058    \item Set the Prolog flag \prologflag{exit_status} to \arg{Status}.
10059
10060    \item Call all hooks registered using at_halt/1.  If \arg{Status}
10061    equals 0 (zero), any of these hooks calls cancel_halt/1,
10062    termination is cancelled.
10063
10064    \item Call all hooks registered using PL_at_halt().  In the future,
10065    if any of these hooks returns non-zero, termination will be
10066    cancelled.  Currently, this only prints a warning.
10067
10068    \item Perform the following system cleanup actions:
10069
10070    \begin{itemize}
10071    \item Cancel all threads, calling thread_at_exit/1 registered
10072          termination hooks.  Threads not responding within 1 second
10073	  are cancelled forcefully.
10074    \item Flush I/O and close all streams except for standard I/O.
10075    \item Reset the terminal if its properties were changed.
10076    \item Remove temporary files and incomplete compilation output.
10077    \item Reclaim memory.
10078    \end{itemize}
10079
10080    \item Call exit(Status) to terminate the process
10081    \end{enumerate}
10082
10083halt/1 has been extended in SWI-Prolog to accept the arg \const{abort}.
10084This performs as halt/1 above except that:
10085
10086    \begin{itemize}
10087    \item Termination cannot be cancelled with cancel_halt/1.
10088    \item abort() is called instead of exit(Status).
10089    \end{itemize}
10090
10091    \predicate{prolog}{0}{}
10092This goal starts the default interactive top level. Queries are read
10093from the stream \const{user_input}. See also the Prolog flag
10094\prologflag{history}. The prolog/0 predicate is terminated (succeeds) by
10095typing the end-of-file character (typically control-D).
10096\end{description}
10097
10098The following two hooks allow for expanding queries and handling the
10099result of a query.  These hooks are used by the top level variable
10100expansion mechanism described in \secref{topvars}.
10101
10102\begin{description}
10103    \predicate{expand_query}{4}{+Query, -Expanded, +Bindings, -ExpandedBindings}
10104Hook in module \const{user}, normally not defined.  \arg{Query} and
10105\arg{Bindings} represents the query read from the user and the names
10106of the free variables as obtained using read_term/3.  If this predicate
10107succeeds, it should bind \arg{Expanded} and \arg{ExpandedBindings} to
10108the query and bindings to be executed by the top level.  This predicate
10109is used by the top level (prolog/0).  See also expand_answer/2 and
10110term_expansion/2.
10111
10112    \predicate{expand_answer}{2}{+Bindings, -ExpandedBindings}
10113Hook in
10114module \const{user}, normally not defined. Expand the result of a
10115successfully executed top-level query. \arg{Bindings} is the query
10116$<Name>=<Value>$ binding list from the query. \arg{ExpandedBindings}
10117must be unified with the bindings the top level should print.
10118\end{description}
10119
10120\section{Creating a Protocol of the User Interaction}	\label{sec:protocol}
10121
10122SWI-Prolog offers the possibility to log the interaction with the user
10123on a file.%
10124    \footnote{A similar facility was added to Edinburgh C-Prolog by
10125              Wouter Jansweijer.}
10126All Prolog interaction, including warnings and tracer output, are written
10127to the protocol file.
10128
10129\begin{description}
10130    \predicate{protocol}{1}{+File}
10131Start protocolling on file \arg{File}. If there is already a protocol
10132file open, then close it first. If \arg{File} exists it is truncated.
10133    \predicate{protocola}{1}{+File}
10134Equivalent to protocol/1, but does not truncate the \arg{File} if it
10135exists.
10136    \predicate{noprotocol}{0}{}
10137Stop making a protocol of the user interaction.  Pending output is
10138flushed on the file.
10139    \predicate{protocolling}{1}{-File}
10140True if a protocol was started with protocol/1 or protocola/1 and
10141unifies \arg{File} with the current protocol output file.
10142\end{description}
10143
10144\section{Debugging and Tracing Programs}	\label{sec:debugger}
10145
10146This section is a reference to the debugger interaction predicates. A
10147more use-oriented overview of the debugger is in \secref{debugoverview}.
10148
10149If you have installed XPCE, you can use the graphical front-end of the
10150tracer.  This front-end is installed using the predicate guitracer/0.
10151
10152\begin{description}
10153    \predicate{trace}{0}{}
10154Start the tracer. trace/0 itself cannot be seen in the tracer.  Note that
10155the Prolog top level treats trace/0 special; it means `trace the next goal'.
10156    \predicate{tracing}{0}{}
10157True if the tracer is currently switched on.  tracing/0 itself cannot
10158be seen in the tracer.
10159    \predicate{notrace}{0}{}
10160Stop the tracer. notrace/0 itself cannot be seen in the tracer.
10161    \predicate{trace}{1}{+Pred}
10162Equivalent to \exam{trace(\arg{Pred}, +all)}.
10163    \predicate{trace}{2}{+Pred, +Ports}
10164Put a trace point on all predicates satisfying the predicate specification
10165\arg{Pred}. \arg{Ports} is a list of port names (\const{call},
10166\const{redo}, \const{exit}, \const{fail}). The atom \const{all} refers
10167to all ports. If the port is preceded by a \const{-} sign, the
10168trace point is cleared for the port. If it is preceded by a \const{+},
10169the trace point is set. Tracing a predicate is achieved by
10170\jargon{wrapping} the predicate using wrap_predicate/4.
10171
10172Each time a port (of the 4-port model) is passed that has a trace point
10173set, the goal is printed. Unlike trace/0, however, the execution is
10174continued without asking for further information. Examples:
10175
10176\begin{center}
10177\begin{tabular}{lp{3in}}
10178\exam{?- trace(hello).}          & Trace all ports of hello with any arity
10179                                   in any module. \\
10180\exam{?- trace({foo}/2, +fail).} & Trace failures of {foo}/2 in any module. \\
10181\exam{?- trace({bar}/1, -all).}  & Stop tracing {bar}/1.
10182\end{tabular}
10183\end{center}
10184
10185    \predicate{notrace}{1}{:Goal}
10186Call \arg{Goal}, but suspend the debugger while \arg{Goal} is executing.
10187The current implementation cuts the choice points of \arg{Goal} after
10188successful completion. See once/1.  Later implementations may have the
10189same semantics as call/1.
10190
10191    \predicate{debug}{0}{}
10192Start debugger. In debug mode, Prolog stops at spy and break points,
10193disables last-call optimisation and aggressive destruction of
10194choice points to make debugging information accessible.  Implemented
10195by the Prolog flag \prologflag{debug}.
10196
10197Note that the \const{min_free} parameter of all stacks is enlarged to
101988~K cells if debugging is switched off in order to avoid excessive GC. GC
10199complicates tracing because it renames the \textit{_<NNN>} variables
10200and replaces unreachable variables with the atom
10201\verb$<garbage_collected>$. Calling nodebug/0 does \emph{not} reset the
10202initial free-margin because several parts of the top level and debugger
10203disable debugging of system code regions.  See also set_prolog_stack/2.
10204
10205    \predicate{nodebug}{0}{}
10206Stop debugger.  Implemented by the Prolog flag \prologflag{debug}.  See
10207also debug/0.
10208
10209    \predicate{debugging}{0}{}
10210Print debug status and spy points on current output stream.  See also
10211the Prolog flag \prologflag{debug}.
10212    \predicate{spy}{1}{+Pred}
10213Put a spy point on all predicates meeting the predicate specification
10214\arg{Pred}. See \secref{listing}.
10215    \predicate{nospy}{1}{+Pred}
10216Remove spy point from all predicates meeting the predicate specification
10217\arg{Pred}.
10218    \predicate{nospyall}{0}{}
10219Remove all spy points from the entire program.
10220    \predicate{leash}{1}{?Ports}
10221Set/query leashing (ports which allow for user interaction). \arg{Ports} is
10222one of \arg{+Name}, \arg{-Name}, \arg{?Name} or a list of these.
10223\arg{+Name} enables leashing on that port, \arg{-Name} disables it and
10224\arg{?Name} succeeds or fails according to the current setting.
10225Recognised ports are \const{call}, \const{redo}, \const{exit}, \const{fail} and
10226\const{unify}. The special shorthand \const{all} refers to all ports,
10227\const{full} refers to all ports except for the unify port (default).
10228\const{half} refers to the \const{call}, \const{redo} and \const{fail}
10229port.
10230
10231    \predicate{visible}{1}{+Ports}
10232Set the ports shown by the debugger. See leash/1 for a description of
10233the \arg{Ports} specification. Default is \const{full}.
10234
10235    \predicate{unknown}{2}{-Old, +New}
10236Edinburgh-Prolog compatibility predicate, interfacing to the ISO Prolog
10237flag \prologflag{unknown}. Values are \const{trace} (meaning \const{error})
10238and \const{fail}. If the \prologflag{unknown} flag is set to
10239\const{warning}, unknown/2 reports the value as \const{trace}.
10240
10241    \predicate{style_check}{1}{+Spec}
10242Modify/query style checking options. \arg{Spec} is one of the terms
10243below or a list of these.
10244
10245\begin{itemize}
10246    \item +\arg{Style} enables a style check
10247    \item -\arg{Style} disables a style check
10248    \item ?(\arg{Style}) queries a style check (note the brackets).
10249	  If \arg{Style} is unbound, all active style check options
10250	  are returned on backtracking.
10251\end{itemize}
10252
10253Loading a file using load_files/2 or one of its derived predicates reset
10254the style checking options to their value before loading the file,
10255scoping the option to the remainder of the file and all files loaded
10256\emph{after} changing the style checking.
10257
10258\begin{description}
10259    \termitem{singleton}{true}
10260The predicate read_clause/3 (used by the compiler to read source code)
10261warns on variables appearing only once in a term (clause) which have a
10262name not starting with an underscore. See \secref{singleton} for details
10263on variable handling and warnings.
10264
10265    \termitem{no_effect}{true}
10266This warning is generated by the compiler for BIPs (built-in predicates)
10267that are inlined by the compiler and for which the compiler can prove
10268that they are meaningless.  An example is using \predref{==}{2} against
10269a not-yet-initialised variable as illustrated in the example below. This
10270comparison is always \const{false}.
10271
10272\begin{code}
10273always_false(X) :-
10274	X == Y,
10275	write(Y).
10276\end{code}
10277
10278    \termitem{var_branches}{false}
10279Verifies that if a variable is introduced in a branch and used
10280\emph{after} the branch, it is introduced in all branches. This code
10281aims at bugs following the skeleton below, where \term{p}{Next} may be
10282called with \arg{Next} unbound.
10283
10284\begin{code}
10285p(Arg) :-
10286	(  Cond
10287        -> Next = value1
10288        ;  true
10289	),
10290	p(Next).
10291\end{code}
10292
10293If a variable \arg{V} is intended to be left unbound, one can use
10294\exam{V=_}. This construct is removed by the compiler and thus has no
10295implications for the performance of your program.
10296
10297This check was suggested together with \jargon{semantic} singleton
10298checking. The SWI-Prolog libraries contain about a hundred clauses that
10299are triggered by this style check. Unlike semantic singleton analysis,
10300only a tiny fraction of these clauses proofed faulty. In most cases, the
10301branches failing to bind the variable fail or raise an exception or the
10302caller handles the case where the variable is unbound.  The status of
10303this style check is unclear. It might be removed in the future or it
10304might be enhanced with a deeper analysis to be more precise.
10305
10306    \termitem{discontiguous}{true}
10307Warn if the clauses for a predicate are not together in the same source file.
10308It is advised to disable the warning for discontiguous predicates using
10309the discontiguous/1 directive.
10310
10311    \termitem{charset}{false}
10312Warn on atoms and variable names holding non-ASCII characters that are
10313not quoted. See also \secref{processorcharset}.
10314\end{description}
10315\end{description}
10316
10317\section{Obtaining Runtime Statistics}	\label{sec:statistics}
10318
10319\begin{description}
10320    \predicate{statistics}{2}{+Key, -Value}
10321Unify system statistics determined by \arg{Key} with \arg{Value}. The
10322possible keys are given in the \tabref{statistics}.  This predicate
10323supports additional keys for compatibility reasons.  These keys are
10324described in \tabref{qpstatistics}.
10325
10326\begin{table}
10327\begin{center}
10328\begin{tabular}{|l|p{\linewidth-35mm}|}
10329\hline
10330\multicolumn{2}{|c|}{Native keys (times as float in seconds)} \\
10331\hline
10332agc		& Number of atom garbage collections performed \\
10333agc_gained	& Number of atoms removed \\
10334agc_time	& Time spent in atom garbage collections \\
10335atoms           & Total number of defined atoms \\
10336atom_space      & Bytes used to represent atoms \\
10337c_stack		& System (C-) stack limit.  0 if not known. \\
10338cgc		& Number of clause garbage collections performed \\
10339cgc_gained	& Number of clauses reclaimed \\
10340cgc_time	& Time spent in clause garbage collections \\
10341clauses         & Total number of clauses in the program \\
10342codes           & Total size of (virtual) executable code in words \\
10343cputime         & (User) {\sc cpu} time since thread was started in seconds \\
10344epoch		& Time stamp when thread was started \\
10345functors        & Total number of defined name/arity pairs \\
10346functor_space   & Bytes used to represent functors \\
10347global          & Allocated size of the global stack in bytes \\
10348globalused      & Number of bytes in use on the global stack \\
10349globallimit     & Size to which the global stack is allowed to grow \\
10350global_shifts	& Number of global stack expansions \\
10351heapused        & Bytes of heap in use by Prolog (0 if not maintained) \\
10352inferences      & Total number of passes via the call and redo ports
10353                  since Prolog was started \\
10354modules         & Total number of defined modules \\
10355local           & Allocated size of the local stack in bytes \\
10356local_shifts	& Number of local stack expansions \\
10357locallimit      & Size to which the local stack is allowed to grow \\
10358localused       & Number of bytes in use on the local stack \\
10359table_space_used& Amount of bytes in use by the thread's answer tables \\
10360trail           & Allocated size of the trail stack in bytes \\
10361trail_shifts	& Number of trail stack expansions \\
10362traillimit      & Size to which the trail stack is allowed to grow \\
10363trailused       & Number of bytes in use on the trail stack \\
10364shift_time	& Time spent in stack-shifts \\
10365stack		& Total memory in use for stacks in all threads \\
10366predicates	& Total number of predicates.  This includes predicates
10367		  that are undefined or not yet resolved. \\
10368indexes_created & Number of clause index tables creates. \\
10369indexes_destroyed & Number of clause index tables destroyed. \\
10370process_epoch	& Time stamp when Prolog was started \\
10371process_cputime & (User) {\sc cpu} time since Prolog was started in seconds \\
10372thread_cputime  & MT-version: Seconds CPU time used by \textbf{finished}
10373		  threads. The implementation requires non-portable
10374		  functionality.  Currently works on Linux, MacOSX,
10375		  Windows and probably some more. \\
10376threads		& MT-version: number of active threads \\
10377threads_created & MT-version: number of created threads \\
10378engines		& MT-version: number of existing engines \\
10379engines_created & MT-version: number of created engines \\
10380threads_peak	& MT-version: highest id handed out.  This is a fair but
10381		  possibly not 100\% accurate value for the highest
10382		  number of threads since the process was created. \\
10383\hline
10384\end{tabular}
10385\end{center}
10386    \caption{Keys for statistics/2. Space is expressed in bytes.
10387	     Time is expressed in seconds, represented as a
10388	     floating point number.}
10389    \label{tab:statistics}
10390\end{table}
10391
10392
10393\begin{table}
10394\begin{center}
10395\begin{tabular}{|l|p{\linewidth-35mm}|}
10396\hline
10397\multicolumn{2}{|c|}{Compatibility keys (times in milliseconds)} \\
10398\hline
10399runtime		& [ CPU time, CPU time since last ]
10400		  (milliseconds, excluding time spent in
10401		   garbage collection) \\
10402system_time	& [ System CPU time, System CPU time since last ]
10403		  (milliseconds)\\
10404real_time	& [ Wall time, Wall time since last ]
10405		  (integer seconds. See get_time/1) \\
10406walltime	& [ Wall time since start, Wall time since last]
10407		  (milliseconds, SICStus compatibility) \\
10408memory		& [ Total unshared data, free memory ]
10409		  (Used is based on \const{ru_idrss} from getrusage().
10410		   Free is based on \const{RLIMIT_DATA} from
10411		   getrlimit(). Both are reported as zero if the OS
10412		   lacks support. Free is -1 if getrlimit() is supported
10413		   but returns infinity.) \\
10414stacks		& [ global use, local use ] \\
10415program		& [ heap use, 0 ] \\
10416global_stack	& [ global use, global free ] \\
10417local_stack	& [ local use, local free ] \\
10418trail		& [ trail use, trail free ] \\
10419garbage_collection & [ number of GC, bytes gained, time spent, bytes left ]
10420		  The last column is a SWI-Prolog extension.  It contains the
10421		  sum of the memory left after each collection, which can be
10422		  divided by the count to find the average working set size
10423		  after GC.  Use \exam{[Count, Gained, Time|_]} for compatibility. \\
10424stack_shifts    & [ global shifts, local shifts, time spent ] \\
10425atoms		& [ number, memory use, 0 ] \\
10426atom_garbage_collection &
10427		  [ number of AGC, bytes gained, time spent ] \\
10428clause_garbage_collection &
10429		  [ number of CGC, clauses gained, time spent ] \\
10430core		& Same as memory \\
10431\hline
10432\end{tabular}
10433\end{center}
10434    \caption{Compatibility keys for statistics/2. Time is expressed in
10435	     milliseconds.}
10436    \label{tab:qpstatistics}
10437\end{table}
10438
10439    \predicate{statistics}{0}{}
10440Display a table of system statistics on the stream \const{user_error}.
10441
10442    \predicate{time}{1}{:Goal}
10443Execute \arg{Goal} just like call/1 and print time used, number of
10444logical inferences and the average number of \arg{lips} (logical
10445inferences per second). Note that SWI-Prolog counts the actual executed
10446number of inferences rather than the number of passes through the call
10447and redo ports of the theoretical 4-port model. If \arg{Goal} is
10448non-deterministic, print statistics for each solution, where the
10449reported values are relative to the previous answer.
10450\end{description}
10451
10452		 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
10453		 %	      PROFILER		%
10454		 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
10455
10456\input{profile.tex}
10457
10458
10459		 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
10460		 %	GARBAGE COLLECTION	%
10461		 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
10462
10463\section{Memory Management}		\label{sec:memory}
10464
10465\subsection{Garbage collection}		\label{sec:gc}
10466
10467\begin{description}
10468    \predicate{garbage_collect}{0}{}
10469Invoke the global and trail stack garbage collector.  Normally the
10470garbage collector is invoked automatically if necessary.  Explicit
10471invocation might be useful to reduce the need for garbage collections in
10472time-critical segments of the code.  After the garbage collection
10473trim_stacks/0 is invoked to release the collected memory resources.
10474
10475    \predicate{garbage_collect_atoms}{0}{}
10476Reclaim unused atoms. Normally invoked after \prologflag{agc_margin} (a
10477Prolog flag) atoms have been created. On multithreaded versions the
10478actual collection is delayed until there are no threads performing
10479normal garbage collection. In this case garbage_collect_atoms/0 returns
10480immediately. Note that there is no guarantee it will \emph{ever}
10481happen, as there may always be threads performing garbage collection.
10482
10483    \predicate{garbage_collect_clauses}{0}{}
10484Reclaim retracted clauses. During normal operation, retracting a clause
10485implies setting the \jargon{erased generation} to the current
10486\jargon{generation} of the database and increment the generation.
10487Keeping the clause around is both needed to realise the \jargon{logical
10488update view} and deal with the fact that other threads may be executing
10489the clause. Both static and dynamic code is processed this
10490way.\footnote{Up to version 7.3.11, dynamic code was handled using
10491\jargon{reference counts}.}.
10492
10493The clause garbage collector (CGC) scans the environment stacks of all
10494threads for referenced dirty predicates and at which generation this
10495reference accesses the predicate. It then removes the references for
10496clauses that have been retracted before the oldest access generation
10497from the clause list as well as the secondary clauses indexes of the
10498predicate. If the clause list is not being scanned, the clause
10499references and ultimately the clause itself is reclaimed.
10500
10501The clause garbage collector is called under three conditions, (1) after
10502\jargon{reloading} a source file, (2) if the memory occupied by
10503retracted but not yet reclaimed clauses exceeds 12.5\% of the program
10504store, or (3) if skipping dead clauses in the clause lists becomes too
10505costly. The cost of clause garbage collection is proportional with the
10506total size of the local stack of all threads (the scanning phase) and
10507the number of clauses in all `dirty' predicates (the reclaiming phase).
10508
10509    \predicate{set_prolog_gc_thread}{1}{+Status}
10510Control whether or not atom and clause garbage collection are executed
10511in a dedicated thread. The default is \const{true}. Values for
10512\arg{Status} are \const{true}, \const{false} and \const{stop}. The
10513latter stops the \const{gc} thread but allows is to be recreated lazily.
10514This is use by e.g., fork/1 to avoid forking a multi-threaded
10515application.  See also \prologflag{gc_thread}.
10516
10517    \predicate{trim_stacks}{0}{}
10518Release stack memory resources that are not in use at this moment,
10519returning them to the operating system. It can be used to release memory
10520resources in a backtracking loop, where the iterations require typically
10521seconds of execution time and very different, potentially large, amounts
10522of stack space. Such a loop can be written as follows:
10523
10524\begin{code}
10525loop :-
10526        generator,
10527            trim_stacks,
10528            potentially_expensive_operation,
10529        stop_condition, !.
10530\end{code}
10531
10532The Prolog top-level loop is written this way, reclaiming memory
10533resources after every user query.
10534
10535    \predicate{set_prolog_stack}{2}{+Stack, +KeyValue}
10536Set a parameter for one of the Prolog runtime stacks. \arg{Stack} is one
10537of \const{local}, \const{global} or \const{trail}. The table below
10538describes the \arg{Key}(\arg{Value}) pairs.
10539
10540Current settings can be retrieved with prolog_stack_property/2.
10541
10542\begin{description}
10543    \termitem{min_free}{+Cells}
10544Minimum amount of free space after trimming or shifting the stack.
10545Setting this value higher can reduce the number of garbage collections
10546and stack-shifts at the cost of higher memory usage. The
10547amount is reported and specified in \jargon{cells}. A cell is 4 bytes
10548in the 32-bit version and 8 bytes on the 64-bit version. See
10549\prologflag{address_bits}. See also trim_stacks/0 and debug/0.
10550
10551    \termitem{low}{+Cells}
10552\nodescription
10553    \termitem{factor}{+Number}
10554These two figures determine whether, if the stacks are low, a stack
10555\jargon{shift} (expansion) or garbage collection is performed. This
10556depends on these two parameters, the current stack usage and the amount
10557of stack used after the last garbage collection.  A garbage collection
10558is started if $used > factor \times lastused + low$.
10559
10560    \termitem{spare}{+Cells}
10561All stacks trigger overflow before actually reaching the limit, so the
10562resulting error can be handled gracefully. The spare stack is used for
10563print_message/2 from the garbage collector and for handling exceptions.
10564The default suffices, unless the user redefines related hooks. Do
10565\textbf{not} specify large values for this because it reduces the amount
10566of memory available for your real task.
10567
10568Related hooks are message_hook/3 (redefining GC messages),
10569prolog_trace_interception/4 and prolog_exception_hook/4.
10570\end{description}
10571
10572    \predicate{prolog_stack_property}{2}{?Stack, ?KeyValue}
10573True if \arg{KeyValue} is a current property of \arg{Stack}.  See
10574set_prolog_stack/2 for defined properties.
10575\end{description}
10576
10577The total space limit for all stacks is controlled using the prolog
10578flag \prologflag{stack_limit}.
10579
10580\subsection{Heap memory (malloc)}	\label{sec:malloc}
10581
10582\index{tcmalloc}%
10583SWI-Prolog's memory management is based on the C runtime malloc()
10584function and related functions.  The characteristics of the malloc()
10585implementation may affect performance and overall memory usage of the
10586system. For most Prolog programs the performance impact of the allocator
10587is small.\footnote{Multi-threaded applications may suffer from
10588allocators that do not effectively avoid \jargon{false sharing} that
10589affect CPU cache behaviour or operate using a single lock to provide
10590thread safety. Such allocators should be rare in modern OSes.} The
10591impact on total memory usage can be significant though, in particular
10592for multi-threaded applications. This is due to two aspects of
10593SWI-Prolog memory management:
10594
10595\begin{itemize}
10596    \item The Prolog stacks are allocated using malloc().  The stacks can
10597    be extremely large. SWI-Prolog assumes malloc() will use a mechanism
10598    that allows returning this memory to the OS.  Most todays allocators
10599    satisfy this requirement.
10600
10601    \item Atoms and clauses are allocated by the thread that requires
10602    them, but this memory is freed by the thread running the atom or
10603    clause garbage collector (see garbage_collect_atoms/0 and
10604    garbage_collect_clauses/0). Normally these run in the thread
10605    \const{gc}, which means that all deallocation happens in this
10606    thread.  Notably the \href{http://www.malloc.de/en/}{ptmalloc}
10607    implementation used by the GNU C library (glibc) seems to handle
10608    this poorly.
10609\end{itemize}
10610
10611Starting with version 8.1.27, SWI-Prolog by default links against
10612\href{https://github.com/google/tcmalloc}{tcmalloc} when available. Note
10613that changing the allocator can only be done by linking the main
10614executable (\program{swipl}) to an alternative library.  When embedded
10615(see \secref{embedded}) the main program that embeds \file{libswipl}
10616must be linked with tcmalloc.  On ELF based systems (Linux), this effect
10617can also be achieved using the environment variable \const{LD_PRELOAD}:
10618
10619\begin{code}
10620% LD_PRELOAD=/path/to/libtcmalloc.so swipl ...
10621\end{code}
10622
10623If SWI-Prolog core detects that tcmalloc is the current allocator and
10624provides the following additional predicates.
10625
10626\begin{description}
10627    \predicate[nondet]{malloc_property}{1}{?Property}
10628True when \arg{Property} is a property of the current allocator.  The
10629properties are defined by the allocator.  The properties of tcmalloc
10630are defined in
10631\file{gperftools/malloc_extension.h}:\footnote{Documentation copied from
10632the header.}
10633
10634    \begin{description}
10635	\termitem{'generic.current_allocated_bytes'}{-Int}
10636Number of bytes currently allocated by application.
10637	\termitem{'generic.heap_size'}{-Int}
10638Number of bytes in the heap (= current_allocated_bytes + fragmentation
10639+ freed memory regions).
10640	\termitem{'tcmalloc.max_total_thread_cache_bytes'}{-Int}
10641Upper limit on total number of bytes stored across all thread caches.
10642	\termitem{'tcmalloc.current_total_thread_cache_bytes'}{-Int}
10643Number of bytes used across all thread caches.
10644	\termitem{'tcmalloc.central_cache_free_bytes'}{-Int}
10645Number of free bytes in the central cache that have been
10646assigned to size classes. They always count towards virtual
10647memory usage, and unless the underlying memory is swapped out
10648by the OS, they also count towards physical memory usage.
10649	\termitem{'tcmalloc.transfer_cache_free_bytes'}{-Int}
10650Number of free bytes that are waiting to be transferred between
10651the central cache and a thread cache. They always count
10652towards virtual memory usage, and unless the underlying memory
10653is swapped out by the OS, they also count towards physical
10654	\termitem{'tcmalloc.thread_cache_free_bytes'}{-Int}
10655Number of free bytes in thread caches. They always count
10656towards virtual memory usage, and unless the underlying memory
10657is swapped out by the OS, they also count towards physical
10658memory usage.
10659	\termitem{'tcmalloc.pageheap_free_bytes'}{-Int}
10660Number of bytes in free, mapped pages in page heap.  These
10661bytes can be used to fulfill allocation requests.  They
10662always count towards virtual memory usage, and unless the
10663underlying memory is swapped out by the OS, they also count
10664towards physical memory usage.  This property is not writable.
10665	\termitem{'tcmalloc.pageheap_unmapped_bytes'}{-Int}
10666Number of bytes in free, unmapped pages in page heap.
10667These are bytes that have been released back to the OS,
10668possibly by one of the MallocExtension "Release" calls.
10669They can be used to fulfill allocation requests, but
10670typically incur a page fault.  They always count towards
10671virtual memory usage, and depending on the OS, typically
10672do not count towards physical memory usage.
10673    \end{description}
10674
10675    \predicate[det]{set_malloc}{1}{+Property}
10676Set properties described in malloc_property/1.  Currently
10677the only writable property is
10678\const{tcmalloc.max_total_thread_cache_bytes}. Setting an unknown
10679property raises a \const{domain_error} and setting a read-only property
10680raises a \const{permission_error} exception.
10681
10682    \predicate[semidet]{thread_idle}{2}{:Goal, +Duration}
10683Indicates to the system that the calling thread will idle for some time
10684while calling \arg{Goal} as once/1.  This call releases resources to the
10685OS to minimise the footprint of the calling thread while it waits.
10686Despite the name this predicate is always provided, also if the system
10687is not configured with tcmalloc or is single threaded.
10688\arg{Duration} is one of
10689
10690    \begin{description}
10691	\termitem{short}{}
10692Calls trim_stacks/0 and, if tcmalloc is used, calls
10693MallocExtension_MarkThreadTemporarilyIdle() which empties the thread's
10694malloc cache but preserves the cache itself.
10695
10696	\termitem{long}{}
10697Calls garbage_collect/0 and trim_stacks/0 and, if tcmalloc is used,
10698calls MallocExtension_MarkThreadIdle() which releases all
10699thread-specific allocation data structures.
10700    \end{description}
10701\end{description}
10702
10703
10704\section{Windows DDE interface}          \label{sec:DDE}
10705
10706The predicates in this section deal with MS-Windows `Dynamic Data
10707Exchange' or DDE protocol.%
10708        \footnote{This interface is contributed by Don Dwiggins.}
10709A Windows DDE conversation is a form of interprocess communication
10710based on sending reserved window events between the communicating
10711processes.
10712
10713Failing DDE operations raise an error of the structure below, where
10714\arg{Operation} is the name of the (partial) operation that failed and
10715\arg{Message} is a translation of the operator error code. For some
10716errors, \arg{Context} provides additional comments.
10717
10718\begin{code}
10719	error(dde_error(Operation, Message), Context)
10720\end{code}
10721
10722
10723\subsection{DDE client interface}
10724\label{sec:dde-client}
10725
10726The DDE client interface allows Prolog to talk to DDE server programs.
10727We will demonstrate the use of the DDE interface using the Windows
10728PROGMAN (Program Manager) application:
10729
10730\begin{code}
107311 ?- open_dde_conversation(progman, progman, C).
10732
10733C = 0
107342 ?- dde_request(0, groups, X)
10735
10736--> Unifies X with description of groups
10737
107383 ?- dde_execute(0, '[CreateGroup("DDE Demo")]').
10739true.
10740
107414 ?- close_dde_conversation(0).
10742true.
10743\end{code}
10744
10745
10746For details on interacting with \program{progman}, use the SDK online
10747manual section on the Shell DDE interface. See also the Prolog
10748\file{library(progman)}, which may be used to write simple Windows setup
10749scripts in Prolog.
10750
10751
10752\begin{description}
10753    \predicate{open_dde_conversation}{3}{+Service, +Topic, -Handle}
10754Open a conversation with a server supporting the given service name and
10755topic (atoms).  If successful, \arg{Handle} may be used to send
10756transactions to the server.  If no willing server is found this
10757predicate fails silently.
10758
10759    \predicate{close_dde_conversation}{1}{+Handle}
10760Close the conversation associated with \arg{Handle}.  All opened
10761conversations should be closed when they're no longer needed, although
10762the system will close any that remain open on process termination.
10763
10764    \predicate{dde_request}{3}{+Handle, +Item, -Value}
10765Request a value from the server.  \arg{Item} is an atom that identifies
10766the requested data, and \arg{Value} will be a string (\const{CF_TEXT} data
10767in DDE parlance) representing that data, if the request is successful.
10768
10769    \predicate{dde_execute}{2}{+Handle, +Command}
10770Request the DDE server to execute the given command string.  Succeeds
10771if the command could be executed and fails with an error message otherwise.
10772
10773    \predicate{dde_poke}{4}{+Handle, +Item, +Command}
10774Issue a \const{POKE} command to the server on the specified \arg{Item}.
10775\arg{command} is passed as data of type \const{CF_TEXT}.
10776\end{description}
10777
10778
10779\subsection{DDE server mode}
10780\label{sec:dde-server}
10781
10782The \file{library(dde)} defines primitives to realise simple
10783DDE server applications in SWI-Prolog.  These features are provided as
10784of version 2.0.6 and should be regarded as prototypes.  The C part of
10785the DDE server can handle some more primitives, so if you need features
10786not provided by this interface, please study \file{library(dde)}.
10787
10788
10789\begin{description}
10790    \predicate{dde_register_service}{2}{+Template, +Goal}
10791Register a server to handle DDE request or DDE \const{execute} requests from
10792other applications. To register a service for a DDE request, \arg{Template} is of the form:
10793\begin{quote}
10794+Service(+Topic, +Item, +Value)
10795\end{quote}
10796\arg{Service} is the name of the DDE service provided (like
10797\program{progman} in the client example above). \arg{Topic} is either an
10798atom, indicating \arg{Goal} only handles requests on this topic, or a
10799variable that also appears in \arg{Goal}. \arg{Item} and \arg{Value} are
10800variables that also appear in \arg{Goal}. \arg{Item} represents the
10801request data as a Prolog atom.%
10802    \footnote{Up to version 3.4.5 this was a list of character codes.
10803	      As recent versions have atom garbage collection there is
10804	      no need for this anymore.}
10805
10806The example below registers the Prolog current_prolog_flag/2 predicate
10807to be accessible from other applications. The request may be given from
10808the same Prolog as well as from another application.
10809
10810\begin{code}
10811?- dde_register_service(prolog(current_prolog_flag, F, V),
10812                        current_prolog_flag(F, V)).
10813
10814?- open_dde_conversation(prolog, current_prolog_flag, Handle),
10815   dde_request(Handle, home, Home),
10816   close_dde_conversation(Handle).
10817
10818Home = '/usr/local/lib/pl-2.0.6/'
10819\end{code}
10820
10821Handling DDE \const{execute} requests is very similar.  In this case the
10822template is of the form:
10823
10824\begin{quote}
10825+Service(+Topic, +Item)
10826\end{quote}
10827
10828Passing a \arg{Value} argument is not needed as \const{execute} requests either
10829succeed or fail.  If \arg{Goal} fails, a `not processed' is passed back
10830to the caller of the DDE request.
10831    \predicate{dde_unregister_service}{1}{+Service}
10832Stop responding to \arg{Service}. If Prolog is halted, it will
10833automatically call this on all open services.
10834    \predicate{dde_current_service}{2}{-Service, -Topic}
10835Find currently registered services and the topics served on them.
10836    \predicate{dde_current_connection}{2}{-Service, -Topic}
10837Find currently open conversations.
10838\end{description}
10839
10840
10841\section{Miscellaneous}			\label{sec:miscpreds}
10842
10843\begin{description}
10844    \predicate{dwim_match}{2}{+Atom1, +Atom2}
10845True if \arg{Atom1} matches \arg{Atom2} in the `Do What I Mean' sense.
10846Both \arg{Atom1} and \arg{Atom2} may also be integers or floats.
10847The two atoms match if:
10848\begin{shortlist}
10849    \item They are identical
10850    \item They differ by one character (spy $\equiv$ spu)
10851    \item One character is inserted/deleted (debug $\equiv$ deug)
10852    \item Two characters are transposed (trace $\equiv$ tarce)
10853    \item `Sub-words' are glued differently (existsfile $\equiv$ existsFile $\equiv$ exists_file)
10854    \item Two adjacent sub-words are transposed (existsFile $\equiv$ fileExists)
10855\end{shortlist}
10856    \predicate{dwim_match}{3}{+Atom1, +Atom2, -Difference}
10857Equivalent to dwim_match/2, but unifies \arg{Difference} with an atom
10858identifying the difference between \arg{Atom1} and \arg{Atom2}.  The
10859return values are (in the same order as above): \const{equal},
10860\const{mismatched_char}, \const{inserted_char}, \const{transposed_char},
10861\const{separated} and \const{transposed_word}.
10862    \predicate{wildcard_match}{2}{+Pattern, +String}
10863\nodescription
10864    \predicate{wildcard_match}{3}{+Pattern, +String, +Options}
10865True if \arg{String} matches the wildcard pattern \arg{Pattern}.
10866\arg{Pattern} is very similar to the Unix \const{csh} pattern matcher. The
10867patterns are given below:
10868
10869\begin{center}\begin{tabular}{ll}
10870\const{?}          & Matches one arbitrary character. \\
10871\const{*}          & Matches any number of arbitrary characters. \\
10872\const{[\ldots]}   & Matches one of the characters specified between the
10873		     brackets. \\
10874		   & \mbox{\tt <char1>-<char2>} indicates a range. \\
10875\const{\{\ldots\}} & Matches any of the patterns of the comma-separated
10876list between the braces.
10877\end{tabular}\end{center}
10878
10879Example:
10880
10881\begin{code}
10882?- wildcard_match('[a-z]*.{pro,pl}[%~]', 'a_hello.pl%').
10883true.
10884\end{code}
10885
10886The wildcard_match/3 version processes the following option:
10887
10888\begin{description}
10889    \termitem{case_sensitive}{+Boolean}
10890When \const{false} (default \const{true}), match case insensitively.
10891\end{description}
10892
10893    \predicate{sleep}{1}{+Time}
10894Suspend execution \arg{Time} seconds. \arg{Time} is either a floating
10895point number or an integer. Granularity is dependent on the system's
10896timer granularity.  A negative time causes the timer to return
10897immediately. On most non-realtime operating systems we can only ensure
10898execution is suspended for {\bf at least} \arg{Time} seconds.
10899
10900On Unix systems the sleep/1 predicate is realised ---in order of
10901preference--- by nanosleep(), usleep(), select() if the time is below 1
10902minute, or sleep().  On Windows systems Sleep() is used.
10903\end{description}
10904