Patched Texinfo file for SICStus Prolog User’s Manual, version 0.7.
Mats Carlsson. SICStus Prolog User’s Manual, version 0.7, Swedish Institute of Computer Science, 19 November 1991. This manual corresponds to SICStus version 0.7 patch level #7. Patched Texinfo file
Size 249.6 kB - File type text/x-texFile contents
% -*- texinfo -*- \raggedbottom %\input texinfoh \input texinfo @c $Header: /tmp_mnt/usr/share/src/local/sicstus/sicstus0.7/doc/RCS/sicstus.tex,v 1.3 90/08/28 15:19:45 matsc Exp Locker: matsc $ @comment %**start of header (This is for running Texinfo on a region.) @setfilename /usr/share/src/local/gnu/emacs/info/sicstus0.7 @settitle SICStus @setchapternewpage odd @comment %**end of header (This is for running Texinfo on a region.) @c @smallbook @ifinfo This file documents SICStus Prolog. Copyright @copyright{} 1988, Swedish Institute of Computer Science. @end ifinfo @tex % LaTeX "sloppy" \global\tolerance=10000 \global\hfuzz=.5pt \global\vfuzz=.5pt % Adjust \hoffset for A4 paper %\global\vsize 25.6cm %\global\pageheight=\vsize %\global\hoffset-0.125cm @end tex @macro ctrl{char} ^\char\ @end macro @titlepage @title SICStus Prolog User's Manual @font@authorrm=cmbx10 scaled @magstep2 @author Mats Carlsson @author Swedish Institute of Computer Science @author PO Box 1263, S-16428 KISTA, Sweden @sp 4 @c @subtitle Draft version: @today @subtitle Draft version: 19 November 1991 @page @sp 10 @center @titlefont{SICStus Prolog User's Manual} @sp 2 @c @center @today @center 19 November 1991 @sp 4 @center This manual is based on DECsystem-10 Prolog User's Manual by @center D.L. Bowen, L. Byrd, F.C.N. Pereira, @center L.M. Pereira, D.H.D. Warren @sp 1 @center Modified for SICStus Prolog by @center Mats Carlsson and Johan Widen @center Swedish Institute of Computer Science @center PO Box 1263 @center S-164 28 KISTA, Sweden @sp 4 @center This manual corresponds to SICStus version 0.7 patch level #7. @end titlepage @page @ifinfo @node Top, Intro,, (DIR) @comment node-name, next, previous, up SICStus Prolog ************** Prolog is a simple but powerful programming language developed at the University of Marseilles, as a practical tool for programming in logic. From a user's point of view the major attraction of the language is ease of programming. Clear, readable, concise programs can be written quickly with few errors. @end ifinfo @menu * Intro:: An introduction to this manual. * Notation:: Notational conventions. Indexes, nodes containing large menus * Predicate Index:: An item for each predicate. * Concept Index:: An item for each concept. How to run Prolog * Run Intro:: Chapter abstract. * Start:: Getting started. * Reading In:: Reading in programs. * Inserting Clauses:: Inserting clauses at the terminal. * Directives:: Queries and commands. * Syntax Errors:: How syntax errors are displayed. * Undefined Predicates:: Handling of undefined predicates. * Execution:: Program execution and interruption. * Exiting:: Exiting from the interpreter. * Nested:: Nested executions---Break and Abort. * Saving:: Saving and Restoring program states. Debugging * Debug Intro:: Chapter abstract. * Procedure Box:: The Procedure Box Control Flow model. * Basic:: Basic debugging predicates. * Trace:: Tracing a program. * Spy-Point:: Break points. * Debug Format:: Format of debugging messages. * Debug Options:: Options available during debugging. * Consult:: Consulting during debugging. Loading Programs * Load Intro:: Chapter abstract. * Load Predicates:: Predicates which Load Programs. * Declarations:: Declarations. * Pitfalls:: Pitfalls of file-to-file compilation. * Indexing:: Indexing of clauses. * Tail:: Tail recursion optimisation. Built-In Predicates * Built Intro:: Chapter abstract. * Input Output:: Input / Output. * Arithmetic:: Arithmetic. * Term Compare:: Comparison of terms. * Control:: Control predicates. * State Info:: Information about the state of the program. * Meta Logic:: Meta-logical predicates. * Modify Prog:: Modification of the Program. * Database:: Internal database. * All Solutions:: All Solutions. * Foreign:: Interface to foreign language functions. * Debug Pred:: Predicates controlling debugging. * Profiling:: Execution profiling. * Definite:: Definite clause grammars. * Misc Pred:: Miscellaneous predicates. The Prolog Language * Prolog Intro:: Chapter abstract. * Syntax:: Syntax, terminology and informal semantics. * Terms:: Terms. * Programs:: Programs. * Declarative:: Declarative semantics. * Procedural:: Procedural semantics. * Occur:: Occurs check and Cyclic Terms. * Cut:Cut Symbol:: The cut symbol. * Operators:: Operators. * Restrictions:: Syntax restrictions. * Comments:: Comments. * Full Syntax:: Full Prolog syntax. Programming Examples * Example Intro:: Chapter abstract. * Simple List:: Simple list processing. * Small Database:: A small database. * Association Lists:: Association list primitives. * Derivative:: Differentiation. * Set Primitives:: Representing sets as ordered lists w/o duplicates. * Use Of Meta:: Use of meta predicates. * Interpreter:: Prolog in Prolog. * Translate:: Translating English sentences into logic formulae. Installation Dependencies * Installation Intro:: Installation Dependencies. Summary of Built-In Predicates * Pred Summary:: Summary of built-in predicates. Standard Operators * Standard Operators:: Standard Operators. Subnodes of Input Output * Read In:: Reading in programs. * Term IO:: Input and output of terms. * Char IO:: Input and output of characters. * Stream Pred:: Stream IO. * File Pred:: DEC-10 Prolog File IO. * IO Example:: An example. Subnodes of Full Syntax * Syntax Notation:: Notation. * Sentence:: Syntax of sentences as terms. * Term Token:: Syntax of terms as tokens. * Token String:: Syntax of tokens as character strings. * Syntax Notes:: Notes @end menu @node Intro, Notation, Concept Index, Top @comment node-name, next, previous, up @unnumbered Introduction Prolog is a simple but powerful programming language developed at the University of Marseilles (@cite{Prolog : Manuel de Reference et d'Utilisation} by P. Roussel, Groupe d'Intelligence Artificielle, Marseille-Luminy, 1975), as a practical tool for @dfn{programming in logic} (@cite{Logic for Problem Solving} by R.A. Kowalski, DCL Memo 75, Dept. of Artificial Intelligence, University of Edinburgh, March, 1974). From a user's point of view the major attraction of the language is ease of programming. Clear, readable, concise programs can be written quickly with few errors. @refill @cindex logic programming @cindex programming in logic For an introduction to programming in Prolog, readers are recommended to consult @cite{The Art of Prolog} by L. Sterling and E. Shapiro, The MIT Press, Cambridge MA, 1986. However, for the benefit of those who do not have access to a copy of this book, and for those who have some prior knowledge of logic programming, a summary of the language is included. For a more general introduction to the field of Logic Programming see @cite{Artificial Intelligence: Logic for Problem Solving} by R.A. Kowalski, North Holland, 1979. @xref{Prolog Intro}. @refill @cindex WAM This manual describes a Prolog system developed at the Swedish Institute of Computer Science. The system consists of a @dfn{WAM} emulator written in C, a library and runtime system written in C and Prolog and an interpreter and a compiler written in Prolog. The Prolog engine is a Warren Abstract Machine (WAM) emulator defined by D.H.D. Warren in @cite{An Abstract Prolog Instruction Set}, Tech. Note 309, SRI International, Menlo Park, CA, 1983. Two modes of compilation are available: in-core i.e. incremental, and file-to-file. @refill When compiled, a predicate will run about 8 times faster and use store more economically. However, it is recommended that the new user should gain experience with the interpreter before attempting to use the compiler. The interpreter facilitates the development and testing of Prolog programs as it provides powerful debugging facilities. It is only worthwhile compiling programs which are well-tested and are to be used extensively. SICStus Prolog follows the mainstream Prolog tradition in terms of syntax and built-in predicates, and is largely compatible with DECsystem-10 Prolog and Quintus Prolog (@cite{Quintus Prolog Reference Manual version 10}, Quintus Computer Systems, Inc, Mountain View, 1987). It also contains primitives for data-driven and object-oriented programming. Certain aspects of the Prolog system are unavoidably installation dependent. Whenever there are differences, this manual describes the SICS installation which runs under Berkeley UNIX. @xref{Installation Intro}. This manual is based on the @cite{DECsystem-10 Prolog User's Manual} by D.L. Bowen (editor), L. Byrd, F.C.N. Pereira, L.M. Pereira, D.H.D. Warren. Quintus and Quintus Prolog are trademarks of Quintus Computer Systems, Inc. UNIX is a trademark of Bell Laboratories. DEC is a trademark of Digital Equipment Corporation. @node Notation, Run Intro, Concept Index, Top @comment node-name, next, previous, up @unnumbered Notational Conventions @cindex notation @cindex predicate spec Predicates in Prolog are distinguished by their name @emph{and} their arity. The notation @code{@var{name}/@var{arity}} is therefore used when it is necessary to refer to a predicate unambiguously; e.g. @code{concatenate/3} specifies the predicate which is named ``concatenate'' and which takes 3 arguments. We shall call @code{@var{name}/@var{arity}} a @dfn{predicate spec}. @refill @cindex mode spec When introducing a built-in predicate, we shall present its usage with a @dfn{mode spec} which has the form @var{name(arg, ..., arg)} where each @var{arg} can be of one of the forms: @var{+ArgName}---this argument should be instantiated in goals for the predicate. @var{-ArgName}---this argument should @emph{not} be instantiated in goals for the predicate. @var{?ArgName}---this argument may or may not be instantiated in goals for the predicate. @refill We adopt the following convention for delineating character strings in the text of this manual: when a string is being used as a Prolog atom it is written thus: @code{user} or @code{'user'}; but in all other circumstances double quotes are used. @cindex keyboard When referring to keyboard characters, printing characters are written thus: @kbd{a}, while control characters are written like this: @ctrl{A}. Thus @ctrl{C} is the character you get by holding down the @key{CTL} key while you type @kbd{c}. Finally, the special control characters carriage-return, line-feed and space are often abbreviated to @key{RET}, @key{LFD} and @key{SPC} respectively.@refill @node Run Intro, Start, Concept Index, Top @comment node-name, next, previous, up @chapter How to run Prolog SICStus Prolog offers the user an interactive programming environment with tools for incrementally building programs, debugging programs by following their executions, and modifying parts of programs without having to start again from scratch. The text of a Prolog program is normally created in a file or a number of files using one of the standard text editors. The Prolog interpreter can then be instructed to read in programs from these files; this is called @dfn{consulting} the file. Alternatively, the Prolog compiler can be used for @dfn{compiling} the file. @node Start, Reading In, Run Intro, Top @comment node-name, next, previous, up @section Getting Started @cindex running SICStus is typically started from one of the UNIX shells by entering the shell command (@pxref{Installation Intro}): @example % prolog @end example @noindent The interpreter responds with a message of identification and the prompt @samp{| ?- } as soon as it is ready to accept input, thus: @example SICStus 0.7 #0: Thu Jun 7 10:40:30 MET DST 1990 | ?- @end example During program development it is often convenient to run in a GNU Emacs Prolog window, available by the Emacs command @example M-x run-prolog @end example @noindent The GNU Emacs Prolog mode that comes with SICStus Prolog provides a host of commands for incremental program development (@pxref{Installation Intro}). @cindex top level @cindex query @cindex command When SICStus is initialised it looks for a file @file{~/.sicstusrc} and consults it, if it exists. At this point the interpreter is expecting input of a directive, i.e. a @dfn{query} or @dfn{command}. @xref{Directives}. You cannot type in clauses immediately (@pxref{Inserting Clauses}). While typing in a directive, the prompt (on following lines) becomes @samp{ }. That is, the @samp{?-} appears only for the first line of the directive, and subsequent lines are indented. @refill @node Reading In, Inserting Clauses, Start, Top @comment node-name, next, previous, up @section Reading in Programs @cindex consulting @cindex reading in A program is made up of a sequence of clauses, possibly interspersed with directives to the interpreter. The clauses of a predicate do not have to be immediately consecutive, but remember that their relative order may be important (@pxref{Procedural}). To input a program from a file @var{file}, just type the filename inside list brackets (followed by full-stop and carriage-return), thus: @example | ?- [@var{file}]. @end example @noindent This instructs the interpreter to read in (@dfn{consult}) the program. Note that it may be necessary to surround the file specification @var{file} with single quotes to make it a legal Prolog atom; e.g. @example | ?- ['myfile.pl']. | ?- ['/usr/prolog/somefile']. @end example @noindent The specified file is then read in. Clauses in the file are stored ready to be interpreted, while any directives are obeyed as they are encountered. When the end of the file is found, the interpreter displays on the terminal the time spent for read-in. This indicates the completion of the directive. Predicates that expect the name of a Prolog source file as an argument use @code{absolute_file_name/2} (@pxref{Stream Pred}) to look up the file. This predicate will first search for a file with the suffix @samp{.pl} added to the name given as an argument. If this fails it will look for a file with no extra suffix added. There is also support for libraries. In general, this directive can be any list of filenames, such as: @example | ?- [myprog,extras,tests]. @end example @noindent In this case all three files would be consulted. The clauses for all the predicates in the consulted files will replace any existing clauses for those predicates, i.e. any such previously existing clauses in the database will be deleted. @cindex reconsult Note that @code{consult/1} in SICStus Prolog behaves like @code{reconsult/1} in DEC-10 Prolog. @refill @node Inserting Clauses, Directives, Reading In, Top @comment node-name, next, previous, up @section Inserting Clauses at the Terminal @cindex user Clauses may also be typed in directly at the terminal, although this is only recommended if the clauses will not be needed permanently, and are few in number. To enter clauses at the terminal, you must give the special directive: @example | ?- [user]. | @end example @noindent and the new prompt @samp{| } shows that the interpreter is now in a state where it expects input of clauses or directives. To return to interpreter top level, type @ctrl{D}. The interpreter responds thus: @example @{user consulted, 20 msec 200 bytes@} @end example @node Directives, Syntax Errors, Inserting Clauses, Top @comment node-name, next, previous, up @section Directives: Queries and Commands @cindex directive @dfn{Directives} are either @dfn{queries} or @dfn{commands}. Both are ways of directing the system to execute some goal or goals. In the following, suppose that list membership has been defined by: @example member(X, [X|_]). member(X, [_|L]) :- member(X, L). @end example @noindent (Notice the use of anonymous variables written @samp{_}.) The full syntax of a query is @samp{?-} followed by a sequence of goals. E.g. @refill @example ?- member(b, [a,b,c]). @end example At interpreter top level (signified by the initial prompt of @samp{| ?- }), a query may be abbreviated by omitting the @samp{?-} which is already included in the prompt. Thus a query at top level looks like this: @example | ?- member(b, [a,b,c]). @end example @noindent Remember that Prolog terms must terminate with a full stop (@kbd{.} followed by whitespace), and that therefore Prolog will not execute anything until you have typed the full stop (and then @key{RET}, carriage-return) at the end of the query. If the goal(s) specified in a query can be satisfied, and if there are no variables as in this example, then the system answers @example yes @end example @noindent and execution of the query terminates. If variables are included in the query, then the final value of each variable is displayed (except for anonymous variables). Thus the query @example | ?- member(X, [a,b,c]). @end example @noindent would be answered by @example X = a @end example @noindent At this point the interpreter is waiting for input of either just a carriage-return (@key{RET}) or else a @kbd{;} followed by @key{RET}. Simply typing @key{RET} terminates the query; the interpreter responds with @samp{yes}. However, typing @kbd{;} causes the system to @dfn{backtrack} (@pxref{Procedural}) looking for alternative solutions. If no further solutions can be found it outputs @samp{no}. @refill The outcome of some queries is shown below, where a number preceded by @kbd{_} is a system-generated name for a variable. @example | ?- member(X, [tom,dick,harry]). X = tom @kbd{;} X = dick @kbd{;} X = harry @kbd{;} no | ?- member(X, [a,b,f(Y,c)]), member(X, [f(b,Z),d]). X = f(b,c), Y = b, Z = c yes | ?- member(X, [f(_),g]). X = f(_52) yes | ?- @end example Commands are like queries except that @enumerate @item Variable bindings are not displayed if and when the command succeeds. @item You are not given the chance to backtrack through other solutions. @end enumerate @noindent Commands start with the symbol @samp{:-}. (At top level this is simply written after the prompted @w{@samp{| ?- }} which is then effectively overridden.) Any required output must be programmed explicitly; e.g. the command: @refill @example :- member(3, [1,2,3]), write(ok). @end example @noindent directs the system to check whether @code{3} belongs to the list @code{[1,2,3]}. Execution of a command terminates when all the goals in the command have been successfully executed. Other alternative solutions are not sought. If no solution can be found, the system gives: @refill @example @{WARNING: goal failed: :- @var{Goal}@} @end example @noindent as a warning. The principal use for commands (as opposed to queries) is to allow files to contain directives which call various predicates, but for which you do not want to have the answers printed out. In such cases you only want to call the predicates for their effect, i.e. you don't want terminal interaction in the middle of consulting the file. A useful example would be the use of a directive in a file which consults a whole list of other files, e.g. @example :- [ bits, bobs, main, tests, data, junk ]. @end example @noindent If a command like this were contained in the file @file{myprog} then typing the following at top-level would be a quick way of reading in your entire program: @example | ?- [myprog]. @end example When simply interacting with the top-level of the Prolog interpreter this distinction between queries and commands is not normally very important. At top-level you should just type queries normally. In a file, if you wish to execute some goals then you should use a command; i.e. a directive in a file must be preceded by @samp{:-}, otherwise it would be treated as a clause. @node Syntax Errors, Undefined Predicates, Directives, Top @comment node-name, next, previous, up @section Syntax Errors @cindex syntax errors Syntax errors are detected during reading. Each clause, directive or in general any term read in by the built-in predicate @code{read/1} that fails to comply with syntax requirements is displayed on the terminal as soon as it is read. A mark indicates the point in the string of symbols where the parser has failed to continue analysis. e.g. @example member(X, X:L). @end example @noindent gives: @example ** atom follows expression ** member ( X , X ** here ** : L ) @end example @noindent if @kbd{:} has not been declared as an infix operator. Note that any comments in the faulty line are not displayed with the error message. If you are in doubt about which clause was wrong you can use the @code{listing/1} predicate to list all the clauses which were successfully read-in, e.g. @example | ?- listing(member). @end example @node Undefined Predicates, Execution, Syntax Errors, Top @comment node-name, next, previous, up @section Undefined Predicates @cindex undefined predicate @findex unknown/2 There is a difference between predicates that have no definition and predicates that have no clauses. The latter case is meaningful e.g. for dynamic predicates (@pxref{Declarations}) that clauses are being added to or removed from. There are good reasons for treating calls to undefined predicates as errors, as such calls easily arise from typing errors. @refill The system can optionally catch calls to predicates that have no definition. The state of the catching facility can be: @itemize @bullet @item @code{trace}, which causes calls to undefined predicates to be reported and the debugging system to be entered at the earliest opportunity (the default state); @refill @item @code{fail}, which causes calls to such predicates to fail. @refill @end itemize Calls to predicates that have no clauses are not caught. The built-in predicate @code{unknown(@var{?OldState}, @var{?NewState})} unifies @var{OldState} with the current state and sets the state to @var{NewState}. It fails if the arguments are not appropriate. The built-in predicate @code{debugging/0} prints the value of this state along with its other information. @refill @node Execution, Exiting, Undefined Predicates, Top @comment node-name, next, previous, up @section Program Execution And Interruption @cindex execution @cindex interruption Execution of a program is started by giving the interpreter a directive which contains a call to one of the program's predicates. Only when execution of one directive is complete does the interpreter become ready for another directive. However, one may interrupt the normal execution of a directive by typing @ctrl{C}. This @ctrl{C} interruption has the effect of suspending the execution, and the following message is displayed: @refill @example Prolog interruption (h or ? for help) ? @end example @noindent At this point the interpreter accepts one-letter commands corresponding to certain actions. To execute an action simply type the corresponding character (lower or upper case) followed by @key{RET}. The possible commands are: @table @kbd @item a abort the current computation. @item b invoke the Prolog interpreter recursively. @item c continue the execution. @item d enable debugging. @xref{Debug Intro}. @item e exit from SICStus, closing all files. @item h @itemx ? list available commands. @item t enable trace. @xref{Trace}. @end table If the standard input stream is not connected to the terminal, e.g. by redirecting standard input to a file or a UNIX pipe, the above @ctrl{C} interrupt options are not available. Instead, typing @ctrl{C} causes SICStus to exit, and no terminal prompts are printed. @node Exiting, Nested, Execution, Top @comment node-name, next, previous, up @section Exiting From The Interpreter @cindex exiting To exit from the interpreter and return to the shell either type @ctrl{D} at interpreter top level, or call the built-in predicate @code{halt/0}, or use the @kbd{e} (exit) command following a @ctrl{C} interruption. @node Nested, Saving, Exiting, Top @comment node-name, next, previous, up @section Nested Executions---Break and Abort @cindex nested execution @cindex break @findex break/0 The Prolog system provides a way to suspend the execution of your program and to enter a new incarnation of the top level where you can issue directives to solve goals etc. This is achieved by issuing the directive (@pxref{Execution}): @example | ?- break. @end example @noindent This causes a recursive call to the Prolog interpreter, indicated by the message: @example @{ Break level 1 @} @end example @noindent You can now type queries just as if the interpreter were at top level. If another call of @code{break/0} is encountered, it moves up to level 2, and so on. To close the break and resume the execution which was suspended, type @ctrl{D}. The debugger state and current input and output streams will be restored, and execution will be resumed at the procedure call where it had been suspended after printing the message: @refill @example @{ End break @} @end example @noindent Alternatively, the suspended execution can be aborted by calling the built-in predicate @code{abort/0}. @refill @cindex abort @findex abort/0 A suspended execution can be aborted by issuing the directive: @example | ?- abort. @end example @noindent within a break. In this case no @ctrl{D} is needed to close the break; @emph{all} break levels are discarded and the system returns right back to top-level. IO streams remain open, but the debugger is switched off. @code{abort/0} may also be called from within a program. @refill @node Saving, Debug Intro, Nested, Top @comment node-name, next, previous, up @section Saving and Restoring Program States @cindex saving @cindex restoring @cindex program state @findex save/1 Once a program has been read, the interpreter will have available all the information necessary for its execution. This information is called a @dfn{program state}. The state of a program may be saved on disk for future execution. To save a program into a file @var{File}, perform the directive: @example | ?- save(@var{File}). @end example @noindent This predicate may be called at any time, for example it may be useful to call it in a break in order to save an intermediate execution state. The file @var{File} becomes an executable file. @xref{Installation Intro}. @findex restore/1 Once a program has been saved into a file @var{File}, the following directive will restore the interpreter to the saved state: @example | ?- restore(@var{File}). @end example @noindent After execution of this directive, which may be given in the same session or at some future date, the interpreter will be in @emph{exactly} the same state as existed immediately prior to the call to @code{save/1}. Thus if you saved a program as follows: @refill @example | ?- save(myprog), write('myprog restored'). @end example @noindent then on restoring you will get the message @samp{myprog restored} printed out. @findex save_program/1 A partial program state, containing only the user defined predicates may also be saved with the directive: @example | ?- save_program(@var{File}). @end example @noindent The file @var{File} becomes an executable file. @xref{Installation Intro}. After restoring a partial program state, the interpreter will reinitialise itself. Note that when a new version of the Prolog system is installed, all program files saved with the old version become obsolete. @node Debug Intro, Procedure Box, Saving, Top @comment node-name, next, previous, up @chapter Debugging @cindex debugging This chapter describes the debugging facilities that are available in the Prolog interpreter. The purpose of these facilities is to provide information concerning the control flow of your program. The main features of the debugging package are as follows: @itemize @bullet @item The @dfn{Procedure Box} model of Prolog execution which provides a simple way of visualising control flow, especially during backtracking. Control flow is viewed at the predicate level, rather than at the level of individual clauses. @refill @item The ability to exhaustively trace your program or to selectively set @dfn{spy-points}. Spy-points allow you to nominate interesting predicates at which the program is to pause so that you can interact. @refill @item The wide choice of control and information options available during debugging. @refill @end itemize Much of the information in this chapter is also in Chapter eight of @cite{Programming in Prolog} by W.F. Clocksin and C.S. Mellish (Springer-Verlag, 1981) which is recommended as an introduction. @node Procedure Box, Basic, Debug Intro, Top @comment node-name, next, previous, up @section The Procedure Box Control Flow Model @cindex procedure box During debugging the interpreter prints out a sequence of goals in various states of instantiation in order to show the state the program has reached in its execution. However, in order to understand what is occurring it is necessary to understand when and why the interpreter prints out goals. As in other programming languages, key points of interest are procedure entry and return, but in Prolog there is the additional complexity of backtracking. One of the major confusions that novice Prolog programmers have to face is the question of what actually happens when a goal fails and the system suddenly starts backtracking. The Procedure Box model of Prolog execution views program control flow in terms of movement about the program text. This model provides a basis for the debugging mechanism in the interpreter, and enables the user to view the behaviour of the program in a consistent way. Let us look at an example Prolog procedure : @smallexample @group *--------------------------------------* Call | | Exit ---------> + descendant(X,Y) :- offspring(X,Y). + ---------> | | | descendant(X,Z) :- | <--------- + offspring(X,Y), descendant(Y,Z). + <--------- Fail | | Redo *--------------------------------------* @end group @end smallexample @noindent The first clause states that @var{Y} is a descendant of @var{X} if @var{Y} is an offspring of @var{X}, and the second clause states that @var{Z} is a descendant of @var{X} if @var{Y} is an offspring of @var{X} and if @var{Z} is a descendant of @var{Y}. In the diagram a box has been drawn around the whole procedure and labelled arrows indicate the control flow in and out of this box. There are four such arrows which we shall look at in turn. @refill @table @var @item Call This arrow represents initial invocation of the procedure. When a goal of the form @code{descendant(X,Y)} is required to be satisfied, control passes through the @var{Call} port of the descendant box with the intention of matching a component clause and then satisfying any subgoals in the body of that clause. Note that this is independent of whether such a match is possible; i.e. first the box is called, and then the attempt to match takes place. Textually we can imagine moving to the code for descendant when meeting a call to descendant in some other part of the code. @refill @item Exit This arrow represents a successful return from the procedure. This occurs when the initial goal has been unified with one of the component clauses and any subgoals have been satisfied. Control now passes out of the @var{Exit} port of the descendant box. Textually we stop following the code for descendant and go back to the place we came from. @refill @item Redo This arrow indicates that a subsequent goal has failed and that the system is backtracking in an attempt to find alternatives to previous solutions. Control passes through the @var{Redo} port of the descendant box. An attempt will now be made to resatisfy one of the component subgoals in the body of the clause that last succeeded; or, if that fails, to completely rematch the original goal with an alternative clause and then try to satisfy any subgoals in the body of this new clause. Textually we follow the code backwards up the way we came looking for new ways of succeeding, possibly dropping down on to another clause and following that if necessary. @refill @item Fail This arrow represents a failure of the initial goal, which might occur if no clause is matched, or if subgoals are never satisfied, or if any solution produced is always rejected by later processing. Control now passes out of the @var{Fail} port of the descendant box and the system continues to backtrack. Textually we move back to the code which called this procedure and keep moving backwards up the code looking for choice points. @refill @end table In terms of this model, the information we get about the procedure box is only the control flow through these four ports. This means that at this level we are not concerned with which clause matches, and how any subgoals are satisfied, but rather we only wish to know the initial goal and the final outcome. However, it can be seen that whenever we are trying to satisfy subgoals, what we are actually doing is passing through the ports of @emph{their} respective boxes. If we were to follow this, then we would have complete information about the control flow inside the procedure box. @refill Note that the box we have drawn round the procedure should really be seen as an @dfn{invocation box}. That is, there will be a different box for each different invocation of the procedure. Obviously, with something like a recursive procedure, there will be many different @var{Calls} and @var{Exits} in the control flow, but these will be for different invocations. Since this might get confusing each invocation box is given a unique integer identifier. @refill @node Basic, Trace, Procedure Box, Top @comment node-name, next, previous, up @section Basic Debugging Predicates @cindex debugging predicates The interpreter provides a range of built-in predicates for control of the debugging facilities. The most basic predicates are as follows: @table @code @item debug @findex debug/0 Switches the debugger on. (It is initially off.) In order for the full range of control flow information to be available it is necessary to have this on from the start. When it is off the system does not remember invocations that are being executed. (This is because it is expensive and not required for normal running of programs.) You can switch @var{Debug Mode} on in the middle of execution, either from within your program or after a @ctrl{C} (see trace below), but information prior to this will just be unavailable. @refill @item nodebug @findex nodebug/0 Switches the debugger off. If there are any spy-points set then they will be kept but disabled. @refill @item debugging @findex debugging/0 Prints onto the terminal information about the current debugging state. This will show: @refill @enumerate @item Whether undefined predicates are being trapped. @item Whether the debugger is switched on. @item What spy-points have been set (see below). @item What mode of leashing is in force (see below). @item What the interpreter maxdepth is (see below). @end enumerate @end table @node Trace, Spy-Point, Basic, Top @comment node-name, next, previous, up @section Tracing @cindex tracing The following built-in predicate may be used to commence an exhaustive trace of a program. @table @code @item trace @findex trace/0 Switches the debugger on, if it is not on already, and ensures that the next time control enters a procedure box, a message will be produced and you will be asked to interact. The effect of trace can also be achieved by typing @kbd{t} after a @ctrl{C} interruption of a program. @refill @noindent At this point you have a number of options. @xref{Debug Options}. In particular, you can just type @key{RET} (carriage-return) to @dfn{creep} (or single-step) into your program. If you continue to creep through your program you will see every entry and exit to/from every invocation box. You will notice that the interpreter stops at all ports. However, if this is not what you want, the following built-in predicate gives full control over the ports at which you are prompted: @refill @item leash(@var{+Mode}) @findex leash/1 Leashing Mode is set to @var{Mode}. Leashing Mode determines the ports of procedure boxes at which you are to be prompted when you Creep through your program. At unleashed ports a tracing message is still output, but program execution does not stop to allow user interaction. Note that the ports of spy-points are always leashed (and cannot be unleashed). @var{Mode} can be a subset of the following, specified as a list: @refill @table @code @item call Prompt on Call. @item exit Prompt on Exit. @item redo Prompt on Redo. @item fail Prompt on Fail. @end table @noindent The initial value of @var{Leashing Mode} is @code{[call,exit,redo,fail]} (full leashing). @item notrace @findex notrace/0 Equivalent to @code{nodebug}. @refill @end table @node Spy-Point, Debug Format, Trace, Top @comment node-name, next, previous, up @section Spy-points @cindex spy-point For programs of any size, it is clearly impractical to creep through the entire program. @dfn{Spy-points} make it possible to stop the program whenever it gets to a particular predicate which is of interest. Once there, one can set further spy-points in order to catch the control flow a bit further on, or one can start creeping. Setting a spy-point on a predicate indicates that you wish to see all control flow through the various ports of its invocation boxes. When control passes through any port of a procedure box with a spy-point set on it, a message is output and the user is asked to interact. Note that the current mode of leashing does not affect spy-points: user interaction is requested on @emph{every} port. Spy-points are set and removed by the following built-in predicates which are also standard operators: @table @code @item spy @var{+Spec} @findex spy/1 Sets spy-points on all the predicates given by @var{Spec}. @var{Spec} is either an atom, a predicate spec, or a list of such specifications. An atom is taken as meaning all the predicates whose name is that atom. If you specify an atom but there is no definition for this predicate (of any arity) then nothing will be done. You cannot place a spy-point on an undefined predicate. If you set some spy-points when the debugger is switched off then it will be automatically switched on. @refill @item nospy @var{+Spec} @findex nospy/1 This is similar to spy @var{Spec} except that all the predicates given by @var{Spec} will have previously set spy-points removed from them. @refill @item nospyall @findex nospyall/0 This removes all the spy-points that have been set. @refill @end table @noindent The options available when you arrive at a spy-point are described later. @xref{Debug Options}. @node Debug Format, Debug Options, Spy-Point, Top @comment node-name, next, previous, up @section Format of Debugging messages @cindex debug messages We shall now look at the exact format of the message output by the system at a port. All trace messages are output to the terminal regardless of where the current output stream is directed. (This allows you to trace programs while they are performing file IO.) The basic format is as follows: @example @var{S} 23 6 Call: @var{T} foo(hello,there,_123) ? @end example @noindent @var{S} is a spy-point indicator. It is printed as @samp{+}, indicating that there is a spy-point on @code{foo/3}, or @samp{ }, denoting no spy-point. @var{T} is a subterm trace. This is used in conjunction with the @samp{^} command (set subterm), described below. If a subterm has been selected, @var{T} is printed as the sequence of commands used to select the subterm. Normally, however, @var{T} is printed as @samp{ }, indicating that no subterm has been selected. The first number is the unique invocation identifier. It is nondecreasing regardless of whether or not you are actually seeing the invocations (provided that the debugger is switched on). This number can be used to cross correlate the trace messages for the various ports, since it is unique for every invocation. It will also give an indication of the number of procedure calls made since the start of the execution. The invocation counter starts again for every fresh execution of a command, and it is also reset when retries (see later) are performed. @refill @cindex ancestors The number following this is the @dfn{current depth}; i.e. the number of direct @dfn{ancestors} this goal has. @refill The next word specifies the particular port (Call, Exit, Redo or Fail). The goal is then printed so that you can inspect its current instantiation state. This is done using @code{print/1} (@pxref{Term IO}) so that all goals output by the tracing mechanism can be pretty printed if the user desires. @refill The final @samp{?} is the prompt indicating that you should type in one of the option codes allowed (@pxref{Debug Options}). If this particular port is unleashed then you will obviously not get this prompt since you have specified that you do not wish to interact at this point. @refill Note that not all procedure calls are traced; there are a few basic predicates which have been made invisible since it is more convenient not to trace them. These include debugging directives and basic control structures, including @code{trace/0}, @code{debug/0}, @code{notrace/0}, @code{nodebug/0}, @code{spy/1}, @code{nospy/1}, @code{nospyall/0}, @code{leash/1}, @code{debugging}, @code{true/0}, @code{!/0}, @code{','/2}, @code{'->'/2}, @code{;/2}, @code{'\+'/1}, and @code{if/3}. This means that you will never see messages concerning these predicates during debugging. @refill There are two exceptions to the above debugger message format. A message @example @var{S} - - Block: p(_133) @end example @noindent indicates that the debugger has encountered a @dfn{blocked} goal, i.e. one which is temporarily suspended due to insufficiently instantiated arguments (@pxref{Procedural}). No interaction takes place at this point, and the debugger simply proceeds to the next goal in the execution stream. The suspended goal will be eligible for execution once the blocking condition ceases to exist, at which time a message @refill @example @var{S} - - Unblock: p(_133) @end example @noindent is printed. @node Debug Options, Consult, Debug Format, Top @comment node-name, next, previous, up @section Options available during Debugging @cindex debug options This section describes the particular options that are available when the system prompts you after printing out a debugging message. All the options are one letter mnemonics, some of which can be optionally followed by a decimal integer. They are read from the terminal with any blanks being completely ignored up to the next terminator (carriage-return, line-feed, or escape). Some options only actually require the terminator; e.g. the creep option, as we have already seen, only requires @key{RET}. The only option which you really have to remember is @samp{h} (followed by @key{RET}). This provides help in the form of the following list of available options. @smallexample @group RET creep c creep l leap s skip r retry r <i> retry i f fail f <i> fail i d display p print w write g ancestors g <n> ancestors n & blocked goals & <n> nth blocked goal n nodebug = debugging + spy this - nospy this a abort b break @@ command u unify < reset printdepth < <n> set printdepth ^ reset subterm ^ <n> set subterm ? help h help @end group @end smallexample @table @kbd @item c @itemx @key{RET} @cindex creep @dfn{creep} causes the interpreter to single-step to the very next port and print a message. Then if the port is leashed (@pxref{Trace}), the user is prompted for further interaction. Otherwise it continues creeping. If leashing is off, creep is the same as @dfn{leap} (see below) except that a complete trace is printed on the terminal. @refill @item l @cindex leap @dfn{leap} causes the interpreter to resume running your program, only stopping when a spy-point is reached (or when the program terminates). Leaping can thus be used to follow the execution at a higher level than exhaustive tracing. All you need to do is to set spy-points on an evenly spread set of pertinent predicates, and then follow the control flow through these by leaping from one to the other. @refill @item s @cindex skip @dfn{skip} is only valid for Call and Redo ports. It skips over the entire execution of the predicate. That is, you will not see anything until control comes back to this predicate (at either the Exit port or the Fail port). Skip is particularly useful while creeping since it guarantees that control will be returned after the (possibly complex) execution within the box. If you skip then no message at all will appear until control returns. This includes calls to predicates with spy-points set; they will be masked out during the skip. There is a way of overriding this : the @kbd{t} option after a @ctrl{C} interrupt will disable the masking. Normally, however, this masking is just what is required! @refill @item r @cindex retry @dfn{retry} can be used at any of the four ports (although at the Call port it has no effect). It transfers control back to the Call port of the box. This allows you to restart an invocation when, for example, you find yourself leaving with some weird result. The state of execution is exactly the same as when you originally called, (unless you use side effects in your program; i.e. asserts etc. will not be undone). When a retry is performed the invocation counter is reset so that counting will continue from the current invocation number regardless of what happened before the retry. This is in accord with the fact that you have, in executional terms, returned to the state before anything else was called. @refill If you supply an integer after the retry command, then this is taken as specifying an invocation number and the system tries to get you to the Call port, not of the current box, but of the invocation box you have specified. It does this by continuously failing until it reaches the right place. Unfortunately this process cannot be guaranteed: it may be the case that the invocation you are looking for has been cut out of the search space by cuts (@code{!}) in your program. In this case the system fails to the latest surviving Call port before the correct one. @refill @item f @cindex fail @dfn{fail} can be used at any of the four ports (although at the Fail port it has no effect). It transfers control to the Fail port of the box, forcing the invocation to fail prematurely. @refill If you supply an integer after the command, then this is taken as specifying an invocation number and the system tries to get you to the Fail port of the invocation box you have specified. It does this by continuously failing until it reaches the right place. Unfortunately this process cannot be guaranteed: it may be the case that the invocation you are looking for has been cut out of the search space by cuts (@code{!}) in your program. In this case the system fails to the latest surviving Fail port before the correct one. @refill @item d @dfn{display} goal displays the current goal using @code{display/1}. See Write (below). @refill @item p @dfn{print} goal re-prints the current goal using @code{print/1}. Nested structures will be printed to the specified @var{printdepth} (below). @refill @item w @dfn{write} goal writes the current goal on the terminal using @code{write/1}. @refill @item g Print @dfn{ancestor} goals provides you with a list of ancestors to the current goal, i.e. all goals that are hierarchically above the current goal in the calling sequence. It uses the @code{ancestors/1} built-in predicate (@pxref{State Info}). You can always be sure of jumping to any goal in the ancestor list (by using retry etc). If you supply an integer @var{n}, then only that number of ancestors will be printed. That is to say, the last @var{n} ancestors will be printed counting back from the current goal. The list is printed using @code{print/1} and each entry is preceded by the invocation number followed by the depth number (as would be given in a trace message). @refill @item & Print @dfn{blocked} goals prints a list of the goals which are currently blocked in the current debugging session together with the variable that each such goal is suspended on. The goals are enumerated from 1 and up. If you supply an integer @var{n}, then only that goal will be printed. The goals are printed using @code{print/1}. and each entry is preceded by the goal number followed by the variable name. @refill @item n @dfn{nodebug} switches the debugger off. Note that this is the correct way to switch debugging off at a trace point. You cannot use the @kbd{@@} or @kbd{b} options because they always return to the debugger. @refill @item = @dfn{debugging} outputs information concerning the status of the debugging package. @xref{Debug Pred}. @refill @item + @cindex spy @dfn{spy this}. Set a spy-point on the current goal. @item - @cindex nospy @dfn{nospy this}. Remove spy-point from the current goal. @item a @cindex abort @dfn{abort} causes an abort of the current execution. All the execution states built so far are destroyed and you are put right back at the top level of the interpreter. (This is the same as the built-in predicate @code{abort/0}.) @refill @item b @cindex break @dfn{break} calls the built-in predicate @code{break/0}, thus putting you at interpreter top level with the execution so far sitting underneath you. When you end the break (@ctrl{D}) you will be reprompted at the port at which you broke. The new execution is completely separate from the suspended one; the invocation numbers will start again from 1 during the break. The debugger is temporarily switched off as you call the break and will be re-switched on when you finish the break and go back to the old execution. However, any changes to the leashing or to spy-points will remain in effect. @refill @item @@ @cindex command @dfn{command} gives you the ability to call arbitrary Prolog goals. It is effectively a one-off @dfn{break} (see above). The initial message @samp{| :- } will be output on your terminal, and a command is then read from the terminal and executed as if you were at top level. @refill @item u @cindex unify @dfn{unify} is available at the Call port and gives you the option of providing a solution to the goal from the terminal rather than executing the goal. This is convenient e.g. for providing a ``stub'' for a predicate that has not yet been written. A prompt @samp{|: } will be output on your terminal, and the solution is then read from the terminal and unified with the goal. @refill @item < @cindex printdepth While in the debugger, a @dfn{printdepth} is in effect for limiting the subterm nesting level when printing the current goal using @code{print/1}. When displaying or writing the current goal, all nesting levels are shown. The limit is initially 10. This command, without arguments, resets the limit to 10. With an argument of @var{n}, the limit is set to @var{n}. @refill @item ^ @cindex subterm While at a particular port, a current @dfn{subterm} of the current goal is maintained. It is the current subterm which is displayed, printed, or written when prompting for a debugger command. Used in combination with the printdepth, this provides a means for navigating in the current goal for focusing on the part which is of interest. The current subterm is set to the current goal when arriving at a new port. This command, without arguments, resets the current subterm to the current goal. With an argument of @var{n} (> 0), the current subterm is replaced by its @var{n}:th subterm. With an argument of @var{0}, the current subterm is replaced by its parent term. @refill @item ? @itemx h @dfn{help} displays the table of options given above. @refill @end table @node Consult, Load Intro, Debug Options, Top @comment node-name, next, previous, up @section Consulting during Debugging @cindex reconsult It is possible, and sometimes useful, to consult a file whilst in the middle of program execution. Predicates, which have been successfully executed and are subsequently redefined by a consult and are later reactivated by backtracking, will not notice the change of their definitions. In other words, it is as if every predicate, when called, creates a virtual copy of its definition for backtracking purposes. @refill @node Load Intro, Load Predicates, Consult, Top @comment node-name, next, previous, up @chapter Loading Programs @cindex loading Programs can be loaded in three different ways: consulted or compiled from source files, or loaded from object files. The latter is the fastest way of loading programs, but of course requires that the programs have been compiled to object files first. Object files may be handy when developing large applications consisting of many source files, but are not strictly necessary since it is possible to save and restore entire execution states (@pxref{Misc Pred}). Consulted, or interpreted, predicates are equivalent to, but slower than, compiled ones. Although they use different representations, the two types of predicates can call each other freely. The SICStus Prolog compiler produces compact and efficient code, running about 8 times faster than consulted code, and requiring much less runtime storage. Compiled Prolog programs are comparable in efficiency with LISP programs for the same task. However, against this, compilation itself takes about twice as long as consulting and some debugging aids, such as tracing, are not applicable to compiled code. Spy-points can be placed on compiled predicates, however. @refill The compiler operates in three different modes, controlled by the ``Compilation mode'' flag (see @code{prolog_flag/3}). The possible states of the flag are: @table @code @item compactcode Compilation produces byte-coded abstract instructions (the default). @item fastcode Compilation produces native machine instructions. Only available for Sun-3 computers. Native code runs about 3 times faster than byte code. @item profiledcode Compilation produces byte-coded abstract instructions instrumented to produce execution profiling data. @xref{Profiling}. @end table @noindent The compilation mode can be changed by issuing the directive: @example | ?- prolog_flag(compiling, @var{OldValue}, @var{NewValue}). @end example A Prolog program consists of a sequence of @dfn{sentences} (@pxref{Sentence}). Commands and queries encountered among the sentences are executed immediately as they are encountered, unless they can be interpreted as @dfn{declarations} (@pxref{Declarations}), which affect the treatment of forthcoming clauses. Clauses are loaded as they are encountered. A Prolog program may also contain a list of sentences (including the empty list). This is treated as equivalent to those sentences occurring in place of the list. This feature makes it possible to have @code{term_expansion/2} (@pxref{Definite}) "return" a list of sentences, instead of a single sentence. @node Load Predicates, Declarations, Load Intro, Top @comment node-name, next, previous, up @section Predicates which Load Code @cindex consulting @findex consult/1 To consult a program, issue the directive: @example | ?- consult(Files). @end example @noindent where @var{Files} is either the name of a file (including the file @file{user}) or a list of filenames instructs the interpreter to read-in the program which is in the files. For example: @refill @example | ?- consult([dbase,'extras.pl',user]). @end example When a directive is read it is immediately executed. Any predicate defined in the files erases any clauses for that predicate already present in the interpreter. If the old clauses were loaded from a different file than the present one, the user will be queried first whether (s)he really wants the new definition. However, for existing predicates which have been declared as @code{multifile} (see below) new clauses will be added to the predicate, rather than replacing the old clauses. If clauses for some predicate appear in more than one file, the later set will effectively overwrite the earlier set. The division of the program into separate files does not imply any module structure---any predicate can call any other. @code{consult/1}, used in conjunction with @code{save/1} and @code{restore/1}, makes it possible to amend a program without having to restart from scratch and consult all the files which make up the program. The consulted file is normally a temporary ``patch'' file containing only the amended predicate(s). Note that it is possible to call @code{consult(user)} and then enter a patch directly on the terminal (ending with @ctrl{D}). This is only recommended for small, tentative patches. @refill @example | ?- [File|Files]. @end example @noindent This is a shorthand way of consulting a list of files. (The case where there is just one filename in the list was described earlier (@pxref{Reading In}). @refill @cindex compile @findex compile/1 To compile a program in-core, use the built-in predicate: @refill @example | ?- compile(Files). @end example @noindent where @var{Files} is specified just as for @code{consult/1}. @refill The effect of @code{compile/1} is very much like that of @code{consult}, except all new predicates will be stored in compiled rather than consulted form. However, predicates declared as dynamic (see below) will be stored in consulted form, even though @code{compile/1} is used. @refill @cindex fcompile @findex fcompile/1 To compile a program into an object file, use the built-in predicate: @example | ?- fcompile(Files). @end example @noindent where @var{Files} is specified just as for @code{consult/1}. For each filename in the list, the compiler will append the string @samp{.pl} to it and try to locate a source file with that name and compile it to an object file. The object filename if formed by appending the string @samp{.ql} to the specified name. The internal state of SICStus Prolog is not changed as result of the compilation. @refill @cindex load @findex load/1 To load a program from a set of object files, use the built-in predicate: @example | ?- load(Files). @end example @noindent where @var{Files} is either a single object filename (specified without the trailing @samp{.ql}) or a list of filenames. For each filename in the list, this predicate will first search for a file with the suffix @samp{.ql} added to the name given as an argument. If this fails it will look for a file with no extra suffix added. This directive has the same effect as if the source files had been compiled using @code{compile/1} directly (but see @pxref{Pitfalls}!). Finally, to ensure that some files has been compiled or loaded, use the built-in predicate: @example | ?- ensure_loaded(Files). @end example @noindent where @var{Files} is either a single filename or a list of filenames, similar to the arguments accepted by the above predicates. The predicate takes the following action for each @var{File} in the list of filenames: @refill @enumerate @item If the @var{File} is @code{user}, @code{compile(user)} is performed; @item If @var{File} cannot be found, not even with a @samp{.pl} or @samp{.ql} extension, an error is signalled; @item If an object file is found which has not yet been loaded or which has been modified since it was last loaded, the file is loaded; @item If a source file is found which has not yet been loaded or which has been modified since it was last loaded, the file is compiled; @item If both a source file and an object file are found, item 3 or 4 applies depending on which file was modified most recently; @item Otherwise, no action is taken. @end enumerate Note that @code{ensure_loaded/1} does @emph{not} cause object files to become recompiled. @node Declarations, Pitfalls, Load Predicates, Top @comment node-name, next, previous, up @section Declarations @cindex declaration When a program is to be loaded, it is sometimes necessary to tell the system to treat some of the predicates specially. This information is supplied by including @dfn{declarations} about such predicates in the source file, preceding any clauses for the predicates which they concern. A declaration is written just as a command, beginning with @samp{:- }. A declaration is effective from its occurrence through the end of file. Although declarations that affect more than one predicate may be collapsed into a single declaration, the recommended style is to write the declarations for a predicate immediately before its first clause. The following two declarations are relevant both in Quintus Prolog and in SICStus Prolog: @cindex multifile declaration @example :- multifile @var{PredSpec}, @dots{}, @var{PredSpec}. @end example @noindent causes the specified predicates to be @code{multifile}. This means that if more clauses are subsequently loaded from other files for the same predicate, the new clauses will not replace the old ones, but will be added at the end instead. The old clauses are erased only if the predicate is reloaded from its ``home file'' (the one containing the multifile declaration), if it is reloaded from a different file declaring the predicate as multifile (in which case the user is queried first), or if it is explicitly abolished. Furthermore the compilation mode of the ``home file'' determines the compilation mode of any subsequently loaded clauses. For example, if the ``home file'' declares the predicate as multifile and dynamic, any subsequent clauses will be stored in consulted form even if loaded by @code{compile/1}. If the ``home file'' was compiled to native code, any subsequent clauses will also be compiled to native code even if the compilation mode for the subsequent file was @code{compactcode}. Multifile declarations @emph{must precede} any other declarations for the same predicate(s)! @cindex dynamic declaration @example :- dynamic @var{PredSpec}, @dots{}, @var{PredSpec}. @end example @noindent @cindex dynamic predicate @cindex predicate, dynamic where each @var{PredSpec} is a predicate spec, causes the specified predicates to become @dfn{dynamic}, which means that other predicates may inspect and modify them, adding or deleting individual clauses. Dynamic predicates are always stored in consulted form even if a compilation is in progress. This declaration is meaningful even if the file contains no clauses for a specified predicate---the effect is then to define a dynamic predicate with no clauses. The following declaration is not normally relevant in any Prologs but SICStus Prolog: @cindex wait declaration @example :- wait @var{PredSpec}, @dots{}, @var{PredSpec}. @end example @cindex blocking @noindent introduces an exception to the rule that goals be run strictly from left to right within a clause. Goals for the specified predicates are @dfn{blocked} if the first argument of the goal is uninstantianted. The behaviour of blocking goals on the first argument cannot be switched off, except by abolishing or redefining the predicate. @xref{Procedural}. The following two declarations are sometimes relevant in other Prologs, but are ignored by SICStus Prolog. They are however accepted for compatibility reasons: @cindex public declaration @example :- public @var{PredSpec}, @dots{}, @var{PredSpec}. @end example @noindent In some Prologs, this declaration is necessary for making compiled predicates visible for the interpreter. In SICStus Prolog, any predicate may call any other, and all are visible. @cindex mode declaration @example :- mode @var{ModeSpec}, @dots{}, @var{ModeSpec}. @end example @noindent where each @var{ModeSpec} is a mode spec. In some Prologs, this declaration helps reduce the size of the compiled code for a predicate, and may speed up its execution. Unfortunately, writing mode declarations can be error-prone, and since errors in mode declaration do not show up while running the predicates interpretively, new bugs may show up when predicates are compiled. SICStus Prolog ignores mode declarations. However, mode declarations may be used as a commenting device, as they express the programmer's intention of data flow in predicates. If you do so, use only the atoms @code{+}, @code{-}, and @code{?} as arguments in your mode specs, as in @example :- mode append(+, +, -). @end example @node Pitfalls, Indexing, Declarations, Top @comment node-name, next, previous, up @section Pitfalls of File-To-File Compilation @cindex pitfalls of fcompile @cindex fcompile, pitfalls of When loading clauses belonging to a multifile predicate from an object file different from the predicate's ``home file'', the compilation mode used when the new clauses were compiled must match that of the current clauses. Otherwise, the new clauses are ignored and a warning message is issued. When compiling to an object file, remember that directives occurring in the source file are executed at @emph{run time}, not at compile time. For instance, it does not work to include directives that assert clauses of @code{term_expansion/2} (q.v.) and rely on the new transformations to be effective for subsequent clauses of the same file or subsequent files of the same compilation. For a definition of @code{term_expansion/2} to take effect, it should be loaded as a separate file before being used in the compilation of another file. Operator declarations (q.v.) are an exception to the above rule. If the compiler encounters a command @example :- op(@var{P}, @var{T}, @var{N}). @end example @noindent that command will be executed at compile time as well as at run time. @node Indexing, Tail, Pitfalls, Top @comment node-name, next, previous, up @section Indexing @cindex indexing The clauses of any predicate are @dfn{indexed} according to the principal functor of the first argument in the head of the clause. This means that the subset of clauses which match a given goal, as far as the first step of unification is concerned, is found very quickly, in practically constant time (i.e. in a time independent of the number of clauses of the predicate). This can be very important where there is a large number of clauses for a predicate. Indexing also improves the Prolog system's ability to detect determinacy---important for conserving working storage. @node Tail, Built Intro, Indexing, Top @comment node-name, next, previous, up @section Tail Recursion Optimisation @cindex tail recursion The compiler incorporates @dfn{tail recursion optimisation} to improve the speed and space efficiency of determinate predicates. When execution reaches the last goal in a clause belonging to some predicate, and provided there are no remaining backtrack points in the execution so far of that predicate, all of the predicate's local working storage is reclaimed @emph{before} the final call, and any structures it has created become eligible for garbage collection. This means that programs can now recurse to arbitrary depths without necessarily exceeding core limits. For example: @example cycle(State) :- transform(State, State1), cycle(State1). @end example @noindent where @code{transform/2} is a determinate predicate, can continue executing indefinitely, provided each individual structure, @var{State}, is not too large. The predicate cycle is equivalent to an iterative loop in a conventional language. @refill To take advantage of tail recursion optimisation one must ensure that the Prolog system can recognise that the predicate is determinate at the point where the recursive call takes place. That is, the system must be able to detect that there are no other solutions to the current goal to be found by subsequent backtracking. In general this involves reliance on the Prolog compiler's indexing and/or use of cut, @pxref{Cut}. @node Built Intro, Input Output, Tail, Top @comment node-name, next, previous, up @chapter Built-In Predicates It is not possible to redefine built-in predicates. An attempt to do so will give an error message. @xref{Pred Summary}. @refill SICStus Prolog provides a wide range of built-in predicates to perform the following tasks: @display Input / Output Reading-in Programs Input and Output of Terms Character IO Stream IO Dec-10 Prolog File IO Arithmetic Comparison of Terms Control Information about the State of the Program Meta-Logical Modification of the Program Internal Database All Solutions Interface to Foreign Language Functions Debugging Definite Clause Grammars Miscellaneous @end display @noindent The following descriptions of the built-in predicates are grouped according to the above categorisation of their tasks. @node Input Output, Read In, Built Intro, Top @comment node-name, next, previous, up @section Input / Output @cindex input @cindex output @cindex stream @cindex file There are two sets of file manipulation predicates in SICStus Prolog. One set is inherited from DEC-10 Prolog. These predicates always refer to a file by name. The other set of predicates is inherited from Quintus Prolog and refer to files as streams. Streams correpond to the file pointers used at the operating system level. @refill A stream can be opened and connected to a filename or UNIX file descriptor for input or output by calling the predicate @code{open/3}. @code{open/3} will return a reference to a stream. The stream may then be passed as an argument to various IO predicates. The predicate @code{close/1} is used for closing a stream. The predicate @code{current_stream/3} is used for retrieving information about a stream, and for finding the currently existing streams. @refill The possible formats of a stream are: @table @code @item '$stream'(@var{X},@var{Y}) A stream connected to some file. @var{X} and @var{Y} are integers. @item user_input The standard input stream, i.e. the terminal, usually. @item user_output The standard output stream, i.e. the terminal, usually. @item user_error The standard error stream. @end table @cindex current input stream @cindex current output stream The DEC-10 Prolog IO predicates manipulate streams implicitly, by maintaining the notion of a @dfn{current input stream} and a @dfn{current output stream}. The current input and output streams are set to the @code{user_input} and @code{user_output} initially and for every new break (@pxref{Nested}). The predicates @code{see/1} and @code{tell/1} can be used for setting the current input and output streams (respectively) to newly opened streams for particular files. The predicates @code{seen/0} and @code{told/0} close the current input and output streams (respectively), and reset them to the standard input and output streams. The predicates @code{seeing/1} and @code{telling/1} are used for retrieving the filename associated with the current input and output streams (respectively). @cindex filename The possible formats of a filename are: @table @asis @item @code{user} This ``filename'' stands for the standard input or output stream, depending on context. Terminal output is only guaranteed to be displayed after a newline is written or @code{ttyflush/0} is called. @refill @item @code{library(File)} where @var{File} is an atom, denotes a file @var{File} (with an optional @samp{.pl} suffix when consulting or compiling or an optional @samp{.ql} suffix in @code{load/1}) sought in the directory path(s) specified by the user defined predicate @code{library_directory/1}. @refill @item @var{File} where @var{File} is any atom other than @code{user}, denotes a file @var{File} (with optional suffixes as above) sought in the current working directory. @refill @end table Filename components beginning which with @samp{~} or @samp{$} are treated specially. For example, @table @code @item '~/sample.pl' is equivalent to @file{'/home/sics/al/sample.pl'}, if @file{/home/sics/al} is the user's home directory. (This is also equivalent to @file{'$HOME/sample.pl'} as explained below.) @refill @item '~clyde/sample.pl' is equivalent to @file{'/home/sics/clyde/sample.pl'}, if @file{/home/sics/clyde} is Clyde's home directory. @refill @item '$UTIL/sample.pl' is equivalent to @file{'/usr/local/src/utilities/sample.pl'}, if @file{/usr/local/src/utilities} is the value of the environment variable @code{UTIL}, as defined by the shell command @code{setenv}. @refill @end table Failure to open a file normally causes an abort. This behaviour can be turned off and on by of the built-in predicates @code{nofileerrors/0} and @code{fileerrors/0} decribed below. @refill @node Read In, Term IO, Input Output, Top @comment node-name, next, previous, up @subsection Reading-in Programs If the predicates discussed in this section are invoked in the scope of the interactive toplevel, filenames are relative to the current working directory. If invoked recursively, i.e. in the scope of another invocation of one of these predicates, filenames are relative to the directory of the file being read in. @xref{Load Intro} for an introduction to these predicates. @refill @cindex loading @cindex consulting @cindex compilation @table @code @item consult(@var{+Files}) @itemx reconsult(@var{+Files}) @itemx [] @itemx [@var{+File}|@var{+Files}] @findex consult/1 @findex reconsult/1 @findex []/0, consult @findex ./2, consult Consults the source file or list of files specified by @var{Files}. @item compile(@var{+Files}) @findex compile/1 Compiles the source file or list of files specified by @var{Files}. The compiled code is placed in-core, i.e. is added incrementally to the Prolog database. @refill @item fcompile(@var{+Files}) @findex fcompile/1 Compiles the source file or list of files specified by @var{Files}. The suffix @samp{.pl} is added to the given filenames to yield the real source filenames. The compiled code is placed on the object file or list of files formed by adding the suffix @samp{.ql} to the given filenames. @refill @item load(@var{+Files}) @findex load/1 Loads the object file or list of files specified by @var{Files}. @item ensure_loaded(@var{+Files}) @findex ensure_loaded/1 Compiles or loads the file or list of files specified by @var{Files}, comparing last modified times with the time that the file was last read in. @item source_file(@var{?File}) @itemx source_file(@var{?Pred},@var{?File}) @findex source_file/1 @findex source_file/2 The predicate @var{Pred} is defined in the file @var{File}. @refill @end table @node Term IO, Char IO, Read In, Top @comment node-name, next, previous, up @subsection Input and Output of Terms @cindex term io Several IO predicates that use the current input or output stream available in an alternative version where the stream is specified explicitly. The rule is that the stream is the first argument, which defaults to the current input or output stream, depending on context. @refill @table @code @item read(@var{?Term}) @itemx read(@var{+Stream},@var{?Term}) @findex read/1 @findex read/2 The next term, delimited by a full-stop (i.e. a @kbd{.} followed by either a space or a control character), is read from @var{Stream} and is unified with @var{Term}. The syntax of the term must agree with current operator declarations. If a call @code{read(@var{Stream, Term})} causes the end of @var{Stream} to be reached, @var{Term} is unified with the term @code{end_of_file}. Further calls to @code{read/2} for the same stream will then cause an error failure, unless the stream is connected to the terminal. @refill @item write(@var{?Term}) @itemx write(@var{+Stream},@var{?Term}) @findex write/1 @findex write/2 The term @var{Term} is written onto @var{Stream} according to current operator declarations. @refill @item display(@var{?Term}) @findex display/1 The term @var{Term} is displayed @emph{onto the standard output stream} (which is not necessarily the current output stream) in standard parenthesised prefix notation. @refill @item write_canonical(@var{?Term}) @itemx write_canonical(@var{+Stream},@var{?Term}) @findex write_canonical/1 @findex write_canonical/2 Similar to @code{write(@var{Stream},@var{Term})}. The term will be written according to the standard syntax. The output from @code{write_canonical/2} can be parsed by @code{read/2} even if the term contains special characters or if operator declarations have changed. @refill @item writeq(@var{?Term}) @itemx writeq(@var{+Stream},@var{?Term}) @findex writeq/1 @findex writeq/2 Similar to @code{write(@var{Stream},@var{Term})}, but the names of atoms and functors are quoted where necessary to make the result acceptable as input to @code{read/2}. @refill @item print(@var{?Term}) @itemx print(@var{+Stream},@var{?Term}) @findex print/1 @findex print/2 Print @var{Term} onto @var{Stream}. This predicate provides a handle for user defined pretty printing: @itemize @bullet @item If @var{Term} is a variable then it is output using @code{write(@var{Stream},@var{Term})}. @refill @item If @var{Term} is non-variable then a call is made to the user defined predicate @code{portray/1}. If this succeeds then it is assumed that @var{Term} has been output. @refill @item Otherwise @code{print/2} is called recursively on the components of @var{Term}, unless @var{Term} is atomic in which case it is written via @code{write/2}. @refill @end itemize In particular, the debugging package prints the goals in the tracing messages, and the interpreter top level prints the final values of variables. Thus you can vary the forms of these messages if you wish. @refill Note that on lists (@code{[_|_]}), @code{print/2} will first give the whole list to @code{portray/1}, but if this fails it will only give each of the (top level) elements to @code{portray/1}. That is, @code{portray/1} will not be called on all the tails of the list. @refill @item portray(@var{?Term}) @findex portray/1 @emph{A user defined predicate.} This should either print the @var{Term} and succeed, or do nothing and fail. In the latter case, the default printer (@code{write/1}) will print the @var{Term}. @refill @item portray_clause(@var{+Clause}) @itemx portray_clause(@var{+Stream},@var{+Clause}) @findex portray_clause/1 @findex portray_clause/2 This writes the clause @var{Clause} onto @var{Stream} exactly as @code{listing/0-1} would have written it, including a period at the end. @refill @item format(@var{+Format},@var{+Arguments}) @itemx format(@var{+Stream},@var{+Format},@var{+Arguments}) @findex format/2 @findex format/3 Print @var{Arguments} onto @var{Stream} according to format @var{Format}. @var{Format} is a list of formatting characters. If @var{Format} is an atom then @code{name/2} (@pxref{Meta Logic}) will be used to translate it into a list of characters. Thus @refill @example | ?- format("Hello world!", []). @end example @noindent has the same effect as @example | ?- format('Hello world!', []). @end example @code{format/3} is a Prolog interface to the C @code{stdio} function @code{printf()}. It is due to Quintus Prolog. @refill @var{Arguments} is a list of items to be printed. If there is only one item it may be supplied as an atom. If there are no items then an empty list should be supplied. @refill The default action on a format character is to print it. The character @kbd{~} introduces a control sequence. To print a @kbd{~} repeat it: @refill @example | ?- format("Hello ~~world!", []). @end example @noindent will result in @example Hello ~world! @end example A format may be spread over several lines. The control sequence @kbd{\c} followed by a @key{LFD} will translate to the empty string: @refill @example | ?- format("Hello \c world!", []). @end example @noindent will result in @example Hello world! @end example The general format of a control sequence is @samp{~@var{N}@var{C}}. The character @var{C} determines the type of the control sequence. @var{N} is an optional numeric argument. An alternative form of @var{N} is @samp{*}. @samp{*} implies that the next argument in @var{Arguments} should be used as a numeric argument in the control sequence. Example: @refill @example | ?- format("Hello~4cworld!", [0'x]). @end example @noindent and @example | ?- format("Hello~*cworld!", [4,0'x]). @end example @noindent both produce @example Helloxxxxworld! @end example The following control sequences are available. @table @samp @item ~a The argument is an atom. The atom is printed without quoting. @refill @item ~@var{N}c (Print character.) The argument is a number that will be interpreted as an ASCII code. @var{N} defaults to one and is interpreted as the number of times to print the character. @refill @item ~@var{N}e @itemx ~@var{N}E @itemx ~@var{N}f @itemx ~@var{N}g @itemx ~@var{N}G (Print float). The argument is a float. The float and @var{N} will be passed to the C @code{printf()} function as @refill @example printf("%.@var{N}e", @var{Arg}) printf("%.@var{N}E", @var{Arg}) printf("%.@var{N}f", @var{Arg}) printf("%.@var{N}g", @var{Arg}) printf("%.@var{N}G", @var{Arg}) @end example If @var{N} is not supplied the action defaults to @example printf("%e", @var{Arg}) printf("%E", @var{Arg}) printf("%f", @var{Arg}) printf("%g", @var{Arg}) printf("%G", @var{Arg}) @end example @item ~@var{N}d (Print decimal.) The argument is an integer. @var{N} is interpreted as the number of digits after the decimal point. If @var{N} is 0 or missing, no decimal point will be printed. Example: @refill @example | ?- format("Hello ~1d world!", [42]). | ?- format("Hello ~d world!", [42]). @end example @noindent will print as @example Hello 4.2 world! Hello 42 world! @end example @noindent respectively. @item ~@var{N}D (Print decimal.) The argument is an integer. Identical to @samp{~@var{N}d} except that @samp{,} will separate groups of three digits to the left of the decimal point. Example: @refill @example | ?- format("Hello ~1D world!", [12345]). @end example @noindent will print as @example Hello 1,234.5 world! @end example @item ~@var{N}r (Print radix.) The argument is an integer. @var{N} is interpreted as a radix. @var{N} should be >= 2 and <= 36. If @var{N} is missing the radix defaults to 8. The letters @samp{a-z} will denote digits larger than 9. Example: @refill @example | ?- format("Hello ~2r world!", [15]). | ?- format("Hello ~16r world!", [15]). @end example @noindent will print as @example Hello 1111 world! Hello f world! @end example @noindent respectively. @item ~@var{N}R (Print radix.) The argument is an integer. Identical to @samp{~@var{N}r} except that the letters @samp{A-Z} will denote digits larger than 9. Example: @refill @example | ?- format("Hello ~16R world!", [15]). @end example @noindent will print as @example Hello F world! @end example @item ~@var{N}s (Print string.) The argument is a list of ASCII codes. Exactly @var{N} characters will be printed. @var{N} defaults to the length of the string. Example: @refill @example | ?- format("Hello ~4s ~4s!", ["new","world"]). | ?- format("Hello ~s world!", ["new"]). @end example @noindent will print as @example Hello new worl! Hello new world! @end example @noindent respectively. @item ~i (Ignore argument.) The argument may be of any type. The argument will be ignored. Example: @refill @example | ?- format("Hello ~i~s world!", ["old","new"]). @end example @noindent will print as @example Hello new world! @end example @item ~k (Print canonical.) The argument may be of any type. The argument will be passed to @code{write_canonical/2} (@pxref{Term IO}). Example: @refill @example | ?- format("Hello ~k world!", [[a,b,c]]). @end example @noindent will print as @example Hello .(a,.(b,.(c,[]))) world! @end example @item ~p (print.) The argument may be of any type. The argument will be passed to @code{print/2} (@pxref{Term IO}). Example: @refill @example | ?- assert((portray([X|Y]) :- print(cons(X,Y)))). | ?- format("Hello ~p world!", [[a,b,c]]). @end example @noindent will print as @example Hello cons(a,cons(b,cons(c,[]))) world! @end example @item ~q (Print quoted.) The argument may be of any type. The argument will be passed to @code{writeq/2} (@pxref{Term IO}). Example: @refill @example | ?- format("Hello ~q world!", [['A','B']]). @end example @noindent will print as @example Hello ['A','B'] world! @end example @item ~w (write.) The argument may be of any type. The argument will be passed to @code{write/2} (@pxref{Term IO}). Example: @refill @example | ?- format("Hello ~w world!", [['A','B']]). @end example @noindent will print as @example Hello [A,B] world! @end example @item ~@var{N}n (Print newline.) Print @var{N} newlines. @var{N} defaults to 1. Example: @refill @example | ?- format("Hello ~n world!", []). @end example @noindent will print as @example Hello world! @end example @item ~N (Fresh line.) Print a newline, if not already at the beginning of a line. @end table The following control sequences are also available for compatibility, but do not perform any useful functions. @table @samp @item ~@var{N}| (Set tab.) Set a tab stop at position @var{N}, where @var{N} defaults to the current position, and advance the current position there. @item ~@var{N}+ (Advance tab.) Set a tab stop at @var{N} positions past the current position, where @var{N} defaults to 8, and advance the current position there. @item ~@var{N}t (Set fill character.) Set the fill character to be used in the next position movement to @var{N}, where @var{N} defaults to @key{SPC}. @end table @end table @node Char IO, Stream Pred, Term IO, Top @comment node-name, next, previous, up @subsection Character Input/Output @cindex char io There are two sets of character IO predicates. The first set uses the current input and output streams, while the second set always uses the standard input and output streams. The first set is available in an alternative version where the stream is specified explicitly. The rule is that the stream is the first argument, which defaults to the current input or output stream, depending on context. @refill @table @code @item nl @itemx nl(@var{+Stream}) @findex nl/0 @findex nl/1 A new line is started on @var{Stream} by printing a line feed (@key{LFD}). If @var{Stream} is the terminal, its buffer is flushed. @refill @item get0(@var{?N}) @itemx get0(@var{+Stream},@var{?N}) @findex get0/1 @findex get0/2 @var{N} is the ASCII code of the next character read from @var{Stream}. @refill @item get(@var{?N}) @item get(@var{+Stream},@var{?N}) @findex get/2 @var{N} is the ASCII code of the next non-blank non-layout character read from @var{Stream}. @refill @item skip(@var{+N}) @itemx skip(@var{+Stream},@var{+N}) @findex skip/1 @findex skip/2 Skips just past the next ASCII character code @var{N} from @var{Stream}. @var{N} may be an arithmetic expression. @refill @item put(@var{+N}) @itemx put(@var{+Stream},@var{+N}) @findex put/1 @findex put/2 ASCII character code @var{N} is output onto @var{Stream}. @var{N} may be an arithmetic expression. @refill @item tab(@var{+N}) @itemx tab(@var{+Stream},@var{+N}) @findex tab/1 @findex tab/2 @var{N} spaces are output onto @var{Stream}. @var{N} may be an arithmetic expression. @refill @end table The above predicates are the ones which are the most commonly used, as they can refer to any streams. In most cases these predicates are sufficient, but there is one limitation: if you are writing to the terminal, the output is not guaranteed to be visible until a newline character is written. If this line by line output is inadequate, you have to use @code{ttyflush/0} (see below). @refill The predicates which follow always refer to the terminal. They are convenient for writing interactive programs which also perform file IO. @table @code @item ttynl @findex ttynl/0 A new line is started on the standard output stream and its buffer is flushed. @refill @item ttyflush @findex ttyflush/0 Flushes the standard output stream buffer. Output to the terminal normally simply goes into an output buffer until such time as a newline is output. Calling this predicate forces any characters in this buffer to be output immediately. @refill @item ttyget0(@var{?N}) @findex ttyget0/1 @var{N} is the ASCII code of the next character input from the standard input stream. @refill @item ttyget(@var{?N}) @findex ttyget/1 @var{N} is the ASCII code of the next non-blank printable character from the standard input stream. @refill @item ttyput(@var{+N}) @findex ttyput/1 The ASCII character code @var{N} is output to the standard output stream. @var{N} may be an arithmetic expression. @refill @item ttyskip(@var{+N}) @findex ttyskip/1 Skips to just past the next ASCII character code @var{N} from the standard input stream. @var{N} may be an arithmetic expression. @refill @item ttytab(@var{+N}) @findex ttytab/1 @var{N} spaces are output to the standard output stream. @var{N} may be an arithmetic expression. @refill @end table @node Stream Pred, File Pred, Char IO, Top @comment node-name, next, previous, up @subsection Stream IO The following predicates manipulate streams. Character and line counts are maintained per stream. All streams connected to the terminal, however, share the same set of counts. For example, writing to @code{user_output} will advance the counts for @code{user_input}, if both are connected to the terminal. @table @code @item open(@var{+FileName},@var{+Mode},@var{-Stream}) @findex open/3 If @var{FileName} is a valid file name, the file is opened in mode @var{Mode} (invoking the UNIX function @code{fopen}) and the resulting stream is unified with @var{Stream}. @var{Mode} is one of: @refill @table @code @item read Open the file for input. @item write Open the file for output. The file is created if it does not already exist, the file will otherwise be truncated. @refill @item append Open the file for output. The file is created if it does not already exist, the file will otherwise be appended to. @refill @end table If @var{FileName} is an integer, it is assumed to be a file descriptor passed to Prolog from a foreign function call. The file descriptor is connected to a Prolog stream (invoking the UNIX function @code{fdopen}) which is unified with @var{Stream}. @refill @item close(@var{+X}) @findex close/1 If @var{X} is a stream the stream is closed. If @var{X} is the name of a file opened by @code{see/1} or @code{tell/1} the corresponding stream is closed. @refill @item absolute_file_name(@var{+RelativeName},@var{?AbsoluteName}) @findex absolute_file_name/2 This predicate is used by all predicates that refer to filenames for resolving these. The argument @var{RelativeName} is interpreted as a filename according to the filename syntax rules (@pxref{Input Output}). If the specified file is found (possibly with a @samp{.pl} or @samp{.ql} extension if consulting or compiling source files or loading object files), @var{AbsoluteName} is unified with the full path name of this file. If @var{RelativeName} is @code{user}, then @var{AbsoluteName} is also unified with @code{user}; this ``filename'' stands for the standard input or output stream, depending on context. @refill @item current_input(@var{?Stream}) @findex current_input/1 Unify @var{Stream} with the current input stream. @item current_output(@var{?Stream}) @findex current_output/1 Unify @var{Stream} with the current output stream. @item current_stream(@var{?FileName},@var{?Mode},@var{?Stream}) @findex current_stream/3 @var{Stream} is a stream which was opened in mode @var{Mode} and which is connected to the absolute file name @var{Filename} (an atom) or to the file descriptor @var{Filename} (an integer). This predicate can be used for enumerating all currently open streams through backtracking. @refill @item set_input(@var{+Stream}) @findex set_input/1 Set the current input stream to @var{Stream}. @item set_output(@var{+Stream}) @findex set_output/1 Set the current output stream to @var{Stream}. @item flush_output(@var{+Stream}) @findex flush_output/1 Flush all internally buffered characters for @var{Stream} to the operating system. @refill @item library_directory(@var{?Directory}) @findex library_directory/1 @emph{A user defined predicate.} This predicate specifies a set of directories to be searched when a file specification of the form @code{library(@var{Name})} is used. The directories are searched until a file with the name @file{@var{Name}.@var{Suffix}} or @file{@var{Name}} is found (@pxref{Input Output}), where @var{Suffix} is @samp{ql} when loading object files and @samp{pl} otherwise. @refill Directories to be searched may be added by using @code{asserta/1} or @code{assertz/1} (@pxref{Modify Prog}), provided that @code{library_directory/1} has been declared to be dynamic: @refill @example | ?- assertz(library_directory(@var{Directory})). @end example @item open_null_stream(@var{-Stream}) @findex open_null_stream/1 Open an output stream to the null device. Everything written to this stream will be thrown away. @refill @item character_count(@var{?Stream},@var{?Count}) @findex character_count/2 @var{Count} characters have been read from or written to the stream @var{Stream}. @item line_count(@var{?Stream},@var{?Count}) @findex line_count/2 @var{Count} lines have been read from or written to the stream @var{Stream}. @item line_position(@var{?Stream},@var{?Count}) @findex line_position/2 @var{Count} characters have been read from or written to the current line of the stream @var{Stream}. @item stream_code(@var{+Stream},@var{?StreamCode}) @itemx stream_code(@var{?Stream},@var{+StreamCode}) @findex stream_code/2 @var{StreamCode} is the file descriptor (an integer) corresponding to the Prolog stream @var{Stream}. This predicate is only useful when streams are passed between Prolog and C. A C function wishing to perform I/O on a stream may compute the @code{FILE *} stream pointer as @samp{stdin + fd}, where @samp{fd} is the file descriptor passed from Prolog. Conversely, the file descriptor can be computed as @samp{fileno(s)} from the @code{FILE *} stream pointer @samp{s}. @refill @emph{Warning:} Mixing C I/O and Prolog I/O on the same stream is not recommended practice. The problem is that the character and line counts for a stream are only kept up to date for Prolog I/O (see @code{character_count/2}, @code{line_count/2}, and @code{line_position/2}. @refill @item fileerrors @findex fileerrors/0 Undoes the effect of @code{nofileerrors/0}. @item nofileerrors @findex nofileerrors/0 After a call to this predicate, failure to locate or open a file will cause the operation to fail instead of the default action, which is to type an error message and then abort execution. @refill @end table @node File Pred, IO Example, Stream Pred, Top @comment node-name, next, previous, up @subsection DEC-10 Prolog File IO The following predicates manipulate files. @table @code @item see(@var{+File}) @findex see/1 File @var{File} becomes the current input stream. @var{File} may be a stream previously opened by @code{see/1} or a filename. If it is a filename, the following action is taken: If there is a stream opened by @code{see/1} associated with the same file already, then it becomes the current input stream. Otherwise, the file @var{File} is opened for input and made the current input stream. @refill @item seeing(@var{?FileName}) @findex seeing/1 @var{FileName} is unified with the name of the current input file, if it was opened by @code{see/1}, with the current input stream, if it is not @code{user_input}, otherwise with @code{user}. @item seen @findex seen/0 Closes the current input stream, and resets it to @code{user_input}. @item tell(@var{+File}) @findex tell/1 File @var{File} becomes the current output stream. @var{File} may be a stream previously opened by @code{tell/1} or a filename. If it is a filename, the following action is taken: If there is a stream opened by @code{tell/1} associated with the same file already, then it becomes the current output stream. Otherwise, the file @var{File} is opened for output and made the current output stream. @item telling(@var{?FileName}) @findex telling/1 @var{FileName} is unified with the name of the current output file, if it was opened by @code{tell/1}, with the current output stream, if it is not @code{user_output}, otherwise with @code{user}. @item told @findex told/0 Closes the current output stream, and resets it to @code{user_output}. @end table @node IO Example, Arithmetic, File Pred, Top @comment node-name, next, previous, up @subsection An Example Here is an example of a common form of file processing: @example @group process_file(F) :- seeing(OldInput), see(F), % Open file F repeat, read(T), % Read a term process_term(T), % Process it T == end_of_file, % Loop back if not at end of file !, seen, % Close the file see(OldInput). @end group @end example @cindex repeat loop The above is an example of a @dfn{repeat loop}. Nearly all sensible uses of @code{repeat/0} follow the above pattern. Note the use of a cut to terminate the loop. @node Arithmetic, Term Compare, IO Example, Top @comment node-name, next, previous, up @section Arithmetic @cindex arithmetic @cindex range of numbers @cindex numbers, range of Arithmetic is performed by built-in predicates which take as arguments @dfn{arithmetic expressions} and evaluate them. An arithmetic expression is a term built from numbers, variables, and functors that represent arithmetic functions. At the time of evaluation, each variable in an arithmetic expression must be bound to a non-variable expression. An expression evaluates to a number, which may be an @dfn{integer} or a @dfn{float}. The range of integers is @code{[-2^2147483616, 2^2147483616)}. Thus for all practical purposes, the range of integers can be considered infinite. The range of floats is the one provided by the C @code{double} type, typically @code{[4.9e-324, 1.8e+308]} (plus or minus). Only certain functors are permitted in an arithmetic expression. These are listed below, together with an indication of the functions they represent. @var{X} and @var{Y} are assumed to be arithmetic expressions. Unless stated otherwise, an expression evaluates to a float if any of its arguments is a float, otherwise to an integer. @refill @table @code @item @var{X}+@var{Y} @findex +/2, addition This evaluates to the sum of @var{X} and @var{Y}. @item @var{X}-@var{Y} @findex -/2, subtraction This evaluates to the difference of @var{X} and @var{Y}. @item @var{X}*@var{Y} @findex */2, multiplication This evaluates to the product of @var{X} and @var{Y}. @item @var{X}/@var{Y} @findex / /2, floating division This evaluates to the quotient of @var{X} and @var{Y}. The value is always a @emph{float}. @item @var{X}//@var{Y} @findex // /2, integer division This evaluates to the @emph{integer} quotient of @var{X} and @var{Y}. @item @var{X} mod @var{Y} @findex mod/2 This evaluates to the @emph{integer} remainder after dividing @var{X} by @var{Y}. @item -@var{X} @findex -/1, unary minus This evaluates to the negative of @var{X}. @item integer(@var{X}) @findex integer/1, coercion This evaluates to the nearest integer between @var{X} and 0, if @var{X} is a float, otherwise to @var{X} itself. @item float(@var{X}) @findex float/1, coercion This evaluates to the floating-point equivalent of @var{X}, if @var{X} is an integer, otherwise to @var{X} itself. @item @var{X}/\@var{Y} @findex /\ /2, bitwise conjunction This evaluates to the bitwise conjunction of the integers @var{X} and @var{Y}. @item @var{X}\/@var{Y} @findex \/ /2, bitwise disjunction This evaluates to the bitwise disjunction of the integers @var{X} and @var{Y}. @item @var{X}^@var{Y} @findex ^/2, bitwise exclusive or This evaluates to the bitwise exclusive or of the integers @var{X} and @var{Y}. @item \(@var{X}) @findex \ /1, bitwise negation This evaluates to the bitwise negation of the integer @var{X}. @item @var{X}<<@var{Y} @findex << /2, left shift Bitwise left shift of @var{X} by @var{Y} places. @item X>>Y @findex >> /2, right shift Bitwise right shift of @var{X} by @var{Y} places. @item [@var{X}] A list of just one element evaluates to @var{X} if @var{X} is a number. Since a quoted string is just a list of integers, this allows a quoted character to be used in place of its ASCII code; e.g. @code{"A"} behaves within arithmetic expressions as the integer 65. @refill @end table Variables in an arithmetic expression which is to be evaluated may be bound to other arithmetic expressions rather than just numbers, e.g. @example evaluate(Expression, Answer) :- Answer is Expression. | ?- evaluate(24*9, Ans). Ans = 216 ? yes @end example @noindent This works even for compiled code. Arithmetic expressions, as described above, are just data structures. If you want one evaluated you must pass it as an argument to one of the built-in predicates listed below. Note that @code{is/2} only evaluates one of its arguments, whereas the comparison predicates evaluate both. In the following, @var{X} and @var{Y} stand for arithmetic expressions, and @var{Z} for some term. @refill @table @code @item @var{Z} is @var{X} @findex is/2 The arithmetic expression @var{X} is evaluated and the result is unified with @var{Z}. Fails if @var{X} is not an arithmetic expression. @refill @item @var{X} =:= @var{Y} @findex =:= /2, arithmetic equal The numeric values of @var{X} and @var{Y} are equal. @item @var{X} =\= @var{Y} @findex =\= /2, arithmetic not equal The numeric values of @var{X} and @var{Y} are not equal. @item @var{X} < @var{Y} @findex < /2, arithmetic less than The numeric value of @var{X} is less than the numeric value of @var{Y}. @item @var{X} > @var{Y} @findex > /2, arithmetic greater than The numeric value of @var{X} is greater than the numeric value of @var{Y}. @item @var{X} =< @var{Y} @findex =< /2, arithmetic less or equal The numeric value of @var{X} is less than or equal to the numeric value of @var{Y}. @refill @item @var{X} >= @var{Y} @findex >= /2, arithmetic greater or equal The numeric value of @var{X} is greater than or equal to the numeric value of @var{Y}. @refill @end table @node Term Compare, Control, Arithmetic, Top @comment node-name, next, previous, up @section Comparison of Terms @cindex term comparison @cindex comparing terms @cindex standard order These built-in predicates are meta-logical. They treat uninstantiated variables as objects with values which may be compared, and they never instantiate those variables. They should @emph{not} be used when what you really want is arithmetic comparison (@pxref{Arithmetic}) or unification. @refill The predicates make reference to a @dfn{standard total ordering} of terms, which is as follows: @itemize @bullet @item Variables, in a standard order (roughly, oldest first---the order is @emph{not} related to the names of variables). @refill @item Integers, in numeric order (e.g. -1 is put before 1). @item Floats, in numeric order (e.g. -1.0 is put before 1.0). @item Atoms, in alphabetical (i.e. ASCII) order. @item Compound terms, ordered first by arity, then by the name of the principal functor, then by the arguments (in left-to-right order). Recall that lists are equivalent to compound terms with principal functor @code{./2}. @refill @end itemize For example, here is a list of terms in the standard order: @example [ X, -9, 1, -1.0, fie, foe, X = Y, foe(0,2), fie(1,1,1) ] @end example These are the basic predicates for comparison of arbitrary terms: @table @code @item @var{Term1} == @var{Term2} @findex == /2, equality of terms Tests if the terms currently instantiating @var{Term1} and @var{Term2} are literally identical (in particular, variables in equivalent positions in the two terms must be identical). For example, the query @refill @example | ?- X == Y. @end example @noindent fails (answers @samp{no}) because @var{X} and @var{Y} are distinct uninstantiated variables. However, the query @refill @example | ?- X = Y, X == Y. @end example @noindent succeeds because the first goal unifies the two variables (@pxref{Misc Pred}). @refill @item @var{Term1} \== @var{Term2} @findex \== /2, inequality of terms Tests if the terms currently instantiating @var{Term1} and @var{Term2} are not literally identical. @refill @item @var{Term1} @@< @var{Term2} @findex @@< /2, term less than Term @var{Term1} is before term @var{Term2} in the standard order. @item @var{Term1} @@> @var{Term2} @findex @@> /2, term greater than Term @var{Term1} is after term @var{Term2} in the standard order. @item @var{Term1} @@=< @var{Term2} @findex @@=< /2, term less or equal Term @var{Term1} is not after term @var{Term2} in the standard order. @item @var{Term1} @@>= @var{Term2} @findex @@>= /2, term greater or equal Term @var{Term1} is not before term @var{Term2} in the standard order. @end table Some further predicates involving comparison of terms are: @table @code @item compare(@var{?Op},@var{?Term1},@var{?Term2}) @findex compare/3 The result of comparing terms @var{Term1} and @var{Term2} is @var{Op}, where the possible values for @var{Op} are: @refill @table @code @item = if @var{Term1} is identical to @var{Term2}, @item < if @var{Term1} is before @var{Term2} in the standard order, @item > if @var{Term1} is after @var{Term2} in the standard order. @end table Thus @code{compare(=,Term1,Term2)} is equivalent to @code{Term1 == Term2}. @refill @item sort(@var{+List1},@var{?List2}) @findex sort/2 The elements of the list @var{List1} are sorted into the standard order (@pxref{Term Compare}) and any identical elements are merged, yielding the list @var{List2}. (The time and space complexity of this operation is at worst @var{O(N lg N)} where @var{N} is the length of @var{List1}.) @refill @item keysort(@var{+List1},@var{?List2}) @findex keysort/2 The list @var{List1} must consist of items of the form @var{Key-Value}. These items are sorted into order according to the value of @var{Key}, yielding the list @var{List2}. No merging takes place. This predicate is @emph{stable}, i.e. if @code{K-A} occurs before @code{K-B} in the input, then @code{K-A} will occur before @code{K-B} in the output. (The time and space complexity of this operation is at worst @var{O(N lg N)} where @var{N} is the length of @var{List1}.) @refill @end table @node Control, State Info, Term Compare, Top @comment node-name, next, previous, up @section Control @table @code @item @var{P} , @var{Q} @findex ,/2, conjunction @var{P} and @var{Q}. @item @var{P} ; @var{Q} @findex ;/2, disjunction @var{P} or @var{Q}. @item ! @findex !/0, cut @xref{Cut}. @item \+ @var{P} @findex \+ /1, not provable If the goal @var{P} has a solution, fail, otherwise succeed. This is not real negation (``@var{P} is false''), but a kind of pseudo-negation meaning ``@var{P} is not provable''. It is defined as if by @refill @example \+(@var{P}) :- @var{P}, !, fail. \+(_). @end example @strong{No cuts are allowed in @var{P}.} Remember that with prefix operators such as this one it is necessary to be careful about spaces if the argument starts with a @kbd{(}. For example: @refill @example | ?- \+ (@var{P},@var{Q}). @end example @noindent is this operator applied to the conjunction of @var{P} and @var{Q}, but @refill @example | ?- \+(@var{P},@var{Q}). @end example @noindent would require a predicate @code{\+ /2} for its solution. The prefix operator can however be written as a functor of one argument; thus @refill @example | ?- \+((@var{P},@var{Q})). @end example @noindent is also correct. @item @var{P} -> @var{Q} ; @var{R} @findex -> /2 ;/2, if then else Analogous to @display if @var{P} then @var{Q} else @var{R} @end display @noindent i.e. defined as if by @example (@var{P} -> @var{Q}; @var{R}) :- @var{P}, !, @var{Q}. (@var{P} -> @var{Q}; @var{R}) :- @var{R}. @end example @strong{No cuts are allowed in @var{P}.} Note that this form of if-then-else only explores @emph{the first} solution to the goal @var{P}. Note also that the @kbd{;} is not read as a disjunction operator in this case; instead, it is part of the if-then-else construction. The precedence of @kbd{->} is less than that of @kbd{;} (@pxref{Operators}), so the expression is read as @example ;(->(@var{P},@var{Q}),@var{R}) @end example @item @var{P} -> @var{Q} @findex -> /2, if then When occurring as a goal, this construction is read as equivalent to @example (@var{P} -> @var{Q}; fail) @end example @item if(@var{P},@var{Q},@var{R}) @findex if/3 Analogous to @display if @var{P} then @var{Q} else @var{R} @end display @noindent but differs from @code{P -> Q ; R} in that @code{if(P, Q, R)} explores @emph{all} solutions to the goal @var{P}. There is a small time penalty for this---if @var{P} is known to have only one solution of interest, the form @code{P -> Q ; R} should be preferred. @strong{No cuts are allowed in @var{P}.} @item otherwise @itemx true @findex otherwise/0 @findex true/0 These always succeed. Use of @code{otherwise/0} is discouraged, because it is not as portable as @code{true/0}, and because the former may suggest a completely different semantics than the latter. @refill @item false @itemx fail @findex false/0 @findex fail/0 These always fail. Use of @code{false/0} is discouraged, because it is not as portable as @code{fail/0}, and because the latter has a more procedural flavour to it. @refill @item repeat @findex repeat/0 Generates an infinite sequence of backtracking choices. In sensible code, @code{repeat/0} is hardly ever used except in @emph{repeat loops}. A repeat loop has the structure @refill @example @var{Head} :- ... @var{save}(OldState), repeat, @var{generate}(Datum), @var{action}(Datum), @var{test}(Datum), !, @var{restore}(OldState), ... @end example The purpose is to repeatedly perform some @var{action} on elements which are somehow @var{generate}d, e.g. by reading them from a stream, until some @var{test} becomes true. Usually, @var{generate}, @var{action}, and @var{test} are all determinate. Repeat loops cannot contribute to the logic of the program. They are only meaningful if the @var{action} involves side-effects. @refill The only reason for using repeat loops instead of a more natural tail-recursive formulation is efficiency: when the @var{test} fails back, the Prolog engine immediately reclaims any working storage consumed since the call to @code{repeat/0}. @refill @item freeze(@var{+Goal}) @findex freeze/1 The @var{Goal} is blocked until it is ground. This can be used e.g. for defining a sound form of negation by: @refill @example not(Goal) :- freeze((\+ Goal)). @end example @strong{@code{not/1} is not a built-in predicate.} @item freeze(@var{?X},@var{+Goal}) @findex freeze/2 Block @var{Goal} until @code{nonvar(@var{X})} (@pxref{Meta Logic}) holds. This is defined as if by: @example :- wait freeze/2. freeze(_, Goal) :- Goal. @end example @item frozen(@var{-Var},@var{?Goal}) @findex frozen/2 If some goal is blocked on the variable @var{Var}, then that goal is unified with @var{Goal}. Otherwise, @var{Goal} is unified with the atom @code{true}. @refill @item call(@var{+Term}) @itemx incore(@var{+Term}) @itemx @var{+Term} @findex call/1 @findex incore/1 If @var{Term} is instantiated to a term which would be acceptable as the body of a clause, then the goal @code{call(@var{Term})} is executed exactly as if that term appeared textually in its place, except that any cut (@code{!}) occurring in @var{Term} only cuts alternatives in the execution of @var{Term}. Use of @code{incore/1} is not recommended. @refill If @var{Term} is not instantiated as described above, an error message is printed and the call fails. @refill @item call_residue(@var{+Goal},@var{?Vars}) @findex call_residue/2 The @var{Goal} is executed as if by @code{call/1}. If after the execution there are still some subgoals of @var{Goal} that are blocked on some variables, then @var{Vars} is unified with the list of such variables. Otherwise, @var{Vars} is unified with the empty list @code{[]}. @refill @end table @node State Info, Meta Logic, Control, Top @comment node-name, next, previous, up @section Information about the State of the Program @cindex program state @table @code @item listing @findex listing/0 Lists onto the current output stream all the clauses in the current interpreted program. Clauses listed onto a file can be consulted back. @refill @item listing(@var{+A}) @findex listing/1 If @var{A} is just an atom, then the interpreted predicates for all predicates of that name are listed as for @code{listing/0}. The argument @var{A} may also be a predicate spec in which case only the clauses for the specified predicate are listed. Finally, it is possible for @var{A} to be a list of specifications of either type, e.g. @refill @example | ?- listing([concatenate/3, reverse, go/0]). @end example @item ancestors(@var{?Goals}) @findex ancestors/1 Unifies @var{Goals} with a list of ancestor goals for the current clause. The list starts with the parent goal and ends with the most recent ancestor coming from a call in a compiled clause. @refill Only available when the debugger is switched on. @item subgoal_of(@var{?S}) @findex subgoal_of/1 Equivalent to the sequence of goals: @example | ?- ancestors(@var{Goals}), member(@var{S}, @var{Goals}). @end example @noindent where the predicate @code{member/2} (not a built-in predicate) successively matches its first argument with each of the elements of its second argument. @xref{Directives}. @refill Only available when the debugger is switched on. @item current_atom(@var{?Atom}) @findex current_atom/1 If @var{Atom} is instantiated then test if @var{Atom} is an Atom. @refill If @var{Atom} is unbound then generate (through backtracking) all currently known atoms, and return each one as @var{Atom}. @refill @item current_predicate(@var{?Name},@var{?Head}) @findex current_predicate/2 @var{Name} is the name of a user defined predicate, and @var{Head} is the most general goal for that predicate. This predicate can be used to enumerate all user defined predicates through backtracking. @refill @item predicate_property(@var{?Head},@var{?Property}) @findex predicate_property/2 @var{Head} is the most general goal for an existing predicate, and @var{Property} is a property of that predicate, where the possible properties are @refill @itemize @bullet @item one of the atoms @code{built_in} (for built-in predicates) or @code{compiled} or @code{interpreted} (for user defined predicates). @item zero or more of the atoms @code{dynamic}, @code{multifile}, and @code{wait}, for predicates that have been declared to have these properties (@pxref{Declarations}). N.B. Since these atoms are all prefix operators with precedence greater than 1000 (@pxref{Operators}), they have to be written inside parentheses when they occur as arguments of a compound term, e.g.: @example | ?- predicate_property(Head, (dynamic)). @end example @end itemize This predicate can be used to enumerate all existing predicates and their properties through backtracking. @refill @refill @end table @node Meta Logic, Modify Prog, State Info, Top @comment node-name, next, previous, up @section Meta-Logical @cindex meta-logical @table @code @item var(@var{?X}) @findex var/1 Tests whether @var{X} is currently uninstantiated (@code{var} is short for variable). An uninstantiated variable is one which has not been bound to anything, except possibly another uninstantiated variable. Note that a structure with some components which are uninstantiated is not itself considered to be uninstantiated. Thus the directive @refill @example | ?- var(foo(@var{X}, @var{Y})). @end example @noindent always fails, despite the fact that @var{X} and @var{Y} are uninstantiated. @refill @item nonvar(@var{?X}) @findex nonvar/1 Tests whether @var{X} is currently instantiated. This is the opposite of @code{var/1}. @refill @item atom(@var{?X}) @findex atom/1 Checks that @var{X} is currently instantiated to an atom (i.e. a non-variable term of arity 0, other than a number). @refill @item float(@var{?X}) @findex float/1 Checks that @var{X} is currently instantiated to a float. @refill @item integer(@var{?X}) @findex integer/1 Checks that @var{X} is currently instantiated to an integer. @refill @item number(@var{?X}) @findex number/1 Checks that @var{X} is currently instantiated to a number. @refill @item atomic(@var{?X}) @findex atomic/1 Checks that @var{X} is currently instantiated to an atom or number. @refill @item functor(@var{?Term},@var{?Name},@var{?Arity}) @findex functor/3 The principal functor of term @var{Term} has name @var{Name} and arity @var{Arity}, where @var{Name} is either an atom or, provided @var{Arity} is 0, an integer. Initially, either @var{Term} must be instantiated, or @var{Name} and @var{Arity} must be instantiated to, respectively, either an atom and an integer in [0..256) or an atomic term and 0. If these conditions are not satisfied, an error message is given. In the case where @var{Term} is initially uninstantiated, the result of the call is to instantiate @var{Term} to the most general term having the principal functor indicated. @refill @item arg(@var{+ArgNo},@var{+Term},@var{?Arg}) @findex arg/3 Initially, @var{ArgNo} must be instantiated to a positive integer and @var{Term} to a compound term. The result of the call is to unify @var{Arg} with the argument @var{ArgNo} of term @var{Term}. (The arguments are numbered from 1 upwards.) If the initial conditions are not satisfied or @var{ArgNo} is out of range, the call merely fails. @refill @item @var{?Term} =.@. @var{?List} @findex =.@. /2, univ @var{List} is a list whose head is the atom corresponding to the principal functor of @var{Term}, and whose tail is a list of the arguments of @var{Term}. E.g. @refill @example | ?- product(0, n, n-1) =.@. L. L = [product,0,n,n-1] | ?- n-1 =.@. L. L = [-,n,1] | ?- product =.@. L. L = [product] @end example If @var{Term} is uninstantiated, then @var{List} must be instantiated either to a list of determinate length whose head is an atom, or to a list of length 1 whose head is a number. Note that this predicate is not strictly necessary, since its functionality can be provided by @code{arg/3} and @code{functor/3}, and using the latter two is usually more efficient. @refill @item name(@var{?Const},@var{?CharList}) @findex name/2 If @var{Const} is an atom or number then @var{CharList} is a list of the ASCII codes of the characters comprising the name of @var{Const}. E.g. @refill @example | ?- name(product, L). L = [112,114,111,100,117,99,116] | ?- name(product, "product"). | ?- name(1976, L). L = [49,57,55,54] | ?- name('1976', L). L = [49,57,55,54] | ?- name((:-), L). L = [58,45] @end example If @var{Const} is uninstantiated, @var{CharList} must be instantiated to a list of ASCII character codes. If @var{CharList} can be interpreted as a number, @var{Const} is unified with that number, otherwise with the atom whose name is @var{CharList}. The length of @var{CharList} must be less than 512. E.g. @example | ?- name(X, [58,45]). X = :- | ?- name(X, ":-"). X = :- | ?- name(X, [49,50,51]). X = 123 @end example Note that there are atoms for which @code{name(@var{Const},@var{CharList})} is true, but which will not be constructed if @code{name/2} is called with @var{Const} uninstantiated. One such atom is the atom @code{'1976'}. It is recommended that new programs use @code{atom_chars/2} or @code{number_chars/2}, as these predicates do not have this inconsistency. @refill @item atom_chars(@var{?Const},@var{?CharList}) @findex atom_chars/2 The same as @code{name(@var{Const},@var{CharList})}, but @var{Const} is constrained to be an atom. @refill @item number_chars(@var{?Const},@var{?CharList}) @findex number_chars/2 The same as @code{name(@var{Const},@var{CharList})}, but @var{Const} is constrained to be a number. @refill @end table @node Modify Prog, Database, Meta Logic, Top @comment node-name, next, previous, up @section Modification of the Program The predicates defined in this section allow modification of the program as it is actually running. Clauses can be added to the program (@dfn{asserted}) or removed from the program (@dfn{retracted}). @refill For these predicates, the argument @var{Head} must be instantiated to an atom or a compound term. The argument @var{Clause} must be instantiated either to a term @code{@var{Head} :- @var{Body}} or, if the body part is empty, to @var{Head}. An empty body part is represented as @code{true}. @refill Note that a term @code{@var{Head} :- @var{Body}} must be enclosed in parentheses when it occurs as an argument of a compound term, as @samp{:-} is a standard infix operator with precedence greater than 1000 (@pxref{Operators}), e.g.: @refill @example | ?- assert((@var{Head} :- @var{Body})). @end example Like recorded terms, the clauses of dynamic predicates also have unique implementation-defined identifiers. Some of the predicates below have an additional argument which is this identifier. This identifier makes it possible to access clauses directly instead of requiring a normal database (hash-table) lookup. However it should be stressed that use of these predicates requires some extra care. @refill @table @code @item assert(@var{+Clause}) @itemx assert(@var{+Clause},@var{-Ref}) @findex assert/1 @findex assert/2 The current instance of @var{Clause} is interpreted as a clause and is added to the current interpreted program. The predicate concerned must be currently be dynamic or undefined and the position of the new clause within it is implementation-defined. @var{Ref} is a unique identifier of the asserted clause. Any uninstantiated variables in the @var{Clause} will be replaced by new private variables, along with copies of any subgoals blocked on these variables. @refill @item asserta(@var{+Clause}) @itemx asserta(@var{+Clause},@var{-Ref}) @findex asserta/1 @findex asserta/2 Like @code{assert/2}, except that the new clause becomes the @emph{first} clause for the predicate concerned. @refill @item assertz(@var{+Clause}) @itemx assertz(@var{+Clause},@var{-Ref}) @findex assertz/1 @findex assertz/2 Like @code{assert/2}, except that the new clause becomes the @emph{last} clause for the predicate concerned. @refill @item clause(@var{+Head},@var{?Body}) @itemx clause(@var{+Head},@var{?Body},@var{?Ref}) @itemx clause(@var{?Head},@var{?Body},@var{+Ref}) @findex clause/2 @findex clause/3 The clause @code{(@var{Head} :- @var{Body})} exists in the current interpreted program, and is uniquely identified by @var{Ref}. The predicate concerned must currently be dynamic. At the time of call, either @var{Ref} must be instantiated to a valid identifier, or @var{Head} must be instantiated to an atom or a compound term. Thus @code{clause/3} can have two different modes of use. @refill @item retract(@var{+Clause}) @findex retract/1 The first clause in the current interpreted program that matches @var{Clause} is erased. The predicate concerned must currently be dynamic. @code{retract/1} may be used in a non-determinate fashion, i.e. it will successively retract clauses matching the argument through backtracking. If reactivated by backtracking, invocations of the predicate whose clauses are being retracted will proceed unaffected by the retracts. This is also true for invocations of @code{clause} for the same predicate. The space occupied by a retracted clause will be recovered when instances of the clause are no longer in use. @refill @item retractall(@var{+Head}) @findex retractall/1 Erase all clauses whose head matches @var{Head}, where @var{Head} must be instantiated to an atom or a compound term. The predicate concerned must currently be dynamic. The predicate definition is retained. @refill @item abolish(@var{+Spec}) @itemx abolish(@var{+Name},@var{+Arity}) @findex abolish/1 @findex abolish/2 Erase all clauses of the predicate specified by the predicate spec @var{Spec} or @code{@var{Name}/@var{Arity}}. @var{Spec} may also be a list of predicate specs. The predicate definition and all associated information such as spy-points is also erased. The predicates concerned must all be user defined. @refill @end table @node Database, All Solutions, Modify Prog, Top @comment node-name, next, previous, up @section Internal Database @cindex database The predicates described in this section were introduced in early implementations of Prolog to provide efficient means of performing operations on large quantities of data. The introduction of indexed dynamic predicates have rendered these predicates obsolete, and the sole purpose of providing them is to support existing code. There is no reason whatsoever to use them in new code. These predicates store arbitrary terms in the database without interfering with the clauses which make up the program. The terms which are stored in this way can subsequently be retrieved via the key on which they were stored. Many terms may be stored on the same key, and they can be individually accessed by pattern matching. Alternatively, access can be achieved via a special identifier which uniquely identifies each recorded term and which is returned when the term is stored. @table @code @item recorded(@var{?Key},@var{?Term},@var{?Ref}) @findex recorded/3 The internal database is searched for terms recorded under the key @var{Key}. These terms are successively unified with @var{Term} in the order they occur in the database. At the same time, @var{Ref} is unified with the implementation-defined identifier uniquely identifying the recorded item. If the key is instantiated to a compound term, only its principal functor is significant. If the key is uninstantiated, all terms in the database are successively unified with @var{Term} in the order they occur. @refill @item recorda(@var{+Key},@var{?Term},@var{-Ref}) @findex recorda/3 The term @var{Term} is recorded in the internal database as the first item for the key @var{Key}, where @var{Ref} is its implementation-defined identifier. The key must be given, and only its principal functor is significant. Any uninstantiated variables in the @var{Term} will be replaced by new private variables, along with copies of any subgoals blocked on these variables. @refill @item recordz(@var{+Key},@var{?Term},@var{-Ref}) @findex recordz/3 Like @code{recorda/3}, except that the new term becomes the @emph{last} item for the key @var{Key}. @refill @item erase(@var{+Ref}) @findex erase/1 The recorded item (or dynamic clause (@pxref{Database})) whose implementation-defined identifier is @var{Ref} is effectively erased from the internal database or interpreted program. @refill @item instance(@var{+Ref},@var{?Term}) @findex instance/2 A (most general) instance of the recorded term or clause whose implementation-defined identifier is @var{Ref} is unified with @var{Term}. @var{Ref} must be instantiated to a legal identifier. @refill @item current_key(@var{?KeyName},@var{?KeyTerm}) @findex current_key/2 @var{KeyTerm} is the most general form of the key for a currently recorded term, and @var{KeyName} is the name of that key. This predicate can be used to enumerate in undefined order all keys for currently recorded terms through backtracking. @refill @end table @node All Solutions, Foreign, Database, Top @comment node-name, next, previous, up @section All Solutions @cindex all solutions @cindex solutions, all When there are many solutions to a problem, and when all those solutions are required to be collected together, this can be achieved by repeatedly backtracking and gradually building up a list of the solutions. The following built-in predicates are provided to automate this process. @table @code @item setof(@var{?Template},@var{+Goal},@var{?Set}) @findex setof/3 Read this as ``@var{Set} is the set of all instances of @var{Template} such that @var{Goal} is satisfied, where that set is non-empty''. The term @var{Goal} specifies a goal or goals as in @code{call(@var{Goal})} (@pxref{Control}). @var{Set} is a set of terms represented as a list of those terms, without duplicates, in the standard order for terms (@pxref{Term Compare}). If there are no instances of @var{Template} such that @var{Goal} is satisfied then the predicate fails. @refill The variables appearing in the term @var{Template} should not appear anywhere else in the clause except within the term @var{Goal}. Obviously, the set to be enumerated should be finite, and should be enumerable by Prolog in finite time. It is possible for the provable instances to contain variables, but in this case the list @var{Set} will only provide an imperfect representation of what is in reality an infinite set. @refill If there are uninstantiated variables in @var{Goal} which do not also appear in @var{Template}, then a call to this built-in predicate may backtrack, generating alternative values for @var{Set} corresponding to different instantiations of the free variables of @var{Goal}. (It is to cater for such usage that the set @var{Set} is constrained to be non-empty.) Two instantiations are different iff no renaming of variables can make them literally identical. For example, given the clauses: @refill @example likes(bill, cider). likes(dick, beer). likes(harry, beer). likes(jan, cider). likes(tom, beer). likes(tom, cider). @end example @noindent the query @example | ?- setof(X, likes(X,Y), S). @end example @noindent might produce two alternative solutions via backtracking: @example Y = beer, S = [dick, harry, tom] Y = cider, S = [bill, jan, tom] @end example The query: @example | ?- setof((Y,S), setof(X, likes(X,Y), S), SS). @end example @noindent would then produce: @example SS = [ (beer,[dick,harry,tom]), (cider,[bill,jan,tom]) ] @end example Variables occurring in @var{Goal} will not be treated as free if they are explicitly bound within @var{Goal} by an existential quantifier. An existential quantification is written: @refill @example @var{Y}^@var{Q} @end example @noindent meaning ``there exists a @var{Y} such that @var{Q} is true'', where @var{Y} is some Prolog variable. @refill For example: @example | ?- setof(X, Y^(likes(X,Y)), S). @end example @noindent would produce the single result: @example S = [bill, dick, harry, jan, tom] @end example @noindent in contrast to the earlier example. @item bagof(@var{?Template},@var{+Goal},@var{?Bag}) @findex bagof/3 This is exactly the same as @code{setof/3} except that the list (or alternative lists) returned will not be ordered, and may contain duplicates. The effect of this relaxation is to save a call to @code{sort/2}, which is invoked by @code{setof/3} to return an ordered list. @refill @item @var{X}^@var{P} @findex ^/2, existential quantifier The interpreter recognises this as meaning ``there exists an @var{X} such that @var{P} is true'', and treats it as equivalent to @code{@var{P}} (@pxref{Control}). The use of this explicit existential quantifier outside the @code{setof/3} and @code{bagof/3} constructs is superfluous and discouraged. @refill @item findall(@var{?Template},@var{+Goal},@var{?Bag}) @findex findall/3 @var{Bag} is a list of instances of @var{Template} in all proofs of @var{Goal} found by Prolog. The order of the list corresponds to the order in which the proofs are found. The list may be empty and all variables are taken as being existentially quantified. This means that each invocation of @code{findall/3} succeeds @emph{exactly once}, and that no variables in @var{Goal} get bound. Avoiding the management of universally quantified variables can save considerable time and space. @refill @end table @node Foreign, Debug Pred, All Solutions, Top @comment node-name, next, previous, up @section Interface to Foreign Language Functions @cindex foreign Functions written in the C language (or any other language that uses the same calling conventions) may be called from Prolog. Foreign language modules may be linked in as needed. However: once a module has been linked in to the Prolog load image it is not possible to unlink the module. The foreign language function interface is due to Quintus Prolog. @table @code @item foreign_file(@var{+ObjectFile},@var{+Functions}) @findex foreign_file/2 @emph{A user defined predicate.} Specifies that a set of C language functions, to be called from Prolog, are to be found in @var{ObjectFile}. @var{Functions} is a list of functions exported by @var{ObjectFile}. Only functions that are to be called from Prolog should be listed. For example @refill @example foreign_file('terminal.o', [scroll,pos_cursor,ask]). @end example @noindent specifies that functions @code{scroll()}, @code{pos_cursor()} and @code{ask()} are to be found in object file @file{terminal.o}. @refill @item foreign(@var{+CFunctionName}, @var{+Predicate}) @itemx foreign(@var{+CFunctionName}, @var{+Language}, @var{+Predicate}) @findex foreign/2 @findex foreign/3 @emph{User defined predicates.} They specify the Prolog interface to a C function. @var{Language} is at present constrained to the atom @code{c}. @var{CFunctionName} is the name of a C function. @var{Predicate} specifies the name of the Prolog predicate that will be used to call @var{CFunction()}. @var{Predicate} also specifies how the predicate arguments are to be translated into the corresponding C arguments. @refill @example foreign(pos_cursor, c, move_cursor(+integer, +integer)). @end example The above example says that the C function @code{pos_cursor()} has two integer value arguments and that we will use the predicate @code{move_cursor/2} to call this function. A goal @code{move_cursor(5, 23)} would translate into the C call @code{pos_cursor(5,23);}. @refill @item load_foreign_files(@var{+ObjectFiles},@var{+Libraries}) @findex load_foreign_files/2 Load (link) @var{ObjectFiles} into the Prolog load image. @var{ObjectFiles} is a list of C object files. @var{Libraries} is a list of libraries, the C library @code{'-lc'} will always be used and need not be specified. Example: @refill @example | ?- load_foreign_files(['terminal.o'], []). @end example @end table The third argument of the predicate @code{foreign/3} specifies how to translate between Prolog arguments and C arguments. @table @code @item Prolog: +integer @item C: long The argument should be instantiated to an integer or a float. The call will otherwise fail. @refill @item Prolog: +float @item C: double The argument should be instantiated to an integer or a float. The call will otherwise fail. @refill @item Prolog: +atom @item C: unsigned long The argument should be instantiated to an atom. The call will otherwise fail. Each atom in SICStus is associated with a unique integer. This integer is passed as an unsigned long to the C function. Note that the mapping between atoms and integers depends on the execution history. @refill @item Prolog: +string @item C: char * The argument should be instantiated to an atom. The call will otherwise fail. The C function will be passed the address of a text string containing the printed representation of the atom. The C function should @emph{not} overwrite the string. @refill @item Prolog: +string(@var{N}) @item C: char * The argument should be instantiated to an atom. The call will otherwise fail. The printable representation of the string will be copied into a newly allocated buffer. The string will be truncated if it is longer than @var{N} characters. The string will be blank padded on the right if it is shorter than @var{N} characters. The C function will be passed the address of the buffer. The C function may overwrite the buffer. @refill @item Prolog: +address @item C: char * The argument should be instantiated to an integer; the call will otherwise fail. The argument should be either 0 or a pointer @var{P} previously passed from C to Prolog. The value passed will be @code{NULL} or @var{P}, respectively, type converted to @w{@code{(char *)}}. @refill @item Prolog: +address(@var{TypeName}) @item C: @var{TypeName} * The argument should be instantiated to an integer. The call will otherwise fail. The argument should be either 0 or a pointer @var{P} previously passed from C to Prolog. The value passed will be @code{NULL} or @var{P}, respectively, type converted to @w{@code{(@var{TypeName} *)}}. @refill @item Prolog: -integer @item C: long * The C function is passed a reference to an uninitialised @code{long}. The value returned will be converted to a Prolog integer. The Prolog integer will be unified with the Prolog argument. @refill @item Prolog: -float @item C: double * The C function is passed a reference to an uninitialised @code{double}. The value returned will be converted to a Prolog float. The Prolog float will be unified with the Prolog argument. @refill @item Prolog: -atom @item C: unsigned long * The C function is passed a reference to an uninitialised @code{long}. The value returned should have been obtained earlier from a @code{+atom} type argument. Prolog will attempt to associate an atom with the returned value. The atom will be unified with the Prolog argument. @refill @item Prolog: -string @item C: char ** The C function is passed the address of an uninitialised @code{char *}. The returned string will be converted to a Prolog atom. The atom will be unified with the Prolog argument. C may reuse or destroy the string buffer during later calls. @refill @item Prolog: -string(@var{N}) @item C: char * The C function is passed a reference to a character buffer large enough to store an @var{N} character string. The returned string will be stripped of trailing blanks and converted to a Prolog atom. The atom will be unified with the Prolog argument. @refill @item Prolog: -address @item C: char ** The C function is passed the address of an uninitialised @code{char *}. The returned value, which must be @code{NULL} or a value created by @code{malloc()}, will be converted to a Prolog integer and unified with the Prolog argument. @refill @item Prolog: -address(@var{TypeName}) @item C: @var{TypeName} ** The C function is passed the address of an uninitialised @code{@var{TypeName} *}. The returned value, which must be @code{NULL} or a value created by @code{malloc()}, will be converted to a Prolog integer and unified with the Prolog argument. @refill @item Prolog: [-integer] @item C: long @var{F}() The C function should return a @code{long}. The value returned will be converted to a Prolog integer. The Prolog integer will be unified with the Prolog argument. @refill @item Prolog: [-float] @item C: double @var{F}() The C function should return a @code{double}. The value returned will be converted to a Prolog float. The Prolog float will be unified with the Prolog argument. @refill @item Prolog: [-atom] @item C: unsigned long @var{F}() The C function should return an @code{unsigned long}. The value returned should have been obtained earlier from a @code{+atom} type argument. Prolog will attempt to associate an atom with the returned value. The atom will be unified with the Prolog argument. @refill @item Prolog: [-string] @item C: char *@var{F}() The C function should return a @code{char *}. The returned string will be converted to a Prolog atom. The atom will be unified with the Prolog argument. C may reuse or destroy the string buffer during later calls. @refill @item Prolog: [-string(@var{N})] @item C: char *@var{F}() The C function should return a @code{char *}. The first @var{N} characters of the string will be copied and the copied string will be stripped of trailing blanks. The stripped string will be converted to a Prolog atom. The atom will be unified with the Prolog argument. C may reuse or destroy the string buffer during later calls. @refill @item Prolog: [-address] @item C: char *@var{F}() The C function should return a @code{char *}. The returned value, which must be @code{NULL} or a value created by @code{malloc()}, will be converted to a Prolog integer and unified with the Prolog argument. @refill @item Prolog: [-address(@var{TypeName})] @item C: @var{TypeName} *@var{F}() The C function should return a @code{@var{TypeName} *}. The returned value, which must be @code{NULL} or a value created by @code{malloc()}, will be converted to a Prolog integer and unified with the Prolog argument. @refill @end table Consider, for example, a function which returns the square root of its argument after checking that the argument is valid, defined in the file @file{math.c}: @example #include <math.h> #include <stdio.h> double sqrt_check(d) double d; @{ if (d < 0.0) d = 0.0, fprintf(stderr, "can't take square root of a negative number\n"); return sqrt(d); @} @end example The Prolog interface to this function is defined in a file @file{math.pl}. The function uses the @code{sqrt()} library function, and so the math library @samp{-lm} has to be included: @example foreign_file('math.o', [sqrt_check]). foreign(sqrt_check, c, sqrt(+float, [-float])). :- load_foreign_files(['math.o'], ['-lm']). @end example A simple session using this function could be: @example | ?- [math]. @{consulting /home/sics/al/math.pl...@} @{math consulted, 160 msec 597 bytes@} yes | ?- sqrt(5.0, X). X = 2.23606797749979 ? yes | ?- sqrt(-5.0, X). can't take square root of a negative number X = 0.0 ? yes @end example Unfortunately, the foreign function interface is the least portable part of SICStus Prolog. Therefore, we provide an alternative to the mechanism described above. Using the alternative mechanism, the foreign code is statically linked with the emulator code and with @dfn{interface code}. This interface code is created by first loading into SICStus Prolog @emph{all} @code{foreign_file/2} and @code{foreign/2-3} declarations that are going to be used by @code{load_foreign_files/2}, and then calling the predicate: @table @code @item prepare_foreign_files(@var{+ObjectFiles}) @findex prepare_foreign_files/2 where @var{ObjectFiles} is a list of @emph{all} the object files that are going to be used by @code{load_foreign_files/2}, generates the relevant interface code in @file{flinkage.c} in the current working directory. @end table Once the interface code has been generated, the foreign code can be statically linked with the emulator. The whole procedure is best illustrated by an example. We first exctract the declarations into a file @file{math2.pl}: @example foreign_file('math.o', [sqrt_check]). foreign(sqrt_check, c, sqrt(+float, [-float])). @end example @noindent and use them as follows: @example % prolog SICStus 0.7 #0: Thu Jun 7 10:40:30 MET DST 1990 | ?- [math2], prepare_foreign_files(['math.o']). @{consulting /home/sics/al/math2.pl...@} @{math consulted, 20 msec 510 bytes@} @{flinkage.c generated, 20 msec@} yes | ?- ^D @{ End of SICStus execution, user time 0.100 @} % cc -c flinkage.c % setenv SP_PATH /usr/local/lib/sicstus0.7 % cc $SP_PATH/Emulator/sp.o flinkage.o math.o -lm -o sp % ./sp -f -b $SP_PATH/Library/boot.ql booting SICStus...please wait SICStus 0.7 #0: Thu Jun 7 10:40:30 MET DST 1990 | ?- [math]. @{consulting /home/sics/al/math.pl...@} @{math consulted, 20 msec 597 bytes@} yes | ?- sqrt(5.0, X). X = 2.23606797749979 ? yes @end example At this time, @code{save_program/1} can be called to create an executable saved state for quick start-up. @xref{Installation Intro}. Notice that the semantics of @code{load_foreign_files/2} is somewhat different if user code is statically linked with the emulator: no dynamic linking of object files takes place; instead, the relevant predicates and functions are connected by searching the emulator's internal symbol tables, and the second argument is simply ignored. In general, to statically link the user code with the emulator, create the interface code (@file{flinkage.o}) and issue a Shell command @example % cc $SP_PATH/Emulator/sp.o flinkage.o OBJECTFILES LIBRARIES -o sp @end example @noindent where the environment variable @code{SP_PATH} should be defined as the name of the SICStus source code directory (@file{/usr/local/lib/sicstus0.7} in the example). @node Debug Pred, Profiling, Foreign, Top @comment node-name, next, previous, up @section Debugging @table @code @item unknown(@var{?OldState},@var{?NewState}) @findex unknown/2 Unifies @var{OldState} with the current state of the ``Action on unknown predicates'' flag, and sets the flag to @var{NewState}. This flag determines whether or not the system is to catch calls to undefined predicates (@pxref{Undefined Predicates}). The possible states of the flag are: @refill @table @code @item trace Causes calls to undefined predicates to be reported and the debugging system to be entered at the earliest opportunity (the default state). @refill @item fail Causes calls to such predicates to fail. @refill @end table @item debug @findex debug/0 The debugger is switched on with tracing disabled. @xref{Basic}. @refill @item nodebug @itemx notrace @findex nodebug/0 @findex notrace/0 The debugger is switched off. @xref{Basic}. @refill debugging. @refill @item trace @findex trace/0 The debugger is switched on with tracing enabled. @xref{Trace}. @refill @item leash(@var{+Mode}) @findex leash/1 Leashing Mode is set to @var{Mode}. @xref{Trace}. @refill @item spy @var{+Spec} @findex spy/1 Spy-points are placed on all the predicates given by @var{Spec}. @xref{Spy-Point}. @refill @item nospy @var{+Spec} @findex nospy/1 Spy-points are removed from all the predicates given by @var{Spec}. @xref{Spy-Point}. @refill @item nospyall @findex nospyall/0 This removes all the spy-points that have been set. @refill @item debugging @findex debugging/0 Displays information about the debugger. @xref{Basic}. @refill @end table @node Profiling, Definite, Debug Pred, Top @comment node-name, next, previous, up @section Execution Profiling @cindex execution profiling @cindex profiling, execution @cindex counter Execution profiling is a common aid for improving software performance. The SICStus Prolog compiler has the capability of instrumenting compiled code with @dfn{counters} which are initially zero and incremented whenever the flow of control passes a given point in the compiled code. This way the number of calls, backtracks, choicepoints created, etc., can be counted for the instrumented predicates, and an estimate of the time spent in individual clauses and disjuncts can be calculated. The profiling package was written by M.M. Gorlick and C.F. Kesselman at the Aerospace Corporation (@cite{Timing Prolog Programs Without Clocks}, Proc. Symposium on Logic Programming, pp. 426--432, IEEE Computer Society, 1987). Only compiled code can be instrumented. To get an execution profile of a program, the compiler must first be told to produce instrumented code. This is done by issuing the directive: @example | ?- prolog_flag(compiling,_,profiledcode). @end example @noindent after which the program to be analyzed can be compiled as usual. Any new compiled code will be instrumented while the compilation mode flag has the value @code{profiledcode}. The profiling data is generated by simply running the program. The predicate @code{profile_data/4} (see below) makes available a selection of the data as a Prolog term. The predicate @code{profile_reset/1} zeroes the profiling counters for a selection of the currently instrumented predicates. @refill @table @code @item profile_data(@var{+Files},@var{?Selection},@var{?Resolution},@var{-Data}) @findex profile_data/4 This unifies @var{Data} with profiling data collected from the predicates defined in @var{Files}, which should be either a single filename or a list of filenames, similar to the argument accepted by e.g. @code{compile/1}. @refill The @var{Selection} argument determines the kind of profiling data to be collected. If uninstantiated, the predicate will backtrack over its possible values, which are: @refill @table @code @item calls All instances of entering a clause by a procedure call are counted. This is equivalent to counting all procedure calls @emph{that have not been determined to fail by indexing on the first argument}. @refill @item backtracks All instances of entering a clause by backtracking are counted. @item choice_points All instances of creating a choicepoint are counted. This occurs, roughly, when the implementation determines that there are more than one possibly matching clauses for a procedure call, and when a disjunction is entered. @item shallow_fails All instances of backtracking ``early'' in a clause or disjunct when there are outstanding alternatives for the current procedure call are counted. @item deep_fails All instances of backtracking ``late'' in a clause or disjunct, or when there are no outstanding alternatives for the current procedure call, are counted. The reason for distinguishing shallow and deep failures is that the former are considerably cheaper to execute than the latter. @item execution_time The execution time for the selected predicates, clauses, or disjuncts is estimated in artificial units. @end table The @var{Resolution} argument determines the level of resolution of the profiling data to be collected. If uninstantiated, the predicate will backtrack over its possible values, which are: @refill @table @code @item predicate @var{Data} is a list of @code{@var{PredName}-@var{Count}}, where @var{Count} is a sum of the corresponding counts per clause. @item clause @var{Data} is a list of @code{@var{ClauseName}-@var{Count}}, where @var{Count} includes counts for any disjunctions occurring inside that clause. Note, however, that the selections @code{calls} and @code{backtracks} do @emph{not} include counts for disjunctions. @item all @var{Data} is a list of @code{@var{InternalName}-@var{Count}}. This is the finest resolution level, counting individual clauses and disjuncts. @end table @noindent Above, @var{PredName} is a predicate spec, @var{ClauseName} is a compound term @code{@var{PredName}/@var{ClauseNumber}}, and @var{InternalName} is either@* @var{ClauseName}---corresponding to a clause, or@* @code{(@var{ClauseName}-@var{DisjNo})/@var{Arity}/@var{AltNo}}---corresponding to a disjunct. @item profile_reset(@var{+Files}) @findex profile_reset/1 Zeroes all counters for predicates defined in @var{Files}, which should be either a single filename or a list of filenames, similar to the argument accepted by @code{profile_data/4}. @refill @end table @node Definite, Misc Pred, Profiling, Top @comment node-name, next, previous, up @section Definite Clause Grammars @cindex grammars Prolog's grammar rules provide a convenient notation for expressing definite clause grammars, see @cite{Les Grammaires de Metamorphos} by A. Colmerauer, Technical Report, Groupe d'Intelligence Artificielle, Marseille-Luminy, November, 1975, and @cite{Definite clause grammars for language analysis---a survey of the formalism and a comparison with augmented transition networks} by F.C.N. Pereira and D.H.D. Warren, in @cite{Artificial Intelligence} 13:231-278, 1980. @refill Definite clause grammars are an extension of the well-known context-free grammars. A grammar rule in Prolog takes the general form @example @var{head} --> @var{body}. @end example @noindent meaning ``a possible form for @var{head} is @var{body}''. Both @var{body} and @var{head} are sequences of one or more items linked by the standard Prolog conjunction operator @samp{,}. @refill Definite clause grammars extend context-free grammars in the following ways: @enumerate @item A non-terminal symbol may be any Prolog term (other than a variable or number). @refill @item A terminal symbol may be any Prolog term. To distinguish terminals from non-terminals, a sequence of one or more terminal symbols is written within a grammar rule as a Prolog list. An empty sequence is written as the empty list @samp{[]}. If the terminal symbols are ASCII character codes, such lists can be written (as elsewhere) as strings. An empty sequence is written as the empty list, @samp{[]} or @samp{""}. @refill @item Extra conditions, in the form of Prolog procedure calls, may be included in the right-hand side of a grammar rule. Such procedure calls are written enclosed in @samp{@{@}} brackets. @refill @item The left-hand side of a grammar rule consists of a non-terminal, optionally followed by a sequence of terminals (again written as a Prolog list). @refill @item Alternatives may be stated explicitly in the right-hand side of a grammar rule, using the disjunction operator @samp{;} or @samp{|} as in Prolog. @refill @item The cut symbol may be included in the right-hand side of a grammar rule, as in a Prolog clause. The cut symbol does not need to be enclosed in @samp{@{@}} brackets. @refill @end enumerate As an example, here is a simple grammar which parses an arithmetic expression (made up of digits and operators) and computes its value. @example @group expr(Z) --> term(X), "+", expr(Y), @{Z is X + Y@}. expr(Z) --> term(X), "-", expr(Y), @{Z is X - Y@}. expr(X) --> term(X). term(Z) --> number(X), "*", term(Y), @{Z is X * Y@}. term(Z) --> number(X), "/", term(Y), @{Z is X / Y@}. term(Z) --> number(Z). number(C) --> "+", number(C). number(C) --> "-", number(X), @{C is -X@}. number(X) --> [C], @{"0"=<C, C=<"9", X is C - "0"@}. @end group @end example In the last rule, @var{C} is the ASCII code of some digit. The query @example | ?- expr(Z, "-2+3*5+1", []). @end example @noindent will compute @var{Z}=14. The two extra arguments are explained below. Now, in fact, grammar rules are merely a convenient ``syntactic sugar'' for ordinary Prolog clauses. Each grammar rule takes an input string, analyses some initial portion, and produces the remaining portion (possibly enlarged) as output for further analysis. The arguments required for the input and output strings are not written explicitly in a grammar rule, but the syntax implicitly defines them. We now show how to translate grammar rules into ordinary clauses by making explicit the extra arguments. A rule such as @example p(X) --> q(X). @end example @noindent translates into @example p(X, S0, S) :- q(X, S0, S). @end example If there is more than one non-terminal on the right-hand side, as in @example p(X, Y) --> q(X), r(X, Y), s(Y). @end example @noindent then corresponding input and output arguments are identified, as in @example p(X, Y, S0, S) :- q(X, S0, S1), r(X, Y, S1, S2), r(Y, S2, S). @end example Terminals are translated using the built-in predicate @code{'C'(@var{S1}, @var{X}, @var{S2})}, read as ``point @var{S1} is connected by terminal @var{X} to point @var{S2}'', and defined by the single clause @refill @example 'C'([X|S], X, S). @end example (This predicate is not normally useful in itself; it has been given the name upper-case @kbd{c} simply to avoid using up a more useful name.) Then, for instance @example p(X) --> [go,to], q(X), [stop]. @end example @noindent is translated by @example p(X, S0, S) :- 'C'(S0, go, S1), 'C'(S1, to, S2), q(X, S2, S3), 'C'(S3, stop, S). @end example Extra conditions expressed as explicit procedure calls naturally translate as themselves, e.g. @example p(X) --> [X], @{integer(X), X>0@}, q(X). @end example @noindent translates to @example p(X, S0, S) :- 'C'(S0, X, S1), integer(X), X>0, q(X, S1, S). @end example Similarly, a cut is translated literally. Terminals on the left-hand side of a rule translate into an explicit list in the output argument of the main non-terminal, e.g. @example is(N), [not] --> [aint]. @end example @noindent becomes @example is(N, S0, [not|S]) :- 'C'(S0, aint, S). @end example Disjunction has a fairly obvious translation, e.g. @example args(X, Y) --> ( dir(X), [to], indir(Y) ; indir(Y), dir(X) ). @end example @noindent translates to @example args(X, Y, S0, S) :- ( dir(X, S0, S1), 'C'(S1, to, S2), indir(Y, S2, S) ; indir(Y, S0, S1), dir(X, S1, S) ). @end example The built-in predicates which are concerned with grammars are as follows. @table @code @item expand_term(@var{+Term1},@var{?Term2}) @findex expand_term/2 When a program is read in, some of the terms read are transformed before being stored as clauses. If @var{Term1} is a term that can be transformed, @var{Term2} is the result. Otherwise @var{Term2} is just @var{Term1} unchanged. This transformation takes place automatically when grammar rules are read in, but sometimes it is useful to be able to perform it explicitly. Grammar rule expansion is not the only transformation available, the user may define clauses for the predicate @code{term_expansion/2} to perform other transformations. @code{term_expansion(@var{Term1},@var{Term2})} is called first, and only if it fails is the standard expansion used. @refill @item term_expansion(@var{+Term1},@var{?Term2}) @findex term_expansion/2 @emph{A user defined predicate}, which overrides the default grammar rule expansion of clauses to be consulted or compiled. @refill @item phrase(@var{+Phrase},@var{?List}) @itemx phrase(@var{+Phrase},@var{?List},@var{?Remainder}) @findex phrase/2 @findex phrase/3 The list @var{List} is a phrase of type @var{Phrase} (according to the current grammar rules), where @var{Phrase} is either a non-terminal or more generally a grammar rule body. @var{Remainder} is what remains of the list after a phrase has been found. If called with 2 arguments, the remainder has to be the empty list. @refill @item 'C'(@var{?S1},@var{?Terminal},@var{?S2}) @findex C/3 Not normally of direct use to the user, this built-in predicate is used in the expansion of grammar rules (see above). It is defined as if by the clause @code{'C'([X|S], X, S).} @refill @end table @node Misc Pred, Prolog Intro, Definite, Top @comment node-name, next, previous, up @section Miscellaneous @table @code @item @var{X} = @var{Y} @findex =/2, unification Defined as if by the clause @code{Z=Z.}; i.e. @var{X} and @var{Y} are unified. @refill @item dif(@var{X},@var{Y}) @findex dif/2 Constrains @var{X} and @var{Y} to represent different terms i.e. to be non unifiable. Calls to @code{dif/2} either succeed, fail, or are blocked depending on whether @var{X} and @var{Y} are sufficiently instantiated. This predicate is due to Prolog II (see @cite{Prolog II: Manuel de Reference et Modele Theorique}, by A. Colmerauer, Groupe Intelligence Artificielle, Universite Aix-Marseille II, 1982). @refill For example: @example @group | ?- dif(X,a). X = _74, dif(_74,a) ? yes | ?- dif(X,a), X=a. no | ?- dif([X|a],[b|Y]), X=a. X = a, Y = _154 ? yes @end group @end example @item length(@var{?List},@var{?Length}) @findex length/2 If @var{List} is instantiated to a list of determinate length, then @var{Length} will be unified with this length. @refill If @var{List} is of indeterminate length and @var{Length} is instantiated to an integer, then @var{List} will be unified with a list of length @var{Length}. The list elements are unique variables. @refill If @var{Length} is unbound then @var{Length} will be unified with all possible lengths of @var{List}. @refill @item prolog_flag(@var{+FlagName},@var{?OldValue},@var{?NewValue}) @findex prolog_flag/3 Unify @var{OldValue} with the value of the flag @var{FlagName}, then set the value of @var{FlagName} to @var{NewValue}. The possible flag names and values are: @refill @table @code @item character_escapes @code{on} or @code{off}. Enable or disable character escaping. Currently this has @emph{no effect} in SICStus Prolog. @refill @item compiling Governs the mode in which @code{compile/1} and @code{fcompile/1} operate (@pxref{Load Intro}). @table @code @item compactcode Compilation produces byte-coded abstract instructions (the default). @item fastcode Compilation produces native machine instructions. Only available for Sun-3 computers. @item profiledcode Compilation produces byte-coded abstract instructions instrumented to produce execution profiling data. @end table @item debugging Corresponds to the predicates @code{debug/0}, @code{nodebug/0}, @code{trace/0}, @code{notrace/0} (@pxref{Debug Pred}). @table @code @item trace Turn on trace mode. @item debug Turn on the debugger. @item off Turn off trace mode and the debugger (the default). @end table @item fileerrors @code{on} or @code{off}. Turn aborting on file errors on or off. Equivalent to @code{fileerrors/0} and @code{fileerrors/0}, respectively (@pxref{Stream Pred}). Initially @code{on}. @item gc @code{on} or @code{off}. Turn garbage collection on or off. Initially @code{on}. @item gc_margin @var{Margin}: Number of kilobytes. If less than @var{Margin} kilobytes are reclaimed in a garbage collection then the size of the garbage collected area should be increased. Also, no garbage collection is attempted unless the garbage collected area has at least @var{Margin} kilobytes. Initially 500. @refill @item gc_trace Governs garbage collection trace messages. @table @code @item verbose Turn on verbose tracing of garbage collection. @item terse Turn on terse tracing of garbage collection. @item off Turn off tracing of garbage collection (the default). @end table @item redefine_warnings @code{on} or @code{off}. Enable or disable warning messages when a predicate is being redefined from a different file than its previous definition. Initially @code{on}. @refill @item single_var_warnings @code{on} or @code{off}. Enable or disable warning messages when a clause containing non-anonymous variables occurring once only is compiled or consulted. Initially @code{on}. @refill @item unknown Corresponds to the predicate @code{unknown/2} (@pxref{Debug Pred}). @table @code @item trace Cause calls to undefined predicates to be reported and the debugging system to be entered at the earliest opportunity (the default). @item fail Cause calls to such predicates to fail. @end table @end table @item prolog_flag(@var{+FlagName},@var{?OldValue}) @findex prolog_flag/2 This is a shorthand for @example prolog_flag(@var{FlagName},@var{OldValue},@var{OldValue}) @end example @item copy_term(@var{?Term},@var{?CopyOfTerm}) @findex copy_term/2 @var{CopyOfTerm} is an independent copy of @var{Term}, with new variables substituted for all variables in @var{Term}. It is defined as if by @refill @example copy_term(X, Y) :- assert('copy of'(X)), retract('copy of'(Y)). @end example @item numbervars(@var{?Term},@var{+N},@var{?M}) @findex numbervars/3 Unifies each of the variables in term @var{Term} with a special term, so that @code{write(@var{Term})} (or @code{writeq(@var{Term})}) (@pxref{Term IO}) prints those variables as (@kbd{A} + (@var{i} mod 26))(@var{i}/26) where @var{i} ranges from @var{N} to @var{M}-1. @var{N} must be instantiated to an integer. If it is 0 you get the variable names A, B, @dots{}, Z, A1, B1, etc. This predicate is used by @code{listing/0, listing/1} (@pxref{State Info}). @refill @item setarg(@var{+ArgNo},@var{+CompoundTerm},@var{?NewArg}) @findex setarg/3 Replace destructively argument @var{ArgNo} in @var{CompoundTerm} by @var{NewArg}. The assignment is undone on backtracking. @strong{This operation is only safe if there is no further use of the ``old'' value of the replaced argument}. The use of this predicate is discouraged, as the idea of destructive replacement is alien to logic programming. @refill @item undo(@var{+Term}) @findex undo/1 The goal @code{call(@var{Term})} (@pxref{Control}) is executed on backtracking. @refill @item halt @findex halt/0 Causes an irreversible exit from Prolog back to the shell. @refill @item op(@var{+Precedence},@var{+Type},@var{+Name}) @findex op/3 Declares the atom @var{Name} to be an operator of the stated @var{Type} and @var{Precedence} (@pxref{Operators}). @var{Name} may also be a list of atoms in which case all of them are declared to be operators. If @var{Precedence} is 0 then the operator properties of @var{Name} (if any) are cancelled. @refill @item current_op(@var{?Precedence},@var{?Type},@var{?Op}) @findex current_op/3 The atom @var{Op} is currently an operator of type @var{Type} and precedence @var{Precedence}. Neither @var{Op} nor the other arguments need be instantiated at the time of the call; i.e. this predicate can be used to generate as well as to test. @refill @item break @findex break/0 Invokes the Prolog interpreter recursively. @xref{Nested}. @refill @item query_expansion(@var{+RawQuery},@var{?Query}) @findex query_expansion/1 @emph{A user defined predicate}, which may be used to transform queries entered at the terminal in response to the @samp{| ?-} prompt. The Prolog interpreter will call this for every top-level query @var{RawQuery}. If it succeeds, @var{Query} will be executed instead of @var{RawQuery}, but the variable bindings will be printed as usual upon completion. This feature is useful e.g. to implement a simple command interpreter. @refill @item abort @findex abort/0 Aborts the current execution. @xref{Nested}. @refill @item save(@var{+File}) @findex save/1 The system saves the current state of the system into file @var{File}. When it is restored, Prolog will resume execution that called @code{save/1}. @xref{Saving}. @refill @item save(@var{+File},@var{?Return}) @findex save/2 Saves the current system state in @var{File} just as @code{save(@var{File})}, but in addition unifies @var{Return} to 0 or 1 depending on whether the return from the call occurs in the original incarnation of the state or through a call @code{restore(@var{File})} (respectively). @refill @item save_program(@var{+File}) @findex save_program/1 The system saves the currently defined predicates into file @var{File}. When it is restored, Prolog will reinitialise itself. @xref{Saving}. @refill @item restore(@var{+File}) @findex restore/1 The system is returned to the system state previously saved to file @var{File}. @xref{Saving}. @refill @item reinitialise @findex reinitialise/0 This predicate can be used to force the initialisation behaviour to take place at any time. When SICStus is initialised it looks for a file @file{~/.sicstusrc} and consults it, if it exists. @refill @item maxdepth(@var{+Depth}) @findex maxdepth/1 The positive integer @var{Depth} specifies the maximum depth, i.e. the maximum number of nested interpreted calls, beyond which the interpreter will trap to the debugger. The top level has zero depth. This is useful for guarding against loops in an untested program, or for curtailing infinite execution branches. Note that calls to compiled predicates are not included in the computation of the depth. The interpreter will check for maximum depth only if the debugger is switched on. @refill @item depth(@var{?Depth}) @findex depth/1 Unifies @var{Depth} with the current depth, i.e. the number of currently active interpreted procedure calls. Depth information is only available when the debugger is switched on. @refill @item garbage_collect @findex garbage_collect/0 Perform a garbage collection of the global stack immediately. @refill @item gc @findex gc/0 Enables garbage collection of the global stack (the default). @refill @item nogc @findex nogc/0 Disables garbage collection of the global stack. @item statistics @findex statistics/0 Display on the terminal statistics relating to memory usage, run time, garbage collection of the global stack and stack shifts. @refill @item statistics(@var{?Key},@var{?Value}) @findex statistics/2 This allows a program to gather various execution statistics. For each of the possible keys @var{Key}, @var{Value} is unified with a list of values, as follows: @refill @table @code @item global_stack @code{[@var{size used},@var{free}]}@* This refers to the global stack, where compound terms are stored. @item local_stack @code{[@var{size used},@var{free}]}@* This refers to the local stack, where recursive predicate environments are stored. @item trail @code{[@var{size used},@var{free}]}@* This refers to the trail stack, where conditional variable bindings are recorded. @item choice @code{[@var{size used},@var{free}]}@* This refers to the choicepoint stack, where partial states are stored for backtracking purposes. @item core @itemx memory @code{[@var{size used},0]}@* These refer to the amount of memory actually allocated by the UNIX process. @item heap @itemx program @code{[@var{size used},0]}@* These refer to the amount of memory allocated for compiled and interpreted clauses, symbol tables, and the like. @item runtime @code{[@var{since start of Prolog},@var{since previous statistics}]} @item garbage_collection @code{[@var{no. of GCs},@var{bytes freed},@var{time spent}]} @item stack_shifts @code{[@var{no. of local shifts},@var{no. of trail shifts},@var{time spent}]} @end table Times are in milliseconds, sizes of areas in bytes. @item prompt(@var{?Old},@var{?New}) @findex prompt/2 The sequence of characters (prompt) which indicates that the system is waiting for user input is represented as an atom, and unified with @var{Old}; the atom bound to New specifies the new prompt. In particular, the goal @code{prompt(X, X)} unifies the current prompt with @var{X}, without changing it. Note that this predicate only affects the prompt given when a user's program is trying to read from the terminal (e.g. by calling @code{read/1}). Note also that the prompt is reset to the default @samp{|: } on return to top-level. @refill @item version @findex version/0 Displays the introductory messages for all the component parts of the current system. @refill Prolog will display its own introductory message when initially run but not normally at any time after this. If this message is required at some other time it can be obtained using this predicate which displays a list of introductory messages; initially this list comprises only one message (Prolog's), but you can add more messages using @code{version/1}. @refill @item version(@var{+Message}) @findex version/1 This takes a message, in the form of an atom, as its argument and appends it to the end of the message list which is output by @code{version/0}. @refill The idea of this message list is that, as systems are constructed on top of other systems, each can add its own identification to the message list. Thus @code{version/0} should always indicate which modules make up a particular package. It is not possible to remove messages from the list. @refill @item help @findex help/0 Displays basic information, or a user defined help message. It first calls @code{user_help/0}, and only if that call fails is a default help message printed on the current output stream. @refill @item user_help @findex user_help/0 @emph{A user defined predicate.} This may be defined by the user to print a help message on the current output stream. @refill @item unix(@var{+Term}) @itemx plsys(@var{+Term}) @findex unix/1 @findex plsys/1 Allows certain interactions with the operating system. Under UNIX the possible forms of @var{Term} are as follows: @refill @table @code @item access(@var{+Path},@var{+Mode}) The path name @var{Path} and the integer @var{Mode} are passed to the UNIX C library function @code{access(2)}. The call succeeds if access is granted. @item argv(@var{?Args}) @var{Args} is unified with a list of atoms representing the program arguments supplied when the current SICStus process was started (@pxref{Installation Intro}). For example, if SICStus were invoked with @refill @example % prolog hello world @end example @noindent then @var{Args} would be unified with @code{[hello,world]}. @item cd(@var{+Path}) Change the current working directory to @var{Path}. @item cd Change the current working directory to the home directory. @refill @item chmod(@var{+Path},@var{?Old},@var{?New}) The path name @var{Path} and the integer @var{New} are passed to the UNIX C library function @code{chmod(2)}. @var{Old} is unified with the old file mode. The call succeeds if access is granted. @item exit(@var{+Status}) The SICStus process is exited, returning the integer value @var{Status}. @item mktemp(@var{+Template},@var{?Filename}) @var{Filename} is unified with a unique filename constructed from the atom @var{Template}. This is an interface to the UNIX C library function @code{mktemp(3)}. @item shell Start a new interactive UNIX shell. The control is returned to Prolog upon termination of the shell. @refill @item shell(@var{+Command}) Pass @var{Command} to a new UNIX shell for execution. @refill @item shell(@var{+Command},@var{?Status}) @var{Command} is passed to a new UNIX shell for execution, and @var{Status} is unified with the value returned by the shell. @item system(@var{+Command}) Pass @var{Command} to a new UNIX @code{sh} process for execution. @refill @item system(@var{+Command},@var{?Status}) @var{Command} is passed to a new UNIX @code{sh} process for execution, and @var{Status} is unified with the value returned by the process. @item umask(@var{?Old},@var{?New}) The integer @var{New} are passed to the UNIX C library function @code{umask(2)}. @var{Old} is unified with the old file mode creation mask. @end table @end table @node Prolog Intro, Syntax, Misc Pred, Top @comment node-name, next, previous, up @chapter The Prolog Language @cindex defininte clause @cindex Horn clause This chapter provides a brief introduction to the syntax and semantics of a certain subset of logic (@dfn{definite clauses}, also known as @dfn{Horn clauses}), and indicates how this subset forms the basis of Prolog. @node Syntax, Terms, Prolog Intro, Top @comment node-name, next, previous, up @section Syntax, Terminology and Informal Semantics @node Terms, Programs, Syntax, Top @comment node-name, next, previous, up @subsection Terms @cindex term @cindex constant @cindex variable @cindex compound term The data objects of the language are called @dfn{terms}. A term is either a @dfn{constant}, a @dfn{variable} or a @dfn{compound term}. @cindex integer The constants include @dfn{integers} such as @example 0 1 999 -512 @end example Besides the usual decimal, or base 10, notation, integers may also be written in any base from 2 to 36, of which base 2 (binary), 8 (octal), and 16 (hex) are probably the most useful. Letters @kbd{A} through @kbd{Z} (upper or lower case) are used for bases greater than 10. E.g. @example 15 2'1111 8'17 16'F @end example @noindent all represent the integer fifteen. There is also a special notation for character constants. E.g. @example 0'A @end example @noindent is equivalent to @code{65} (the numerical value of the ASCII code for @kbd{A}). @refill @cindex float Constants also include @dfn{floats} such as @example 1.0 -3.141 4.5E7 -0.12e+8 12.0e-9 @end example Note that there must be a decimal point in floats written with an exponent, and that there must be at least one digit before and after the decimal point. @cindex atom Constants also include @dfn{atoms} such as @example a void = := 'Algol-68' [] @end example Constants are definite elementary objects, and correspond to proper nouns in natural language. For reference purposes, here is a list of the possible forms which an atom may take: @enumerate @item Any sequence of alphanumeric characters (including @kbd{_}), starting with a lower case letter. @refill @item Any sequence from the following set of characters:@* @kbd{+}@kbd{-}@kbd{*}@kbd{/}@kbd{\}@kbd{^}@kbd{<}@kbd{>}@kbd{=}@kbd{`}@kbd{~}@kbd{:}@kbd{.}@kbd{?}@kbd{@@}@kbd{#}@kbd{$}@kbd{&}@* This set can in fact be larger; @pxref{Token String} for a precise definition. @item Any sequence of characters delimited by single quotes. If the single quote character is included in the sequence it must be written twice, e.g. @code{'can''t'}. @refill @item Any of: @kbd{!} @kbd{;} @kbd{[]} @kbd{@{@}}@* Note that the bracket pairs are special: @kbd{[]} and @kbd{@{@}} are atoms but @kbd{[}, @kbd{]}, @kbd{@{}, and @kbd{@}} are not. However, when they are used as functors (see below) the form @code{@{@var{X}@}} is allowed as an alternative to @code{@{@}(@var{X})}. The form @code{[@var{X}]} is the normal notation for lists, as an alternative to @code{.(X,[])}. @refill @end enumerate Variables may be written as any sequence of alphanumeric characters (including @kbd{_}) starting with either a capital letter or @kbd{_}; e.g. @example X Value A A1 _3 _RESULT @end example @cindex anonymous variable If a variable is only referred to once in a clause, it does not need to be named and may be written as an @dfn{anonymous} variable, indicated by the underline character @kbd{_}. A clause may contain several anonymous variables; they are all read and treated as distinct variables. A variable should be thought of as standing for some definite but unidentified object. This is analogous to the use of a pronoun in natural language. Note that a variable is not simply a writeable storage location as in most programming languages; rather it is a local name for some data object, cf. the variable of pure LISP and identity declarations in Algol68. @cindex functor @cindex arity The structured data objects of the language are the compound terms. A compound term comprises a @dfn{functor} (called the principal functor of the term) and a sequence of one or more terms called @dfn{arguments}. A functor is characterised by its name, which is an atom, and its @dfn{arity} or number of arguments. For example the compound term whose functor is named @code{point} of arity 3, with arguments @code{X}, @code{Y} and @code{Z}, is written @refill @example point(X, Y, Z) @end example Note that an atom is considered to be a functor of arity 0. Functors are generally analogous to common nouns in natural language. One may think of a functor as a record type and the arguments of a compound term as the fields of a record. Compound terms are usefully pictured as trees. For example, the term @example s(np(john),vp(v(likes),np(mary))) @end example @noindent would be pictured as the structure @smallexample s / \ np vp | / \ john v np | | likes mary @end smallexample Sometimes it is convenient to write certain functors as operators---2-ary functors may be declared as infix operators and 1-ary functors as prefix or postfix operators. Thus it is possible to write, e.g. @example X+Y (P;Q) X<Y +X P; @end example @noindent as optional alternatives to @example +(X,Y) ;(P,Q) <(X,Y) +(X) ;(P) @end example @noindent The use of operators is described fully below (@pxref{Operators}). Lists form an important class of data structures in Prolog. They are essentially the same as the lists of LISP: a list either is the atom @code{[]} representing the empty list, or is a compound term with functor @code{.} and two arguments which are respectively the head and tail of the list. Thus a list of the first three natural numbers is the structure @refill @smallexample . / \ 1 . / \ 2 . / \ 3 [] @end smallexample @noindent which could be written, using the standard syntax, as @example .(1,.(2,.(3,[]))) @end example @noindent but which is normally written, in a special list notation, as @example [1,2,3] @end example @noindent The special list notation in the case when the tail of a list is a variable is exemplified by @example [X|L] [a,b|L] @end example @noindent representing @smallexample . . / \ / \ X L a . / \ b L @end smallexample @noindent respectively. Note that this notation does not add any new power to the language; it simply makes it more readable. e.g. the above examples could equally be written @example .(X,L) .(a,.(b,L)) @end example @cindex string For convenience, a further notational variant is allowed for lists of integers which correspond to ASCII character codes. Lists written in this notation are called @dfn{strings}. E.g. @example "SICStus" @end example @noindent which represents exactly the same list as @example [83,73,67,83,116,117,115] @end example @node Programs, Declarative, Terms, Top @comment node-name, next, previous, up @subsection Programs @cindex program @cindex goal A fundamental unit of a logic program is the @dfn{goal} or procedure call. E.g. @refill @example gives(tom, apple, teacher) reverse([1,2,3], L) X<Y @end example @cindex predicate A goal is merely a special kind of term, distinguished only by the context in which it appears in the program. The (principal) functor of a goal identifies what @dfn{predicate} the goal is for. It corresponds roughly to a verb in natural language, or to a procedure name in a conventional programming language. @refill @cindex sentence @cindex clause @cindex head @cindex body A logic program consists simply of a sequence of statements called @dfn{sentences}, which are analogous to sentences of natural language. A sentence comprises a @dfn{head} and a @dfn{body}. The head either consists of a single goal or is empty. The body consists of a sequence of zero or more goals (i.e. it too may be empty). If the head is not empty, the sentence is called a @dfn{clause}. @refill @cindex unit clause If the body of a clause is empty, the clause is called a @dfn{unit clause}, and is written in the form @example @var{P}. @end example @noindent where @var{P} is the head goal. We interpret this declaratively as @quotation @var{P} is true. @end quotation @noindent and procedurally as @quotation Goal @var{P} is satisfied. @end quotation @cindex non-unit clause If the body of a clause is non-empty, the clause is called a @dfn{non-unit clause}, and is written in the form @example @var{P} :- @var{Q}, @var{R}, @var{S}. @end example @noindent where @var{P} is the head goal and @var{Q}, @var{R} and @var{S} are the goals which make up the body. We can read such a clause either declaratively as @refill @quotation @var{P} is true if @var{Q} and @var{R} and @var{S} are true. @end quotation or procedurally as @quotation To satisfy goal @var{P}, satisfy goals @var{Q}, @var{R} and @var{S}. @end quotation A sentence with an empty head is called a @dfn{directive} (@pxref{Directives}), of which the most important kind is called a @dfn{query} and is written in the form @refill @example ?- @var{P}, @var{Q}. @end example @noindent where @var{P} and @var{Q} are the goals of the body. Such a query is read declaratively as @quotation Are @var{P} and @var{Q} true? @end quotation @noindent and procedurally as @quotation Satisfy goals @var{P} and @var{Q}. @end quotation Sentences generally contain variables. Note that variables in different sentences are completely independent, even if they have the same name---i.e. the @dfn{lexical scope} of a variable is limited to a single sentence. Each distinct variable in a sentence should be interpreted as standing for an arbitrary entity, or value. To illustrate this, here are some examples of sentences containing variables, with possible declarative and procedural readings: @enumerate @item @code{employed(@var{X}) :- employs(@var{Y},@var{X}).} ``Any @var{X} is employed if any @var{Y} employs @var{X}.'' ``To find whether a person @var{X} is employed, find whether any @var{Y} employs @var{X}.'' @refill @item @code{derivative(@var{X},@var{X},1).} ``For any @var{X}, the derivative of @var{X} with respect to @var{X} is 1.'' @refill ``The goal of finding a derivative for the expression @var{X} with respect to @var{X} itself is satisfied by the result 1.'' @refill @item @code{?- ungulate(@var{X}), aquatic(@var{X}).} ``Is it true, for any @var{X}, that @var{X} is an ungulate and @var{X} is aquatic?'' @refill ``Find an @var{X} which is both an ungulate and aquatic.'' @end enumerate @cindex predicate In any program, the @dfn{predicate} for a particular (principal) functor is the sequence of clauses in the program whose head goals have that principal functor. For example, the predicate for a 3-ary functor @code{concatenate/3} might well consist of the two clauses @refill @example concatenate([], L, L). concatenate([X|L1], L2, [X|L3]) :- concatenate(L1, L2, L3). @end example @noindent where @code{concatenate(@var{L1},@var{L2},@var{L3})} means ``the list @var{L1} concatenated with the list @var{L2} is the list @var{L3}''. Note that for predicates with clauses corresponding to a base case and a recursive case, the preferred style is to write the base case clause first. In Prolog, several predicates may have the same name but different arities. Therefore, when it is important to specify a predicate unambiguously, the form @code{@var{name}/@var{arity}} is used; e.g. @code{concatenate/3}. @cindex built-in predicate Certain predicates are predefined by built-in predicates supplied by the Prolog system. Such predicates are called @dfn{built-in predicates}. As we have seen, the goals in the body of a sentence are linked by the operator @samp{,} which can be interpreted as conjunction (``and''). It is sometimes convenient to use an additional operator @samp{;}, standing for disjunction (``or''). (The precedence of @samp{;} is such that it dominates @samp{,} but is dominated by @samp{:-}.) An example is the clause @refill @example grandfather(X, Z) :- (mother(X, Y); father(X, Y)), father(Y, Z). @end example @noindent which can be read as @quotation For any @var{X}, @var{Y} and @var{Z}, @var{X} has @var{Z} as a grandfather if either the mother of @var{X} is @var{Y} or the father of @var{X} is @var{Y}, and the father of @var{Y} is @var{Z}. @end quotation Such uses of disjunction can always be eliminated by defining an extra predicate---for instance the previous example is equivalent to @example grandfather(X,Z) :- parent(X,Y), father(Y,Z). parent(X,Y) :- mother(X,Y). parent(X,Y) :- father(X,Y). @end example @noindent ---and so disjunction will not be mentioned further in the following, more formal, description of the semantics of clauses. The token @samp{|}, when used outside a list, is an alias for @samp{;}. The aliasing is performed when terms are read in, so that @example a :- b | c. @end example @noindent is read as if it were @example a :- b ; c. @end example Note the double use of the @samp{.} character. On the one hand it is used as a sentence terminator, while on the other it may be used in a string of symbols which make up an atom (e.g. the list functor @code{./2}). The rule used to disambiguate terms is that a @samp{.} followed by a @var{layout-char} is regarded as a sentence terminator (@pxref{Token String}). @node Declarative, Procedural, Programs, Top @comment node-name, next, previous, up @section Declarative Semantics @cindex declarative semantics @cindex semantics The semantics of definite clauses should be fairly clear from the informal interpretations already given. However it is useful to have a precise definition. The @dfn{declarative semantics} of definite clauses tells us which goals can be considered true according to a given program, and is defined recursively as follows. @quotation A goal is true if it is the head of some clause instance and each of the goals (if any) in the body of that clause instance is true, where an instance of a clause (or term) is obtained by substituting, for each of zero or more of its variables, a new term for all occurrences of the variable. @end quotation For example, if a program contains the preceding predicate for @code{concatenate/3}, then the declarative semantics tells us that @refill @example ?- concatenate([a], [b], [a,b]). @end example @noindent is true, because this goal is the head of a certain instance of the first clause for @code{concatenate/3}, namely, @example concatenate([a], [b], [a,b]) :- concatenate([], [b], [b]). @end example @noindent and we know that the only goal in the body of this clause instance is true, since it is an instance of the unit clause which is the second clause for @code{concatenate/3}. @node Procedural, Occur, Programs, Top @comment node-name, next, previous, up @section Procedural Semantics @cindex procedural semantics @cindex semantics Note that the declarative semantics makes no reference to the sequencing of goals within the body of a clause, nor to the sequencing of clauses within a program. This sequencing information is, however, very relevant for the @dfn{procedural semantics} which Prolog gives to definite clauses. The procedural semantics defines exactly how the Prolog system will execute a goal, and the sequencing information is the means by which the Prolog programmer directs the system to execute the program in a sensible way. The effect of executing a goal is to enumerate, one by one, its true instances. Here then is an informal definition of the procedural semantics. We first illustrate the semantics by the simple query @example ?- concatenate(@var{X}, @var{Y}, [a,b]). @end example @noindent We find that it matches the head of the first clause for @code{concatenate/3}, with @var{X} instantiated to @code{[a|@var{X1}]}. The new variable @var{X1} is constrained by the new query produced, which contains a single recursive procedure call: @refill @example ?- concatenate(@var{X1}, @var{Y}, [b]). @end example @noindent Again this goal matches the first clause, instantiating @var{X1} to @code{[b|@var{X2}]}, and yielding the new query: @example ?- concatenate(@var{X2}, @var{Y}, []) @end example @noindent Now the single goal will only match the second clause, instantiating both @var{X2} and @var{Y} to @code{[]}. Since there are no further goals to be executed, we have a solution @refill @example X = [a,b] Y = [] @end example @noindent i.e. a true instance of the original goal is @example concatenate([a,b], [], [a,b]) @end example @noindent If this solution is rejected, backtracking will generate the further solutions @example X = [a] Y = [b] X = [] Y = [a,b] @end example @noindent in that order, by re-matching, against the second clause for concatenate, goals already solved once using the first clause. Thus, in the procedural semantics, the set of clauses @example @var{H} :- @var{B1}, ..., @var{Bm}. @var{H'} :- @var{B1'}, ..., @var{Bm'}. ... @end example @noindent @cindex procedure definition are regarded as a @dfn{procedure definition} for some predicate @var{H}, and in a query @example ?- @var{G1}, ..., @var{Gn}. @end example @noindent @cindex procedure call @cindex computation rule @cindex search rule @cindex unification each @var{Gi} is regarded as a @dfn{procedure call}. To execute a query, the system selects by its @dfn{computation rule} a goal, @var{Gj} say, and searches by its @dfn{search rule} a clause whose head matches @var{Gj}. Matching is done by the @dfn{unification} algorithm (see @cite{A Machine-Oriented Logic Based on the Resolution Principle} by J.A. Robinson, @cite{Journal of the ACM} 12:23-44, January 1965) which computes the most general unifier, @dfn{mgu}, of @var{Gj} and @var{H}. The @var{mgu} is unique if it exists. If a match is found, the current query is @dfn{reduced} to a new query @refill @example ?- (@var{G1}, ..., @var{Gj-1}, @var{B1}, ..., @var{Bm}, @var{Gj+1}, ..., @var{Gn})@var{mgu}. @end example @noindent and a new cycle is started. The execution terminates when the empty query has been produced. @cindex backtracking If there is no matching head for a goal, the execution @dfn{backtracks} to the most recent successful match in an attempt to find an alternative match. If such a match is found, an alternative new query is produced, and a new cycle is started. In SICStus Prolog, as in other Prolog systems, the search rule is simple: ``search forward from the beginning of the program''. @cindex blocking The computation rule in most Prolog systems is simple too: ``pick the leftmost goal of the current query''. However, SICStus Prolog, Prolog II, NU-Prolog, and a few other systems have a somewhat more complex computation rule ``pick the leftmost @dfn{unblocked} goal of the current query''. A goal is @dfn{blocked on its first argument} if that argument is uninstantiated and its predicate definition is annotated with a @dfn{wait declaration} (@pxref{Declarations}). Goals of the built-in predicates @code{freeze/1} and @code{dif/2} (q.v.) may also be blocked if their arguments are not instantiated enough. A goal can only be blocked on a single uninstantiated variable, but a variable may block several goals. @refill Thus binding a variable can cause blocked goals to become unblocked, and backtracking can cause currently unblocked goals to become blocked again. Moreover, if the current query is @example ?- @var{G1}, ..., @var{Gj-1}, @var{Gj}, @var{Gj+1}, ..., @var{Gn}. @end example @noindent where @var{Gj} is the first unblocked goal, and matching @var{Gj} against a clause head causes several blocked goals in @var{G1}, ..., @var{Gj-1} to become unblocked, then these goals may become reordered. The internal order of any two goals that were blocked on the @emph{same} variable is retained, however. @refill @cindex floundering Another consequence is that a query may be derived consisting entirely of blocked goals. Such a query is said to have @dfn{floundered}. The interpreter top-level checks for this condition. If detected, the outstanding blocked subgoals are printed on the terminal along with the answer substitution, to notify the user that the answer (s)he has got is really a speculative one, since it is only valid if the blocked goals can be satisfied. In compiled code, the computation rule is not completely obeyed, as calls to certain built-in predicates compile to instructions. Such calls are executed even if a unification just prior to the call causes a blocked goal to become unblocked. The following built-in predicates do not compile to procedure calls in compiled code. Note also that there is an implicit cut in the @code{\+} and @code{->} constructs: @example 'C'/3 arg/3 atom/1 atomic/1 compare/3 float/1 functor/3 is/2 integer/1 nonvar/1 number/1 var/1 '=='/2 '\=='/2 '@@<'/2 '@@>='/2 '@@>'/2 '@@=<'/2 '=:='/2 '=\='/2 '<'/2 '>='/2 '>'/2 '=<'/2 '=..'/2 '='/2 ','/2 !/0 @end example Sometimes, it is crucial that the blocked goal be executed before a call to one of the above built-in predicates. Since most of the above are meta-logical primitives, their semantics can depend on whether a variable is currently bound etc. Consider, for example, the clauses and query @example :- wait test/1. test(2). data(1). data(2). ?- test(X), data(X), !, ... @end example @noindent thus the first match for @code{data(X)} causes the blocked goal @code{test(X)} to be unblocked, but since the cut is selected before @code{test(X)}, the system is committed to the first match for @code{data(X)}, and the query fails. However, inserting a dummy goal @code{true} enables the unblocked goal to be selected before the cut: @refill @example ?- test(X), data(X), true, !, ... @end example @noindent As @code{test(1)} fails, the system backtracks to the second clause for @code{data(X)}, and the query succeeds with the answer @example X = 2 @end example @node Occur, Cut, Procedural, Top @comment node-name, next, previous, up @section Occurs Check @cindex occurs check It is possible, and sometimes useful, to write programs which unify a variable to a term in which that variable occurs, thus creating a cyclic term. The usual mathematical theory behind Logic Programming forbids the creation of cyclic terms, dictating that an @dfn{occurs check} should be done each time a variable is unified with a term. Unfortunately, an occurs check would be so expensive as to render Prolog impractical as a programming language. Thus cyclic terms may be created and may cause loops trying to print them. SICStus Prolog mitigates the problem by its ability to unify and compare (@pxref{Term Compare}) cyclic terms without looping. Loops in the printer can be interrupted by typing @ctrl{C}. @node Cut, Operators, Occur, Top @comment node-name, next, previous, up @section The Cut Symbol @findex !/0, cut @cindex cut Besides the sequencing of goals and clauses, Prolog provides one other very important facility for specifying control information. This is the @dfn{cut} symbol, written @code{!}. It is inserted in the program just like a goal, but is not to be regarded as part of the logic of the program and should be ignored as far as the declarative semantics is concerned. The effect of the cut symbol is as follows. When first encountered as a goal, cut succeeds immediately. If backtracking should later return to the cut, the effect is to fail the @dfn{parent goal}, i.e. that goal which matched the head of the clause containing the cut, and caused the clause to be activated. In other words, the cut operation @emph{commits} the system to all choices made since the parent goal was invoked, and causes other alternatives to be discarded. The goals thus rendered @dfn{determinate} are the parent goal itself, any goals occurring before the cut in the clause containing the cut, and any subgoals which were executed during the execution of those preceding goals. e.g. @example member(X, [X|_]). member(X, [_|L]) :- member(X, L). @end example @noindent This predicate can be used to test whether a given term is in a list. E.g. @example | ?- member(b, [a,b,c]). @end example @noindent returns the answer @samp{yes}. The predicate can also be used to extract elements from a list, as in @example | ?- member(X, [d,e,f]). @end example @noindent With backtracking this will successively return each element of the list. Now suppose that the first clause had been written instead: @example member(X, [X|_]) :- !. @end example @noindent In this case, the above call would extract only the first element of the list (@code{d}). On backtracking, the cut would immediately fail the whole predicate. @example x :- p, !, q. x :- r. @end example @noindent This is equivalent to @example x := if p then q else r; @end example @noindent in an Algol-like language. It should be noticed that a cut discards all the alternatives since the parent goal, even when the cut appears within a disjunction. This means that the normal method for eliminating a disjunction by defining an extra predicate cannot be applied to a disjunction containing a cut. A proper use of the cut is usually a major difficulty for new Prolog programmers. The usual mistakes are to over-use cut, and to let cuts destroy the logic. We would like to advise all users to follow these general rules. Also @pxref{Example Intro}. @itemize @bullet @item Write each clause as a self-contained logic rule which just defines the truth of goals which match its head. Then add cuts to remove any fruitless alternative computation paths that may tie up store. @item Cuts are usually placed right after the head, sometimes preceded by simple tests. @item Cuts are hardly ever needed in the last clause of a predicate. @end itemize @node Operators, Restrictions, Cut, Top @comment node-name, next, previous, up @section Operators @cindex operators Operators in Prolog are simply a @emph{notational convenience}. For example, the expression @code{2+1} could also be written @code{+(2,1)}. This expression represents the data structure @smallexample + / \ 2 1 @end smallexample @noindent and @emph{not} the number 3. The addition would only be performed if the structure were passed as an argument to an appropriate predicate such as @code{is/2} (@pxref{Arithmetic}). @refill The Prolog syntax caters for operators of three main kinds---@dfn{infix}, @dfn{prefix} and @dfn{postfix}. An infix operator appears between its two arguments, while a prefix operator precedes its single argument and a postfix operator is written after its single argument. @refill Each operator has a precedence, which is a number from 1 to 1200. The precedence is used to disambiguate expressions where the structure of the term denoted is not made explicit through the use of parentheses. The general rule is that it is the operator with the @emph{highest} precedence that is the principal functor. Thus if @samp{+} has a higher precedence than @samp{/}, then @refill @example a+b/c a+(b/c) @end example @noindent are equivalent and denote the term @code{+(a,/(b,c))}. Note that the infix form of the term @code{/(+(a,b),c)} must be written with explicit parentheses, i.e. @refill @example (a+b)/c @end example If there are two operators in the subexpression having the same highest precedence, the ambiguity must be resolved from the types of the operators. The possible types for an infix operator are @example xfx xfy yfx @end example Operators of type @code{xfx} are not associative: it is a requirement that both of the two subexpressions which are the arguments of the operator must be of @emph{lower} precedence than the operator itself, i.e. their principal functors must be of lower precedence, unless the subexpression is explicitly parenthesised (which gives it zero precedence). Operators of type @code{xfy} are right-associative: only the first (left-hand) subexpression must be of lower precedence; the right-hand subexpression can be of the @emph{same} precedence as the main operator. Left-associative operators (type @code{yfx}) are the other way around. @findex op/3 A functor named name is declared as an operator of type @var{Type} and precedence @var{Precedence} by the command @example :- op(@var{Precedence}, @var{Type}, @var{Name}). @end example The argument name can also be a list of names of operators of the same type and precedence. It is possible to have more than one operator of the same name, so long as they are of different kinds, i.e. infix, prefix or postfix. An operator of any kind may be redefined by a new declaration of the same kind. This applies equally to operators which are provided as standard. Declarations of all the standard operators can be found elsewhere (@pxref{Standard Operators}). @refill For example, the standard operators @code{+} and @code{-} are declared by @example :- op( 500, yfx, [ +, - ]). @end example @noindent so that @example a-b+c @end example @noindent is valid syntax, and means @example (a-b)+c @end example @noindent i.e. @smallexample + / \ - c / \ a b @end smallexample The list functor @code{.} is not a standard operator, but we could declare it thus: @example :- op(900, xfy, .). @end example Then @code{a.b.c} would represent the structure @smallexample . / \ a . / \ b c @end smallexample Contrasting this with the diagram above for @code{a-b+c} shows the difference betweeen @code{yfx} operators where the tree grows to the left, and @code{xfy} operators where it grows to the right. The tree cannot grow at all for @code{xfx} operators; it is simply illegal to combine @code{xfx} operators having equal precedences in this way. @refill The possible types for a prefix operator are @example fx fy @end example @noindent and for a postfix operator they are @example xf yf @end example The meaning of the types should be clear by analogy with those for infix operators. As an example, if @code{not} were declared as a prefix operator of type @code{fy}, then @example not not P @end example @noindent would be a permissible way to write @code{not(not(P))}. If the type were @code{fx}, the preceding expression would not be legal, although @refill @example not P @end example @noindent would still be a permissible form for @code{not(P)}. If these precedence and associativity rules seem rather complex, remember that you can always use parentheses when in any doubt. Note that the arguments of a compound term written in standard syntax must be expressions of precedence @emph{below} 1000. Thus it is necessary to parenthesise the expression @code{P :- Q} in @example ?- assert((P :- Q)). @end example @node Restrictions, Comments, Operators, Top @comment node-name, next, previous, up @section Syntax Restrictions @cindex syntax restrictions Note carefully the following syntax restrictions, which serve to remove potential ambiguity associated with prefix operators. @enumerate @item In a term written in standard syntax, the principal functor and its following @kbd{(} must @emph{not} be separated by any intervening spaces, newlines etc. Thus @refill @example point (X,Y,Z) @end example @noindent is invalid syntax. @item If the argument of a prefix operator starts with a @kbd{(}, this @kbd{(} must be separated from the operator by at least one space or other non-printable character. Thus @refill @example :-(p;q),r. @end example @noindent (where @samp{:-} is the prefix operator) is invalid syntax. The system would try to interpret it as the structure: @refill @smallexample , / \ :- r | ; / \ p q @end smallexample That is, it would take @samp{:-} to be a functor of arity 1. However, since the arguments of a functor are required to be expressions of precedence below 1000, this interpretation would fail as soon as the @samp{;} (precedence 1100) was encountered. @refill In contrast, the term: @example :- (p;q),r. @end example @noindent is valid syntax and represents the following structure. @smallexample :- | , / \ ; r / \ p q @end smallexample @end enumerate @node Comments, Full Syntax, Restrictions, Top @comment node-name, next, previous, up @section Comments @comment Comments have no effect on the execution of a program, but they are very useful for making programs more readily comprehensible. Two forms of comment are allowed in Prolog: @enumerate @item The character @kbd{%} followed by any sequence of characters up to end of line. @item The symbol @kbd{/*} followed by any sequence of characters (including new lines) up to @kbd{*/}. @refill @end enumerate @node Full Syntax, Syntax Notation, Comments, Top @comment node-name, next, previous, up @section Full Prolog Syntax A Prolog program consists of a sequence of @dfn{sentences}. Each sentence is a Prolog @dfn{term}. How terms are interpreted as sentences is defined below (@pxref{Sentence}). Note that a term representing a sentence may be written in any of its equivalent syntactic forms. For example, the 2-ary functor @samp{:-} could be written in standard prefix notation instead of as the usual infix operator. @refill Terms are written as sequences of @dfn{tokens}. Tokens are sequences of characters which are treated as separate symbols. Tokens include the symbols for variables, constants and functors, as well as punctuation characters such as brackets and commas. We define below how lists of tokens are interpreted as terms (@pxref{Term Token}). Each list of tokens which is read in (for interpretation as a term or sentence) has to be terminated by a full-stop token. Two tokens must be separated by a space token if they could otherwise be interpreted as a single token. Both space tokens and comment tokens are ignored when interpreting the token list as a term. A comment may appear at any point in a token list (separated from other tokens by spaces where necessary).@refill We define below how tokens are represented as strings of characters (@pxref{Token String}). But we start by describing the notation used in the formal definition of Prolog syntax (@pxref{Syntax Notation}). @refill @node Syntax Notation, Sentence, Full Syntax, Top @comment node-name, next, previous, up @subsection Notation @cindex syntax notation @enumerate @item Syntactic categories (or @dfn{non-terminals}) are written thus: @var{item}. Depending on the section, a category may represent a class of either terms, token lists, or character strings. @refill @item A syntactic rule takes the general form @example @var{C} --> @var{F1} | @var{F2} | @var{F3} @end example @noindent which states that an entity of category @var{C} may take any of the alternative forms @var{F1}, @var{F2}, @var{F3}, etc. @refill @item Certain definitions and restrictions are given in ordinary English, enclosed in @{ @} brackets. @refill @item A category written as @var{C...} denotes a sequence of one or more @var{C}s. @refill @item A category written as @var{?C} denotes an optional @var{C}. Therefore @var{?C...} denotes a sequence of zero or more @var{C}s.@refill @item A few syntactic categories have names with arguments, and rules in which they appear may contain meta-variables looking thus: @var{X}. The meaning of such rules should be clear from analogy with the definite clause grammars (@pxref{Definite}). @refill @item In the section describing the syntax of terms and tokens (@pxref{Term Token}) particular tokens of the category name are written thus: @var{name}, while tokens which are individual punctuation characters are written literally. @refill @end enumerate @node Sentence, Term Token, Syntax Notation, Top @comment node-name, next, previous, up @subsection Syntax of Sentences as Terms @cindex syntax of sentences @cindex sentence @example @var{sentence} --> @var{clause} | @var{directive} | @var{grammar-rule} @var{clause} --> @var{non-unit-clause} | @var{unit-clause} @var{directive} --> @var{command} | @var{query} @var{non-unit-clause} --> @var{head} @kbd{:-} @var{goals} @var{unit-clause} --> @var{head} @r{@{ where @var{head} is not otherwise a @var{sentence} @}} @var{command} --> @kbd{:-} @var{goals} @var{query} --> @kbd{?-} @var{goals} @var{head} --> term @r{@{ where term is not a @var{number} or @var{variable} @}} @var{goals} --> @var{goals} @kbd{,} @var{goals} | @var{goals} @kbd{->} @var{goals} @kbd{;} @var{goals} | @var{goals} @kbd{->} @var{goals} | @kbd{\+} @var{goals} | @var{goals} @kbd{;} @var{goals} | @var{goal} @var{goal} --> term @r{@{ where term is not a @var{number} and is not otherwise a @var{goals} @}} @var{grammar-rule} --> @var{gr-head} @kbd{-->} @var{gr-body} @var{gr-head} --> @var{non-terminal} | @var{non-terminal} @kbd{,} @var{terminals} @var{gr-body} --> @var{gr-body} @kbd{,} @var{gr-body} | @var{gr-body} @kbd{->} @var{gr-body} @kbd{;} @var{gr-body} | @var{gr-body} @kbd{->} @var{gr-body} | @kbd{\+} @var{gr-body} | @var{gr-body} @kbd{;} @var{gr-body} | @var{non-terminal} | @var{terminals} | @var{gr-condition} @var{non-terminal} --> term @r{@{ where term is not a @var{number} or @var{variable} and is not otherwise a @var{gr-body} @}} @var{terminals} --> list | string @var{gr-condition} --> @kbd{@{} @var{goals} @kbd{@}} @end example @node Term Token, Token String, Sentence, Top @comment node-name, next, previous, up @subsection Syntax of Terms as Tokens @cindex syntax of terms @example @var{term-read-in} --> @var{subterm(1200)} @var{full-stop} @var{subterm(N)} --> @var{term(M)} @r{@{ where @var{M} is less than or equal to @var{N} @}} @var{term(N)} --> @var{op(N,fx)} @var{subterm(N-1)} @r{@{ except the case @kbd{-} @var{number} @}} @r{@{ if subterm starts with a @kbd{(}, @var{op} must be followed by a @var{space} @}} | @var{op(N,fy)} @var{subterm(N)} @r{@{ if subterm starts with a @kbd{(},} @r{op must be followed by a @var{space} @}} | @var{subterm(N-1)} @var{op(N,xfx)} @var{subterm(N-1)} | @var{subterm(N-1)} @var{op(N,xfy)} @var{subterm(N)} | @var{subterm(N)} @var{op(N,yfx)} @var{subterm(N-1)} | @var{subterm(N-1)} @var{op(N,xf)} | @var{subterm(N)} @var{op(N,yf)} @var{term(1000)} --> @var{subterm(999)} @kbd{,} @var{subterm(1000)} @var{term(0)} --> @var{functor} @kbd{(} @var{arguments} @kbd{)} @r{@{ provided there is no space between} @r{the @var{functor} and the @kbd{(} @}} | @kbd{(} @var{subterm(1200)} @kbd{)} | @kbd{@{} @var{subterm(1200)} @kbd{@}} | @var{list} | @var{string} | @var{constant} | @var{variable} @var{op(N,T)} --> @var{name} @r{@{ where @var{name} has been declared as an} @r{operator of type @var{T} and precedence @var{N} @}} @var{arguments} --> @var{subterm(999)} | @var{subterm(999)} @kbd{,} @var{arguments} @var{list} --> @kbd{[]} | @kbd{[} @var{listexpr} @kbd{]} @var{listexpr} --> @var{subterm(999)} | @var{subterm(999)} @kbd{,} @var{listexpr} | @var{subterm(999)} @kbd{|} @var{subterm(999)} @var{constant} --> @var{atom} | @var{number} @var{number} --> @var{integer} | @var{float} @var{atom} --> @var{name} @var{integer} --> @var{natural-number} | @kbd{-} @var{natural-number} @var{float} --> @var{unsigned-float} | @kbd{-} @var{unsigned-float} @var{functor} --> @var{name} @end example @node Token String, Syntax Notes, Term Token, Top @comment node-name, next, previous, up @subsection Syntax of Tokens as Character Strings @cindex syntax of tokens By default, SICStus uses the ISO 8859/1 character set standard, but will alternatively support the EUC (Extended UNIX Code) standard. This is governed by the value of the environment variable @code{LC_CTYPE} (@pxref{Installation Intro}). The character categories used below are defined as follows in the two standards: @table @var @item layout-char In ISO 8859/1, these are ASCII codes 0..32 and 127..159. In EUC, these are ASCII codes 0..32 and 127. The common subset includes characters such as @key{TAB}, @key{LFD}, and @key{SPC}. @item small-letter In ISO 8859/1, these are ASCII codes 97..122, 223..246, and 248..255. In EUC, these are ASCII codes 97..122 and 128..255. The common subset are the letters @kbd{a} through @kbd{z}. @item capital-letter In ISO 8859/1, these are ASCII codes 65..90, 192..214, and 216..222. In EUC, these are ASCII codes 65..90. The common subset are the letters @kbd{A} through @kbd{Z}. @item digit In both standards, these are ASCII codes 48..57, i.e. the digits @kbd{0} through @kbd{9}. @item symbol-char In ISO 8859/1, these are ASCII codes 35, 36, 38, 42, 43, 45..47, 58, 60..64, 92, 94, 96, 126, 160..191, 215, and 247. In EUC, these are ASCII codes 35, 36, 38, 42, 43, 45..47, 58, 60..64, 92, 94, 96, and 126. The common subset is@* @kbd{+}@kbd{-}@kbd{*}@kbd{/}@kbd{\}@kbd{^}@kbd{<}@kbd{>}@kbd{=}@kbd{`}@kbd{~}@kbd{:}@kbd{.}@kbd{?}@kbd{@@}@kbd{#}@kbd{$}@kbd{&}. @item solo-char In both standards, these are ASCII codes 33 and 59 i.e. the characters @kbd{!} and @kbd{;}. @item punctuation-char In both standards, these are ASCII codes 37, 40, 41, 44, 91, 93, and 123..125, i.e. the characters @kbd{%(),[]@{|@}}. @item quote-char In both standards, these are ASCII codes 34 and 39 i.e. the characters @kbd{"} and @kbd{'}. @item underline In both standards, this is ASCII code 95 i.e. the character @kbd{_}. @end table @example @var{token} --> @var{name} | @var{natural-number} | @var{unsigned-float} | @var{variable} | @var{string} | @var{punctuation-char} | @var{space} | @var{comment} | @var{full-stop} @var{name} --> @var{quoted-name} | @var{word} | @var{symbol} | @var{solo-char} | @kbd{[} @var{?layout-char...} @kbd{]} | @kbd{@{} @var{?layout-char...} @kbd{@}} @var{quoted-name} --> @kbd{'} @var{?quoted-item...} @kbd{'} @var{quoted-item} --> @var{char} @r{@{ other than @kbd{'} @}} | @kbd{''} @var{word} --> @var{small-letter} @var{?alpha...} @var{symbol} --> @var{symbol-char...} @r{@{ except in the case of a @var{full-stop}} @r{or where the first 2 chars are @kbd{/*} @}} @var{natural-number} --> @var{digit...} | @var{base} @kbd{'} @var{alpha...} @r{@{ where each @var{alpha} must be less than the @var{base},} @r{treating a,b,... and A,B,... as 10,11,... @}} | @kbd{0} @kbd{'} @var{char} @r{@{ yielding the ASCII code for @var{char} @}} @var{base} --> @var{digit...} @r{@{ in the range [2..36] @}} @var{unsigned-float} --> @var{simple-float} | @var{simple-float} @var{exp} @var{exponent} @var{simple-float} --> @var{digit...} @kbd{.} @var{digit...} @var{exp} --> @kbd{e} | @kbd{E} @var{exponent} --> @var{digit...} | @kbd{-} @var{digit...} | @kbd{+} @var{digit...} @var{variable} --> @var{underline} @var{?alpha...} | @var{capital-letter} @var{?alpha...} @var{string} --> @kbd{"} @var{?string-item...} @kbd{"} @var{string-item} --> @var{char} @r{@{ other than @kbd{"} @}} | @kbd{""} @var{space} --> @var{layout-char...} @var{comment} --> @kbd{/*} @var{?char...} @kbd{*/} @r{@{ where @var{?char...} must not contain @kbd{*/} @}} | @kbd{%} @var{?not-end-of-line...} @var{newline} @var{not-end-of-line} --> @r{@{ any character except @var{newline} @}} @var{newline} --> @r{@{ @key{LFD} @}} @var{full-stop} --> @kbd{.} @var{layout-char} @var{char} --> @r{@{ any ASCII character, i.e. @}} @var{layout-char} | @var{alpha} | @var{symbol-char} | @var{solo-char} | @var{punctuation-char} | @var{quote-char} @var{alpha} --> @var{capital-letter} | @var{small-letter} | @var{digit} | @var{underline} @end example @node Syntax Notes, Example Intro, Token String, Top @comment node-name, next, previous, up @subsection Notes @enumerate @item The expression of precedence 1000 (i.e. belonging to syntactic category @var{term(1000)}) which is written @example @var{X},@var{Y} @end example @noindent denotes the term @code{','(@var{X},@var{Y})} in standard syntax. @item The parenthesised expression (belonging to syntactic category @var{term(0)}) @refill @example (@var{X}) @end example @noindent denotes simply the term @code{@var{X}}. @item The curly-bracketed expression (belonging to syntactic category @var{term(0)}) @refill @example @{@var{X}@} @end example @noindent denotes the term @code{@{@}(@var{X})} in standard syntax. @item Note that, for example, @code{-3} denotes a number whereas @code{-(3)} denotes a compound term which has the 1-ary functor @code{-} as its principal functor. @refill @item The character @kbd{"} within a string must be written duplicated. Similarly for the character @kbd{'} within a quoted atom. @refill @item A name token declared to be a prefix operator will be treated as an atom only if no @var{term-read-in} can be read by treating it as a prefix operator. @item A name token declared to be both an infix and a postfix operator will be treated as a postfix operator only if no @var{term-read-in} can be read by treating it as an infix operator. @end enumerate @node Example Intro, Simple List, Notes, Top @comment node-name, next, previous, up @chapter Programming Examples Some simple examples of Prolog programming are given below. They exemplify typical applications of Prolog. We are trying to convey a flavour of Prolog programming style as well, by following the simple rules: @itemize @bullet @item Base case before recursive cases. @item Input arguments before output arguments. @item Use cuts sparingly, and @emph{only} at proper places (@pxref{Cut}). A cut should be placed at the exact point that it is known that the current choice is the correct one: no sooner, no later. @item Use disjunctions sparingly, @emph{always} put parentheses around them, @emph{never} put parentheses around the individual disjuncts, @emph{never} put the @samp{;} at the end of a line. @end itemize The code herein was derived in part from shared code written by by R.A. O'Keefe. @node Simple List, Small Database, Example Intro, Top @comment node-name, next, previous, up @section Simple List Processing The goal @code{concatenate(@var{L1},@var{L2},@var{L3})} is true if list @var{L3} consists of the elements of list @var{L1} concatenated with the elements of list @var{L2}. The goal @code{member(@var{X},@var{L})} is true if @var{X} is one of the elements of list @var{L}. The goal @code{reverse(@var{L1},@var{L2})} is true if list @var{L2} consists of the elements of list @var{L1} in reverse order. @refill @example @group concatenate([], L, L). concatenate([X|L1], L2, [X|L3]) :- concatenate(L1, L2, L3). member(X, [X|_]). member(X, [_|L]) :- member(X, L). reverse(L, L1) :- reverse_concatenate(L, [], L1). reverse_concatenate([], L, L). reverse_concatenate([X|L1], L2, L3) :- reverse_concatenate(L1, [X|L2], L3). @end group @end example @node Small Database, Association Lists, Simple List, Top @comment node-name, next, previous, up @section A Small Database The goal @code{descendant(@var{X},@var{Y})} is true if @var{Y} is a descendant of @var{X}. @refill @example @group descendant(X, Y) :- offspring(X, Y). descendant(X, Z) :- offspring(X, Y), descendant(Y, Z). offspring(abraham, ishmael). offspring(abraham, isaac). offspring(isaac, esau). offspring(isaac, jacob). @end group @end example @* If for example the query @example | ?- descendant(abraham, X). @end example @noindent is executed, Prolog's backtracking results in different descendants of Abraham being returned as successive instances of the variable @var{X}, i.e. @example @group X = ishmael X = isaac X = esau X = jacob @end group @end example @node Association Lists, Derivative, Small Database, Top @comment node-name, next, previous, up @section Association list primitives These predicates implement ``association list'' primitives. They use a binary tree representation. Thus the time complexity for these predicates is @var{O(lg N)}, where @var{N} is the number of keys. These predicates also illustrate the use of @code{compare/3} (@pxref{Term Compare}) for case analysis. @refill @* The goal @code{get_assoc(@var{Key}, @var{Assoc}, @var{Value})} is true when @var{Key} is identical to one of the keys in @var{Assoc}, and @var{Value} unifies with the associated value. @refill @example @group get_assoc(Key, t(K,V,L,R), Val) :- compare(Rel, Key, K), get_assoc(Rel, Key, V, L, R, Val). get_assoc(=, _, Val, _, _, Val). get_assoc(<, Key, _, Tree, _, Val) :- get_assoc(Key, Tree, Val). get_assoc(>, Key, _, _, Tree, Val) :- get_assoc(Key, Tree, Val). @end group @end example @* The goal @w{@code{put_assoc(@var{Key}, @var{OldAssoc}, @var{Val}, @var{NewAssoc})}} is true when @var{OldAssoc} and @var{NewAssoc} define the same mapping for all keys other than @var{Key}, and @code{get_assoc(@var{Key}, @var{NewAssoc}, @var{Val})} is true. @refill @example @group put_assoc(Key, t, Val, Tree) :- !, Tree = t(Key,Val,t,t). put_assoc(Key, t(K,V,L,R), Val, New) :- compare(Rel, Key, K), put_assoc(Rel, Key, K, V, L, R, Val, New). put_assoc(=, Key, _, _, L, R, Val, t(Key,Val,L,R)). put_assoc(<, Key, K, V, L, R, Val, t(K,V,Tree,R)) :- put_assoc(Key, L, Val, Tree). put_assoc(>, Key, K, V, L, R, Val, t(K,V,L,Tree)) :- put_assoc(Key, R, Val, Tree). @end group @end example @node Derivative, Set Primitives, Association Lists, Map @comment node-name, next, previous, up @section Differentiation The goal @code{d(@var{E1}, @var{X}, @var{E2})} is true if expression @var{E2} is a possible form for the derivative of expression @var{E1} with respect to @var{X}. @refill @example @group :- mode d(+, +, -). :- op(300, xfy, **). d(X, X, D) :- atomic(X), !, D = 1. d(C, X, D) :- atomic(C), !, D = 0. d(U+V, X, DU+DV) :- d(U, X, DU), d(V, X, DV). d(U-V, X, DU-DV) :- d(U, X, DU), d(V, X, DV). d(U*V, X, DU*V+U*DV) :- d(U, X, DU), d(V, X, DV). d(U**N, X, N*U**N1*DU) :- integer(N), N1 is N-1, d(U, X, DU). d(-U, X, -DU) :- d(U, X, DU). @end group @end example @node Set Primitives, Use Of Meta, Derivative, Top @comment node-name, next, previous, up @section Representing sets as ordered lists without duplicates The goal @code{list_to_ord_set(@var{List}, @var{Set})} is true when @var{Set} is the ordered representation of the set represented by the unordered representation @var{List}. The only reason for giving it a name at all is that you may not have realised that @code{sort/2} (@pxref{Term Compare}) could be used this way. @refill @example @group list_to_ord_set(List, Set) :- sort(List, Set). @end group @end example @* The goal @code{ord_union(@var{Set1}, @var{Set2}, @var{Union})} is true when @var{Union} is the union of @var{Set1} and @var{Set2}. Note that when something occurs in both sets, we want to retain only one copy. @refill @example @group ord_union(Set1, [], Set) :- !, Set = Set1. ord_union([], Set2, Set) :- !, Set = Set2. ord_union([Head1|Tail1], [Head2|Tail2], Union) :- compare(Order, Head1, Head2), ord_union(Order, Head1, Tail1, Head2, Tail2, Union). ord_union(=, Head, Tail1, _, Tail2, [Head|Union]) :- ord_union(Tail1, Tail2, Union). ord_union(<, Head1, Tail1, Head2, Tail2, [Head1|Union]) :- ord_union(Tail1, [Head2|Tail2], Union). ord_union(>, Head1, Tail1, Head2, Tail2, [Head2|Union]) :- ord_union([Head1|Tail1], Tail2, Union). @end group @end example @* The goal @code{ord_intersect(@var{Set1}, @var{Set2}, @var{Intersection})} is true when @var{Intersection} is the ordered representation of @var{Set1} and @var{Set2}. @example @group ord_intersect(_, [], Set) :- !, Set = []. ord_intersect([], _, Set) :- !, Set = []. ord_intersect([Head1|Tail1], [Head2|Tail2], Intersection) :- compare(Order, Head1, Head2), ord_intersect(Order, Head1, Tail1, Head2, Tail2, Intersection). ord_intersect(=, Head, Tail1, _, Tail2, [Head|Intersection]) :- ord_intersect(Tail1, Tail2, Intersection). ord_intersect(<, _, Tail1, Head2, Tail2, Intersection) :- ord_intersect(Tail1, [Head2|Tail2], Intersection). ord_intersect(>, Head1, Tail1, _, Tail2, Intersection) :- ord_intersect([Head1|Tail1], Tail2, Intersection). @end group @end example @node Use Of Meta, Interpreter, Set Primitives, Top @comment node-name, next, previous, up @section Use of Meta-Predicates This example illustrates the use of the meta-predicates @code{var/1}, @code{arg/3}, and @code{functor/3} (@pxref{Meta Logic}). The procedure call @code{variables(@var{Term}, @var{L}, [])} instantiates variable @var{L} to a list of all the variable occurrences in the term @var{Term}. e.g. @refill @example ?- variables(d(U*V, X, DU*V+U*DV), L, []). L = [U,V,X,DU,V,U,DV] @end example @* @example @group variables(X, [X|L0], L) :- var(X), !, L = L0. variables(T, L0, L) :- functor(T, _, A), variables(0, A, T, L0, L). variables(A, A, _, L0, L) :- !, L = L0. variables(A0, A, T, L0, L) :- % A0<A, A1 is A0+1, arg(A1, T, X), variables(X, L0, L1), variables(A1, A, T, L1, L). @end group @end example @node Interpreter, Translate, Use Of Meta, Top @comment node-name, next, previous, up @section Prolog in Prolog This example shows how simple it is to write a Prolog interpreter in Prolog, and illustrates the use of a variable goal. In this mini-interpreter, goals and clauses are represented as ordinary Prolog data structures (i.e. terms). Terms representing clauses are specified using the predicate @code{my_clause/1}, e.g. @example my_clause( (grandparent(X, Z) :- parent(X, Y), parent(Y, Z)) ). @end example A unit clause will be represented by a term such as @example my_clause( (parent(john, mary) :- true) ). @end example @* The mini-interpreter consists of three clauses: @example @group execute((P,Q)) :- !, execute(P), execute(Q). execute(P) :- predicate_property(P, built_in), !, P. execute(P) :- my_clause((P :- Q)), execute(Q). @end group @end example The second clause enables the mini-interpreter to cope with calls to ordinary Prolog predicates, e.g. built-in predicates. The mini-interpreter needs to be extended to cope with the other control structures, i.e. @code{!}, @code{(P;Q)}, @code{(P->Q)}, @code{(P->Q;R)}, @code{(\+ P)}, and @code{if(P,Q,R)}. @refill @node Translate, Installation Intro, Interpreter, Top @comment node-name, next, previous, up @section Translating English Sentences into Logic Formulae The following example of a definite clause grammar defines in a formal way the traditional mapping of simple English sentences into formulae of classical logic. By way of illustration, if the sentence @quotation Every man that lives loves a woman. @end quotation @noindent is parsed as a sentence by the call @example | ?- phrase(sentence(@var{P}), [every,man,that,lives,loves,a,woman]). @end example @noindent then @var{P} will get instantiated to @example all(X):(man(X)&lives(X) => exists(Y):(woman(Y)&loves(X,Y))) @end example @noindent where @code{:}, @code{&} and @code{=>} are infix operators defined by @example :- op(900, xfx, =>). :- op(800, xfy, &). :- op(300, xfx, :). @end example @* The grammar follows: @example @group sentence(P) --> noun_phrase(X, P1, P), verb_phrase(X, P1). noun_phrase(X, P1, P) --> determiner(X, P2, P1, P), noun(X, P3), rel_clause(X, P3, P2). noun_phrase(X, P, P) --> name(X). verb_phrase(X, P) --> trans_verb(X, Y, P1), noun_phrase(Y, P1, P). verb_phrase(X, P) --> intrans_verb(X, P). rel_clause(X, P1, P1&P2) --> [that], verb_phrase(X, P2). rel_clause(_, P, P) --> []. determiner(X, P1, P2, all(X):(P1=>P2) ) --> [every]. determiner(X, P1, P2, exists(X):(P1&P2) ) --> [a]. noun(X, man(X) ) --> [man]. noun(X, woman(X) ) --> [woman]. name(john) --> [john]. trans_verb(X, Y, loves(X,Y) ) --> [loves]. intrans_verb(X, lives(X) ) --> [lives]. @end group @end example @node Installation Intro, Pred Summary, Translate, Top @comment node-name, next, previous, up @chapter Installation Dependencies To start SICStus issue the shell command: @example % prolog [-f] [-i] @var{arguments} @end example @noindent where the @var{arguments} can be retrieved from SICStus by @code{unix(argv(@var{?Args}))}, which will unify @var{Args} with @var{arguments} represented as a list of atoms. None of the @var{arguments} must begin with a @samp{-} sign. @refill The flags have the following meaning: @table @code @item -f Fast start. Don't read the @file{~/.sicstusrc} file on startup and on @code{reinitialise/1}. If the flag is omitted, SICStus will consult this file on startup and on @code{reinitialise/1}, if it exists. @item -i Forced interactive. Prompt for user input, even if the standard input does not appear to be a terminal. @end table To start SICStus from a saved state @var{file}, issue the shell command: @example % @var{file} [-f] [-i] @var{arguments} @end example @noindent or the shell command: @example % prolog -r @var{file} [-f] [-i] @var{arguments} @end example Assuming the GNU Emacs mode for SICStus has been installed, inserting the following lines in your @file{~/.emacs} will make Emacs use this mode automatically when editing files with a @samp{.pl} extension: @refill @example (setq load-path (cons "/usr/local/lib/sicstus0.7" load-path)) (autoload 'run-prolog "prolog" "Start a Prolog sub-process." t) (autoload 'prolog-mode "prolog" "Major mode for editing prolog programs" t) @end example @noindent where @file{/usr/local/lib/sicstus0.7} should be replaced by the name of the SICStus source code directory. The Emacs mode will use the value of the environment variable @code{EPROLOG} as a shell command to invoke SICStus. This value defaults to @code{prolog}. The Emacs mode provides the following commands: @table @kbd @item M-x run-prolog Run an inferior Prolog process, input and output via the buffer @code{*prolog*}. @item C-c K The entire buffer is compiled. @item C-c k The current region is compiled. @item C-c C-k The predicate around point is compiled. Empty lines are treated as predicate boundaries. @item C-c C The entire buffer is consulted. @item C-c c The current region is consulted. @item C-c C-c The predicate around point is consulted. Empty lines are treated as predicate boundaries. @end table The following environment variable can be set before starting SICStus. Some of these override the default sizes of certain areas. The sizes are given in cells: @table @code @item LC_CTYPE This selects the appropriate character set standard: The supported values are @code{ja_JP.EUC} (for EUC) and @code{iso_8859_1} (for ISO 8859/1). The latter is the default. In fact, any value other than @code{ja_JP.EUC} will cause ISO 8859/1 to be selected. @item TMPDIR If set, indicates the pathname where temporary files should be created. Defaults to @file{/usr/tmp}. @item GLOBALSTKSIZE Governs the initial size of the global stack. @item LOCALSTKSIZE Governs the initial size of the local stack. @item CHOICESTKSIZE Governs the initial size of the choicepoint stack. @item TRAILSTKSIZE Governs the initial size of the trail stack. @end table @node Pred Summary, Standard Operators, Installation Intro, Top @comment node-name, next, previous, up @chapter Summary of Built-In Predicates @table @code @item ! Commit to any choices taken in the current predicate. @item (@var{+P},@var{+Q}) @var{P} and @var{Q}. @item (@var{+P} -> @var{+Q} ; @var{+R}) If @var{P} then @var{Q} else @var{R}, using first solution of @var{P} only. @item (@var{+P} -> @var{+Q}) If @var{P} then @var{Q} else fail, using first solution of @var{P} only. @item [] @itemx [@var{+File}|@var{+Files}] Update the program with interpreted clauses from @var{File} and @var{Files}. @item (@var{+P};@var{+Q}) @var{P} or @var{Q}. @item @var{?X} = @var{?Y} The terms @var{X} and @var{Y} are unified. @item @var{?Term} =.@. @var{?List} The functor and arguments of the term @var{Term} comprise the list @var{List}. @item @var{+X} =:= @var{+Y} @var{X} is numerically equal to @var{Y}. @item @var{?Term1} == @var{?Term2} The terms @var{Term1} and @var{Term2} are strictly identical. @item @var{+X} =\= @var{+Y} @var{X} is not numerically equal to @var{Y}. @item @var{+X} =< @var{+Y} @var{X} is less than or equal to @var{Y}. @item @var{+X} > @var{+Y} @var{X} is greater than @var{Y}. @item @var{+X} >= @var{+Y} @var{X} is greater than or equal to @var{Y}. @item @var{?X} ^ @var{+P} Execute the procedure call @var{P}. @item \+ @var{+P} Goal @var{P} is not provable. @item @var{?Term1} \== @var{?Term2} The terms @var{Term1} and @var{Term2} are not strictly identical. @item @var{+X} < @var{+Y} @var{X} is less than @var{Y}. @item @var{?Term1} @@=< @var{?Term2} The term @var{Term1} precedes or is identical to the term @var{Term2} in the standard order. @item @var{?Term1} @@> @var{?Term2} The term @var{Term1} follows the term @var{Term2} in the standard order. @item @var{?Term1} @@>= @var{?Term2} The term @var{Term1} follows or is identical to the term @var{Term2} in the standard order. @item @var{?Term1} @@< @var{?Term2} The term @var{Term1} precedes the term @var{Term2} in the standard order. @item abolish(@var{+Preds}) Make the predicate(s) specified by @var{Preds} undefined. @item abolish(@var{+Atom},@var{+Arity}) Make the predicate specified by @code{@var{Atom}/@var{Arity}} undefined. @item abort Abort execution of the current directive. @item absolute_file_name(@var{+RelativeName},@var{?AbsoluteName}) @var{AbsoluteName} is the full pathname of @var{RelativeName}. @item ancestors(@var{?Goals}) The ancestor list of the current clause is @var{Goals}. @item arg(@var{+ArgNo},@var{+Term},@var{?Arg}) Argument @var{ArgNo} of the term @var{Term} is @var{Arg}. @item assert(@var{+Clause}) @itemx assert(@var{+Clause},@var{-Ref}) Assert clause @var{Clause} with unique identifier @var{Ref}. @item asserta(@var{+Clause}) @itemx asserta(@var{+Clause},@var{-Ref}) Assert @var{Clause} as first clause with unique identifier @var{Ref}. @item assertz(@var{+Clause}) @itemx assertz(@var{+Clause},@var{-Ref}) Assert @var{Clause} as last clause with unique identifier @var{Ref}. @item atom(@var{?X}) @var{X} is currently instantiated to an atom. @item atom_chars(@var{?Atom},@var{?CharList}) The name of the atom @var{Atom} is the list of characters @var{CharList}. @item atomic(@var{?X}) @var{X} is currently instantiated to an atom or a number. @item bagof(@var{?Template},@var{+Goal},@var{?Bag}) @var{Bag} is the bag of instances of @var{Template} such that @var{Goal} is satisfied (not just provable). @item break Invoke the Prolog interpreter. @item 'C'(@var{?S1},@var{?Terminal},@var{?S2}) @emph{Grammar rules.} @var{S1} is connected by the terminal @var{Terminal} to @var{S2}. @item call(@var{+Term}) Execute the procedure call @var{Term}. @item call_residue(@var{+Term},@var{?Vars}) @emph{SICStus specific.} Execute the procedure call @var{Term}. Any remaining subgoals are blocked on the variables in @var{Vars}. @item character_count(@var{?Stream},@var{?Count}) @var{Count} characters have been read from or written to the stream @var{Stream}. @item clause(@var{+Head},@var{?Body}) @itemx clause(@var{?Head},@var{?Body},@var{?Ref}) There is an interpreted clause whose head is @var{Head}, whose body is @var{Body}, and whose unique identifier is @var{Ref}. @item close(@var{+Stream}) Close stream @var{Stream}. @item compare(@var{?Op},@var{?Term1},@var{?Term2}) @var{Op} is the result of comparing the terms @var{Term1} and @var{Term2}. @item compile(@var{+File}) Compile in-core the clauses in text file(s) @var{File}. @item consult(@var{+File}) Update the program with interpreted clauses from file(s) @var{File}. @item copy_term(@var{?Term},@var{?CopyOfTerm}) @var{CopyOfTerm} is an independent copy of @var{Term}. @item current_atom(@var{?Atom}) One of the currently defined atoms is @var{Atom}. @item current_input(@var{?Stream}) @var{Stream} is the current input stream. @item current_key(@var{?KeyName},@var{?KeyTerm}) There is a recorded item in the internal database whose key is @var{KeyTerm}, the name of which is @var{KeyName}. @item current_op(@var{?Precedence},@var{?Type},@var{?Op}) Atom @var{Op} is an operator type @var{Type} precedence @var{Precedence}. @item current_output(@var{?Stream}) @var{Stream} is the current output stream. @item current_predicate(@var{?Name},@var{?Head}) A user defined predicate is named @var{Name}, most general goal @var{Head}. @item current_stream(@var{?FileName},@var{?Mode},@var{?Stream}) There is a stream @var{Stream} associated with the file @var{FileName} and opened in mode @var{Mode}. @item debug Switch on debugging. @item debugging Display debugging status information. @item depth(@var{?Depth}) The current invocation depth is @var{Depth}. @item dif(@var{?X},@var{?Y}) @emph{SICStus specific.} The terms @var{X} and @var{Y} are different. @item display(@var{?Term}) Display the term @var{Term} on the standard output stream. @item ensure_loaded(@var{File}) Compile or load the file(s) @var{File} if need be. @item erase(@var{+Ref}) Erase the clause or record whose unique identifier is @var{Ref}. @item expand_term(@var{+Term1},@var{?Term2}) The term @var{Term1} is a shorthand which expands to the term @var{Term2}. @item fail @itemx false Backtrack immediately. @item fcompile(@var{+File}) @emph{SICStus specific.} Compile file-to-file the clauses in text file(s) @var{File}. @item fileerrors Enable reporting of file errors. @item findall(@var{?Template},@var{+Goal},@var{?Bag}) @emph{SICStus specific.} @var{Bag} is the bag of instances of @var{Template} such that @var{Goal} is provable (not satisfied). @item float(@var{?X}) @var{X} is currently instantiated to a float. @item flush_output(@var{+Stream}) Flush the buffers associated with @var{Stream}. @item foreign(@var{+CFunctionName}, @var{+Predicate}) @itemx foreign(@var{+CFunctionName}, @var{+Language}, @var{+Predicate}) @emph{User defined}, they tell Prolog how to define @var{Predicate} to invoke @var{CFunctionName}. @item foreign_file(@var{+ObjectFile},@var{+Functions}) @emph{User defined}, tells Prolog that foreign functions @var{Functions} are in file @var{ObjectFile}. @item format(@var{+Format},@var{+Arguments}) @itemx format(@var{+Stream},@var{+Format},@var{+Arguments}) Write @var{Arguments} according to @var{Format} on the stream @var{Stream} or on the current output stream. @item freeze(@var{+Goal}) @emph{SICStus specific.} Block @var{Goal} until @var{Goal} is ground. @item freeze(@var{?Var},@var{+Goal}) @emph{SICStus specific.} Block @var{Goal} until @code{nonvar(@var{Var})} holds. @item frozen(@var{-Var},@var{?Goal}) @emph{SICStus specific.} The goal @var{Goal} is blocked on the variable @var{Var}. @item functor(@var{?Term},@var{?Name},@var{?Arity}) The principal functor of the term @var{Term} has name @var{Name} and arity @var{Arity}. @item garbage_collect Perform a garbage collection. @item gc Enable garbage collection. @item get(@var{?C}) @itemx get(@var{+Stream},@var{?C}) The next printing character from the stream @var{Stream} or from the current input stream is @var{C}. @item get0(@var{?C}) @itemx get0(@var{+Stream},@var{?C}) The next character from the stream @var{Stream} or from the current input stream is @var{C}. @item halt Halt Prolog, exit to the invoking shell. @item help Print a help message. @item if(@var{+P},@var{+Q},@var{+R}) @emph{SICStus specific.} If @var{P} then @var{Q} else @var{R}, exploring all solutions of @var{P}. @item incore(@var{+Term}) Execute the procedure call @var{Term}. @item instance(@var{+Ref},@var{?Term}) @var{Term} is a most general instance of the record or clause uniquely identified by @var{Ref}. @item integer(@var{?X}) @var{X} is currently instantiated to an integer. @item @var{Y} is @var{X} @var{Y} is the value of the arithmetic expression @var{X}. @item keysort(@var{+List1},@var{?List2}) The list @var{List1} sorted by key yields @var{List2}. @item leash(@var{+Mode}) Set leashing mode to @var{Mode}. @item length(@var{?List},@var{?Length}) The length of list @var{List} is @var{Length}. @item library_directory(@var{?Directory}) @emph{User defined}, @var{Directory} is a directory in the search path. @item line_count(@var{?Stream},@var{?Count}) @var{Count} lines have been read from or written to the stream @var{Stream}. @item line_position(@var{?Stream},@var{?Count}) @var{Count} characters have been read from or written to the current line of the stream @var{Stream}. @item listing @itemx listing(@var{+Preds}) List the interpreted predicate(s) specified by @var{Preds} or all interpreted predicates. @item load(@var{+File}) @emph{SICStus specific.} Load compiled object file(s) @var{File} into Prolog. @item load_foreign_files(@var{+ObjectFiles},@var{+Libraries}) Load (link) files @var{ObjectFiles} into Prolog. @item maxdepth(@var{+Depth}) Limit invocation depth to @var{Depth}. @item name(@var{?Const},@var{?CharList}) The name of atom or number @var{Const} is string @var{CharList}. @item nl @itemx nl(@var{+Stream}) Output a new line on stream @var{Stream} or on the current output stream. @item nodebug Switch off debugging. @item nofileerrors Disable reporting of file errors. @item nogc Disable garbage collection. @item nonvar(@var{?X}) @var{X} is a non-variable. @item nospy @var{+Spec} Remove spy-points from the predicate(s) specified by @var{Spec}. @item nospyall Remove all spy-points. @item notrace Switch off debugging. @item number(@var{?X}) @var{X} is currently instantiated to a number. @item number_chars(@var{?Number},@var{?CharList}) The name of the number @var{Number} is the list of characters @var{CharList}. @item numbervars(@var{?Term},@var{+N},@var{?M}) Number the variables in the term @var{Term} from @var{N} to @var{M}-1. @item op(@var{+Precedence},@var{+Type},@var{+Name}) Make atom(s) @var{Name} an operator of type @var{Type} precedence @var{Precedence}. @item open(@var{+FileName},@var{+Mode},@var{-Stream}) Open file @var{FileName} in mode @var{Mode} as stream @var{Stream}. @item open_null_stream(@var{-Stream}) Open an output stream to the null device. @item otherwise Succeed. @item phrase(@var{+Phrase},@var{?List}) @itemx phrase(@var{+Phrase},@var{?List},@var{?Remainder}) @emph{Grammar rules.} The list @var{List} can be parsed as a phrase of type @var{Phrase}. The rest of the list is @var{Remainder} or empty. @item plsys(@var{+Term}) Invoke operating system services. @item portray(@var{+Term}) @emph{User defined}, tells @code{print/1} what to do. @item portray_clause(@var{+Clause}) @itemx portray_clause(@var{+Stream},@var{+Clause}) Pretty print @var{Clause} on the stream @var{Stream} or on the current output stream. @item predicate_property(@var{?Head},@var{?Prop}) @var{Head} is the most general goal of a currently defined predicate that has the property @var{Prop}. @item prepare_foreign_files(@var{+ObjectFiles}) @emph{SICStus specific.} Generate relevant interface code in @file{flinkage.c} for foreign declarations for the files in @var{ObjectFiles}. @item print(@var{?Term}) @itemx print(@var{+Stream},@var{?Term}) Portray or else write the term @var{Term} on the stream @var{Stream} or on the current output stream. @item profile_data(@var{+Files},@var{?Selection},@var{?Resolution},@var{-Data}) @var{Data} is the profiling data collected from the instrumented predicates defined in the files @var{Files} with selection and resolution @var{Selection} and @var{Resolution} respectively. @item profile_reset(@var{+Files}) The profiling counters for the instrumented predicates in @var{Files} are zeroed. @item prolog_flag(@var{+FlagName},@var{?Value}) @var{Value} is the current value of @var{FlagName}. @item prolog_flag(@var{+FlagName},@var{?OldValue},@var{?NewValue}) @var{OldValue} and @var{NewValue} are the old and new values of @var{FlagName}. @item prompt(@var{?Old},@var{?New}) Change the prompt from @var{Old} to @var{New}. @item put(@var{+C}) @itemx put(@var{+Stream},@var{+C}) The next character sent to the stream @var{Stream} or to the current output stream is @var{C}. @item query_expansion(@var{+RawQuery},@var{?Query}) @emph{SICStus specific, user defined}, transforms the interpreter top-level query @var{RawQuery} into @var{Query} to be executed. @item read(@var{?Term}) @itemx read(@var{+Stream},@var{?Term}) Read the term @var{Term} from the stream @var{Stream} or from the current input stream. @item reconsult(@var{+File}) Update the program with interpreted clauses from file(s) @var{File}. @item recorda(@var{+Key},@var{?Term},@var{-Ref}) Make the term @var{Term} the first record under key @var{Key} with unique identifier @var{Ref}. @item recorded(@var{?Key},@var{?Term},@var{?Ref}) The term @var{Term} is currently recorded under key @var{Key} with unique identifier @var{Ref}. @item recordz(@var{+Key},@var{?Term},@var{-Ref}) Make the term @var{Term} the last record under key @var{Key} with unique identifier @var{Ref}. @item reinitialise Initialise Prolog, reconsulting @file{~/.sicstusrc} if it exists. @item repeat Succeed repeatedly. @item restore(@var{+File}) Restore the state saved in file @var{File}. @item retract(@var{+Clause}) Erase repeatedly the next interpreted clause of form @var{Clause}. @item retractall(@var{+Head}) Erase all clauses whose head matches @var{Head}. @item save(@var{+File}) @itemx save(@var{+File},@var{?Return}) Save the current state of Prolog in file @var{File}; @var{Return} is 0 after a save and 1 after a restore. @item save_program(@var{+File}) Save the current state of the Prolog data base in file @var{File}. @item see(@var{+File}) Make file @var{File} the current input stream. @item seeing(@var{?File}) The current input stream is named @var{File}. @item seen Close the current input stream. @item set_input(@var{+Stream}) Set the current input stream to @var{Stream}. @item set_output(@var{+Stream}) Set the current output stream to @var{Stream}. @item setarg(@var{+ArgNo},@var{+CompoundTerm},@var{?NewArg}) @emph{SICStus specific.} Replace destructively argument @var{ArgNo} in @var{CompoundTerm} with @var{NewArg} and undo on backtracking. @item setof(@var{?Template},@var{+Goal},@var{?Set}) @var{Set} is the set of instances of @var{Template} such that @var{Goal} is satisfied (not just provable). @item skip(@var{+C}) @itemx skip(@var{+Stream},@var{+C}) Skip characters from @var{Stream} or from the current input stream until after character @var{C}. @item sort(@var{+List1},@var{List2}) The list @var{List1} sorted into order yields @var{List2}. @item source_file(@var{?File}) @itemx source_file(@var{?Pred},@var{?File}) The predicate @var{Pred} is defined in the file @var{File}. @item spy @var{+Spec} Set spy-points on the predicate(s) specified by @var{Spec}. @item statistics Output various execution statistics. @item statistics(@var{?Key},@var{?Value}) The execution statistic key @var{Key} has value @var{Value}. @item stream_code(@var{?Stream},@var{?StreamCode}) @var{StreamCode} is a foreign language (C) version of @var{Stream}. @item subgoal_of(@var{?Goal}) An ancestor goal of the current clause is @var{Goal}. @item tab(@var{+N}) @itemx tab(@var{+Stream},@var{+N}) Send @var{N} spaces to the stream @var{Stream} or to the current output stream. @item tell(@var{+File}) Make file @var{File} the current output stream. @item telling(@var{?File}) The current output stream is named @var{File}. @item term_expansion(@var{+Term1},@var{?Term2}) @emph{User defined}, tells @code{expand_term/2} what to do. @item told Close the current output stream. @item trace Switch on debugging and start tracing immediately. @item true Succeed. @item ttyflush Flush the standard output stream buffer. @item ttyget(@var{?C}) The next printing character input from the standard input stream is @var{C}. @item ttyget0(@var{?C}) The next character input from the standard input stream is @var{C}. @item ttynl Output a new line on the standard output stream. @item ttyput(@var{+C}) The next character output to the standard output stream is @var{C}. @item ttyskip(@var{+C}) Skip characters from the standard input stream until after character @var{C}. @item ttytab(@var{+N}) Output @var{N} spaces to the standard output stream. @item undo(@var{+Term}) @emph{SICStus specific.} The goal @code{call(@var{Term})} is executed on backtracking. @item unix(@var{+Term}) Invoke operating system services. @item unknown(@var{?OldState},@var{?NewState}) Change action on undefined predicates from @var{OldState} to @var{NewState}. @item user_help @emph{User defined}, tells @code{help/0} what to do. @item var(@var{X}) @var{X} is currently uninstantiated. @item version Displays introductory and/or system identification messages. @item version(@var{+Message}) Adds the atom @var{Message} to the list of introductory messages. @item write(@var{?Term}) @itemx write(@var{+Stream},@var{?Term}) Write the term @var{Term} on the stream @var{Stream} or on the current output stream. @item write_canonical(@var{?Term}) @itemx write_canonical(@var{+Stream},@var{?Term}) Write @var{Term} on the stream @var{Stream} or on the current output stream so that it may be read back. @item writeq(@var{?Term}) @itemx writeq(@var{+Stream},@var{?Term}) Write the term @var{Term} on the stream @var{Stream} or on the current output stream, quoting names where necessary. @end table @node Standard Operators, Predicate Index, Pred Summary, Top @comment node-name, next, previous, up @chapter Standard Operators @example :- op( 1200, xfx, [ :-, --> ]). :- op( 1200, fx, [ :-, ?- ]). :- op( 1150, fx, [ mode, public, dynamic, multifile, wait ]). :- op( 1100, xfy, [ ; ]). :- op( 1050, xfy, [ -> ]). :- op( 1000, xfy, [ ',' ]). /* See note below */ :- op( 900, fy, [ \+, spy, nospy ]). :- op( 700, xfx, [ =, is, =.., ==, \==, @@<, @@>, @@=<, @@>=, =:=, =\=, <, >, =<, >= ]). :- op( 500, yfx, [ +, -, /\, \/ ]). :- op( 500, fx, [ +, - ]). :- op( 400, yfx, [ *, /, //, <<, >> ]). :- op( 300, xfx, [ mod ]). :- op( 200, xfy, [ ^ ]). @end example Note that a comma written literally as a punctuation character can be used as though it were an infix operator of precedence 1000 and type @code{xfy}, i.e. @refill @example X,Y ','(X,Y) @end example @noindent represent the same compound term. @node Predicate Index, Concept Index, Standard Operators, Top @comment node-name, next, previous, up @unnumbered Predicate Index @printindex fn @node Concept Index, Intro, Predicate Index, Top @comment node-name, next, previous, up @unnumbered Concept Index @printindex cp @contents @bye