This repository has been archived on 2023-08-20. You can view files and clone it, but cannot push or open issues or pull requests.
yap-6.3/docs/yapdocs.md

385 KiB
Raw Blame History

/**

@defgroup YAPControl Control Predicates @ingroup YAPBuiltins @{

*/

/** @pred true is iso

Succeeds once.

*/

/** @pred fail is iso

Always fails.

*/

/** @pred false is iso

The same as fail.

*/

/** @pred repeat is iso bprolqSucceeds repeatedly.

In the next example, repeat is used as an efficient way to implement a loop. The next example reads all terms in a file:

 a :- repeat, read(X), write(X), nl, X=end_of_file, !.

the loop is effectively terminated by the cut-goal, when the test-goal X=end succeeds. While the test fails, the goals read(X), write(X), and nl are executed repeatedly, because backtracking is caught by the repeat goal.

The built-in repeat/0 could be defined in Prolog by:

 repeat.
 repeat :- repeat.

The predicate between/3 can be used to iterate for a pre-defined number of steps.

*/

/** @pred call(+ P) is iso Meta-call predicate.

If P is instantiated to an atom or a compound term, the goal call( _P_) is executed as if the clause was originally written as P instead as call( P ), except that any "cut" occurring in P only cuts alternatives in the execution of P.

*/

/** @pred incore(+ P)

The same as call/1.

*/

/** @pred call(+ Closure,...,? Ai,...) is iso

Meta-call where Closure is a closure that is converted into a goal by appending the Ai additional arguments. The number of arguments varies between 0 and 10.

*/

/** @pred call_with_args(+ Name,...,? Ai,...)

Meta-call where Name is the name of the procedure to be called and the Ai are the arguments. The number of arguments varies between 0 and 10. New code should use call/N for better portability.

If Name is a complex term, then call_with_args/n behaves as call/n:

call(p(X1,...,Xm), Y1,...,Yn) :- p(X1,...,Xm,Y1,...,Yn).

*/

/** @pred + P

The same as call( _P_). This feature has been kept to provide compatibility with C-Prolog. When compiling a goal, YAP generates a call( _X_) whenever a variable X is found as a goal.

 a(X) :- X.

is converted to:

 a(X) :- call(X).

*/

/** @pred if(? G,? H,? I)

Call goal H once per each solution of goal H. If goal H has no solutions, call goal I.

The built-in if/3 is similar to -\>/3, with the difference that it will backtrack over the test goal. Consider the following small data-base:

a(1).        b(a).          c(x).
a(2).        b(b).          c(y).

Execution of an if/3 query will proceed as follows:

   ?- if(a(X),b(Y),c(Z)).

X = 1,
Y = a ? ;

X = 1,
Y = b ? ;

X = 2,
Y = a ? ;

X = 2,
Y = b ? ;

no

The system will backtrack over the two solutions for a/1 and the two solutions for b/1, generating four solutions.

Cuts are allowed inside the first goal G, but they will only prune over G.

If you want G to be deterministic you should use if-then-else, as it is both more efficient and more portable.

*/

/** @pred once(: G) is iso

Execute the goal G only once. The predicate is defined by:

 once(G) :- call(G), !.

Note that cuts inside once/1 can only cut the other goals inside once/1.

*/

/** @pred forall(: Cond,: Action)

For all alternative bindings of Cond Action can be proven. The example verifies that all arithmetic statements in the list L are correct. It does not say which is wrong if one proves wrong.

?- forall(member(Result = Formula, [2 = 1 + 1, 4 = 2 * 2]),
                 Result =:= Formula).

*/

/** @pred ignore(: Goal)

Calls Goal as once/1, but succeeds, regardless of whether Goal succeeded or not. Defined as:

ignore(Goal) :-
        Goal, !.
ignore(_).

*/

/** @pred abort

Abandons the execution of the current goal and returns to top level. All break levels (see break/0 below) are terminated. It is mainly used during debugging or after a serious execution error, to return to the top-level.

*/

/** @pred break

Suspends the execution of the current goal and creates a new execution level similar to the top level, displaying the following message:

 [ Break (level <number>) ]

telling the depth of the break level just entered. To return to the previous level just type the end-of-file character or call the end_of_file predicate. This predicate is especially useful during debugging.

*/

/** @pred halt is iso

Halts Prolog, and exits to the calling application. In YAP, halt/0 returns the exit code 0.

*/

/** @pred halt(+ I) is iso

Halts Prolog, and exits to the calling application returning the code given by the integer I.

*/

/** @pred catch( : Goal,+ Exception,+ Action) is iso

The goal catch( _Goal_, _Exception_, _Action_) tries to execute goal Goal. If during its execution, Goal throws an exception E' and this exception unifies with Exception, the exception is considered to be caught and Action is executed. If the exception E' does not unify with Exception, control again throws the exception.

The top-level of YAP maintains a default exception handler that is responsible to capture uncaught exceptions.

*/

/** @pred throw(+ Ball) is iso

The goal throw( _Ball_) throws an exception. Execution is stopped, and the exception is sent to the ancestor goals until reaching a matching catch/3, or until reaching top-level.

*/

/** @pred garbage_collect

The goal garbage_collect forces a garbage collection.

*/

/** @pred garbage_collect_atoms

The goal garbage_collect forces a garbage collection of the atoms in the data-base. Currently, only atoms are recovered.

*/

/** @pred gc

The goal gc enables garbage collection. The same as yap_flag(gc,on).

*/

/** @pred nogc

The goal nogc disables garbage collection. The same as yap_flag(gc,off).

*/

/** @pred grow_heap(+ Size) Increase heap size Size kilobytes.

*/

/** @pred grow_stack(+ Size)

Increase stack size Size kilobytes

@} */

/** @defgroup Undefined_Procedures Handling Undefined Procedures @ingroup YAPBuiltins @{

A predicate in a module is said to be undefined if there are no clauses defining the predicate, and if the predicate has not been declared to be dynamic. What YAP does when trying to execute undefined predicates can be specified in three different ways:

+ By setting an YAP flag, through the yap_flag/2 or

set_prolog_flag/2 built-ins. This solution generalizes the ISO standard. + By using the unknown/2 built-in (this solution is compatible with previous releases of YAP). + By defining clauses for the hook predicate user:unknown_predicate_handler/3. This solution is compatible with SICStus Prolog.

In more detail:

*/

/** @pred unknown(- O,+ N)

Specifies an handler to be called is a program tries to call an undefined static procedure P.

The arity of N may be zero or one. If the arity is 0, the new action must be one of fail, warning, or error. If the arity is 1, P is an user-defined handler and at run-time, the argument to the handler P will be unified with the undefined goal. Note that N must be defined prior to calling unknown/2, and that the single argument to N must be unbound.

In YAP, the default action is to fail (note that in the ISO Prolog standard the default action is error).

After defining undefined/1 by:

undefined(A) :- format('Undefined predicate: ~w~n',[A]), fail.

and executing the goal:

unknown(U,undefined(X)).

a call to a predicate for which no clauses were defined will result in the output of a message of the form:

Undefined predicate: user:xyz(A1,A2)

followed by the failure of that call.

*/

/** @pred yap_flag(unknown,+ SPEC)

Alternatively, one can use yap_flag/2, current_prolog_flag/2, or set_prolog_flag/2, to set this functionality. In this case, the first argument for the built-ins should be unknown, and the second argument should be either error, warning, fail, or a goal.

*/

/** @pred user:unknown_predicate_handler(+G,+M,?NG)

The user may also define clauses for user:unknown_predicate_handler/3 hook predicate. This user-defined procedure is called before any system processing for the undefined procedure, with the first argument G set to the current goal, and the second M set to the current module. The predicate G will be called from within the user module.

If user:unknown_predicate_handler/3 succeeds, the system will execute NG. If user:unknown_predicate_handler/3 fails, the system will execute default action as specified by unknown/2.

*/

/** @pred exception(+ Exception, + Context, - Action)

Dynamic predicate, normally not defined. Called by the Prolog system on run-time exceptions that can be repaired just-in-time'. The values for _Exception_ are described below. See also catch/3 and throw/1. If this hook predicate succeeds it must instantiate the _Action_ argument to the atom failto make the operation fail silently,retryto tell Prolog to retry the operation orerrorto make the system generate an exception. The actionretry` only makes sense if this hook modified the environment such that the operation can now succeed without error.

+ undefined_predicate

Context is instantiated to a predicate-indicator ( Module:Name/Arity). If the predicate fails Prolog will generate an existence_error exception. The hook is intended to implement alternatives to the SWI built-in autoloader, such as autoloading code from a database. Do not use this hook to suppress existence errors on predicates. See also unknown. + undefined_global_variable Context is instantiated to the name of the missing global variable. The hook must call nb_setval/2 or b_setval/2 before returning with the action retry.

@} */

/** @defgroup Messages Message Handling @ingroup YAPBuiltins @{

The interaction between YAP and the user relies on YAP's ability to portray messages. These messages range from prompts to error information. All message processing is performed through the builtin print_message/2, in two steps:

+ The message is processed into a list of commands 
+ The commands in the list are sent to the `format/3` builtin

in sequence.

The first argument to print_message/2 specifies the importance of the message. The options are:

+ error

error handling + warning compilation and run-time warnings, + informational generic informational messages + help help messages (not currently implemented in YAP) + query query used in query processing (not currently implemented in YAP) + silent messages that do not produce output but that can be intercepted by hooks.

The next table shows the main predicates and hooks associated to message handling in YAP:

*/

/** @pred print_message(+ Kind, Term)

The predicate print_message/2 is used to print messages, notably from exceptions in a human-readable format. Kind is one of informational, banner, warning, error, help or silent. A human-readable message is printed to the stream user_error.

If the Prolog flag verbose is silent, messages with Kind informational, or banner are treated as silent.@c See \cmdlineoption{-q}.

This predicate first translates the Term into a list of `message lines' (see print_message_lines/3 for details). Next it will call the hook message_hook/3 to allow the user intercepting the message. If message_hook/3 fails it will print the message unless Kind is silent.

If you need to report errors from your own predicates, we advise you to stick to the existing error terms if you can; but should you need to invent new ones, you can define corresponding error messages by asserting clauses for prolog:message/2. You will need to declare the predicate as multifile.

*/

/** @pred print_message_lines(+ Stream, + Prefix, + Lines)

Print a message (see print_message/2) that has been translated to a list of message elements. The elements of this list are:

+ `\<Format\>`-`\<Args\>`

Where Format is an atom and Args is a list of format argument. Handed to format/3. + flush If this appears as the last element, Stream is flushed (see flush_output/1) and no final newline is generated. + at_same_line If this appears as first element, no prefix is printed for the first line and the line-position is not forced to 0 (see format/1, ~N). + \<Format\> Handed to format/3 as format(Stream, Format, []). + nl A new line is started and if the message is not complete the Prefix is printed too.

*/

/** @pred user:message_hook(+ Term, + Kind, + Lines)

Hook predicate that may be define in the module user to intercept messages from print_message/2. Term and Kind are the same as passed to print_message/2. Lines is a list of format statements as described with print_message_lines/3.

This predicate should be defined dynamic and multifile to allow other modules defining clauses for it too.

*/

/** @pred message_to_string(+ Term, - String)

Translates a message-term into a string object. Primarily intended for SWI-Prolog emulation.

@} */

/** @defgroup Testing_Terms Predicates on terms @ingroup YAPBuiltins @{

*/

/** @pred var( T) is iso

Succeeds if T is currently a free variable, otherwise fails.

*/

/** @pred atom( T) is iso

Succeeds if and only if T is currently instantiated to an atom.

*/

/** @pred atomic(T) is iso

Checks whether T is an atomic symbol (atom or number).

*/

/** @pred compound( T) is iso

Checks whether T is a compound term.

*/

/** @pred db_reference( T)

Checks whether T is a database reference.

*/

/** @pred float( T) is iso

Checks whether T is a floating point number.

*/

/** @pred rational( T)

Checks whether T is a rational number.

*/

/** @pred integer( T) is iso

Succeeds if and only if T is currently instantiated to an integer.

*/

/** @pred nonvar( T) is iso

The opposite of var( _T_).

*/

/** @pred number( T) is iso

Checks whether T is an integer, rational or a float.

*/

/** @pred primitive( T)

Checks whether T is an atomic term or a database reference.

*/

/** @pred simple( T)

Checks whether T is unbound, an atom, or a number.

*/

/** @pred callable( T) is iso

Checks whether T is a callable term, that is, an atom or a compound term.

*/

/** @pred numbervars( T,+ N1,- Nn)

Instantiates each variable in term T to a term of the form: '$VAR'( _I_), with I increasing from N1 to Nn.

*/

/** @pred unnumbervars( T,+ NT)

Replace every '$VAR'( _I_) by a free variable.

*/

/** @pred ground( T) is iso

Succeeds if there are no free variables in the term T.

*/

/** @pred acyclic_term( T) is iso

Succeeds if there are loops in the term T, that is, it is an infinite term.

*/

/** @pred arg(+ N,+ T, A) is iso

Succeeds if the argument N of the term T unifies with A. The arguments are numbered from 1 to the arity of the term.

The current version will generate an error if T or N are unbound, if T is not a compound term, of if N is not a positive integer. Note that previous versions of YAP would fail silently under these errors.

*/

/** @pred functor( T, F, N) is iso

The top functor of term T is named F and has arity N.

When T is not instantiated, F and N must be. If N is 0, F must be an atomic symbol, which will be unified with T. If N is not 0, then F must be an atom and T becomes instantiated to the most general term having functor F and arity N. If T is instantiated to a term then F and N are respectively unified with its top functor name and arity.

In the current version of YAP the arity N must be an integer. Previous versions allowed evaluable expressions, as long as the expression would evaluate to an integer. This feature is not available in the ISO Prolog standard.

*/

/** @pred T =.. L is iso

The list L is built with the functor and arguments of the term T. If T is instantiated to a variable, then L must be instantiated either to a list whose head is an atom, or to a list consisting of just a number.

*/

/** @pred X = Y is iso

Tries to unify terms X and Y.

*/

/** @pred X \= Y is iso

Succeeds if terms X and Y are not unifiable.

*/

/** @pred unify_with_occurs_check(?T1,?T2) is iso

Obtain the most general unifier of terms T1 and T2, if there is one.

This predicate implements the full unification algorithm. An example:n

unify_with_occurs_check(a(X,b,Z),a(X,A,f(B)).

will succeed with the bindings A = b and Z = f(B). On the other hand:

unify_with_occurs_check(a(X,b,Z),a(X,A,f(Z)).

would fail, because Z is not unifiable with f(Z). Note that (=)/2 would succeed for the previous examples, giving the following bindings A = b and Z = f(Z).

*/

/** @pred copy_term(? TI,- TF) is iso

Term TF is a variant of the original term TI, such that for each variable V in the term TI there is a new variable V' in term TF. Notice that:

  • suspended goals and attributes for attributed variables in TI are also duplicated;
  • ground terms are shared between the new and the old term.

If you do not want any sharing to occur please use duplicate_term/2.

*/

/** @pred duplicate_term(? TI,- TF)

Term TF is a variant of the original term TI, such that for each variable V in the term TI there is a new variable V' in term TF, and the two terms do not share any structure. All suspended goals and attributes for attributed variables in TI are also duplicated.

Also refer to copy_term/2.

*/

/** @pred is_list(+ List)

True when List is a proper list. That is, List is bound to the empty list (nil) or a term with functor '.' and arity 2.

*/

/** @pred ? Term1 =@= ? Term2

Same as variant/2, succeeds if Term1 and Term2 are variant terms.

*/

/** @pred subsumes_term(? Subsumer, ? Subsumed)

Succeed if Submuser subsumes Subsuned but does not bind any variable in Subsumer.

*/

/** @pred term_subsumer(? T1, ? T2, ? Subsumer)

Succeed if Subsumer unifies with the least general generalization over T1 and T2.

*/

/** @pred term_variables(? Term, - Variables) is iso

Unify Variables with the list of all variables of term Term. The variables occur in the order of their first appearance when traversing the term depth-first, left-to-right.

*/

/** @pred rational_term_to_tree(? TI,- TF)

The term TF is a tree representation (without cycles) for the Prolog term TI. Loops are replaced by terms of the form _LOOP_( _LevelsAbove_) where LevelsAbove is the size of the loop.

*/

/** @pred tree_to_rational_term(? TI,- TF)

Inverse of rational_term_to_tree/2. The term TI is a tree representation (without cycles) for the Prolog term TF. Loops replace terms of the form _LOOP_( _LevelsAbove_) where LevelsAbove is the size of the loop.

@} */

/** @defgroup Predicates_on_Atoms Predicates on Atoms @ingroup YAPBuiltins @{

The following predicates are used to manipulate atoms:

*/

/** @pred name( A, L)

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). The argument A will be unified with an atomic symbol and L with the list of the ASCII codes for the characters of the external representation of A.

 name(yap,L).

will return:

 L = [121,97,112].

and

 name(3,L).

will return:

 L = [51].

*/

/** @pred atom_chars(? A,? L) is iso

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). The argument A must be unifiable with an atom, and the argument L with the list of the characters of A.

*/

/** @pred atom_codes(? A,? L) is iso

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). The argument A will be unified with an atom and L with the list of the ASCII codes for the characters of the external representation of A.

*/

/** @pred atom_concat(+ As,? A)

The predicate holds when the first argument is a list of atoms, and the second unifies with the atom obtained by concatenating all the atoms in the first list.

*/

/** @pred atomic_concat(+ As,? A)

The predicate holds when the first argument is a list of atomic terms, and the second unifies with the atom obtained by concatenating all the atomic terms in the first list. The first argument thus may contain atoms or numbers.

*/

/** @pred atomic_list_concat(+ As,? A)

The predicate holds when the first argument is a list of atomic terms, and the second unifies with the atom obtained by concatenating all the atomic terms in the first list. The first argument thus may contain atoms or numbers.

*/

/** @pred atomic_list_concat(? As,+ Separator,? A)

Creates an atom just like atomic_list_concat/2, but inserts Separator between each pair of atoms. For example:

?- atomic_list_concat([gnu, gnat], ', ', A).

A = 'gnu, gnat'

YAP emulates the SWI-Prolog version of this predicate that can also be used to split atoms by instantiating Separator and Atom as shown below.

?- atomic_list_concat(L, -, 'gnu-gnat').

L = [gnu, gnat]

*/

/** @pred atom_length(+ A,? I) is iso

The predicate holds when the first argument is an atom, and the second unifies with the number of characters forming that atom.

*/

/** @pred atom_concat(? A1,? A2,? A12) is iso

The predicate holds when the third argument unifies with an atom, and the first and second unify with atoms such that their representations concatenated are the representation for A12.

If A1 and A2 are unbound, the built-in will find all the atoms that concatenated give A12.

*/

/** @pred number_chars(? I,? L) is iso

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). The argument I must be unifiable with a number, and the argument L with the list of the characters of the external representation of I.

*/

/** @pred number_codes(? A,? L) is iso

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). The argument A will be unified with a number and L with the list of the ASCII codes for the characters of the external representation of A.

*/

/** @pred atom_number(? Atom,? Number)

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). If the argument Atom is an atom, Number must be the number corresponding to the characters in Atom, otherwise the characters in Atom must encode a number Number.

*/

/** @pred number_atom(? I,? L)

The predicate holds when at least one of the arguments is ground (otherwise, an error message will be displayed). The argument I must be unifiable with a number, and the argument L must be unifiable with an atom representing the number.

*/

/** @pred sub_atom(+ A,? Bef, ? Size, ? After, ? At_out) is iso

True when A and At_out are atoms such that the name of At_out has size Size and is a sub-string of the name of A, such that Bef is the number of characters before and After the number of characters afterwards.

Note that A must always be known, but At_out can be unbound when calling this built-in. If all the arguments for sub_atom/5 but A are unbound, the built-in will backtrack through all possible sub-strings of A.

@} */

/** @defgroup Predicates_on_Characters Predicates on Characters @ingroup YAPBuiltins @{

The following predicates are used to manipulate characters:

*/

/** @pred char_code(? A,? I) is iso

The built-in succeeds with A bound to character represented as an atom, and I bound to the character code represented as an integer. At least, one of either A or I must be bound before the call.

*/

/** @pred char_type(? Char, ? Type)

Tests or generates alternative Types or Chars. The character-types are inspired by the standard C \<ctype.h\> primitives.

  • alnum Char is a letter (upper- or lowercase) or digit.

  • alpha Char is a letter (upper- or lowercase).

  • csym Char is a letter (upper- or lowercase), digit or the underscore (_). These are valid C- and Prolog symbol characters.

  • csymf Char is a letter (upper- or lowercase) or the underscore (_). These are valid first characters for C- and Prolog symbols

  • ascii Char is a 7-bits ASCII character (0..127).

  • white Char is a space or tab. E.i. white space inside a line.

  • cntrl Char is an ASCII control-character (0..31).

  • digit Char is a digit.

  • digit( Weight) Char is a digit with value Weight. I.e. char_type(X, digit(6)) yields X = '6'. Useful for parsing numbers.

  • xdigit( Weight) Char is a hexa-decimal digit with value Weight. I.e. char_type(a, xdigit(X) yields X = '10'. Useful for parsing numbers.

  • graph Char produces a visible mark on a page when printed. Note that the space is not included!

  • lower Char is a lower-case letter.

  • lower(Upper) Char is a lower-case version of Upper. Only true if Char is lowercase and Upper uppercase.

    • to_lower(Upper) Char is a lower-case version of Upper. For non-letters, or letter without case, Char and Lower are the same. See also upcase_atom/2 and downcase_atom/2.

    • upper Char is an upper-case letter.

    • upper(Lower) Char is an upper-case version of Lower. Only true if Char is uppercase and Lower lowercase.

    • to_upper(Lower) Char is an upper-case version of Lower. For non-letters, or letter without case, Char and Lower are the same. See also upcase_atom/2 and downcase_atom/2.

    • punct Char is a punctuation character. This is a graph character that is not a letter or digit.

    • space Char is some form of layout character (tab, vertical-tab, newline, etc.).

    • end_of_file Char is -1.

    • end_of_line Char ends a line (ASCII: 10..13).

    • newline Char is a the newline character (10).

    • period Char counts as the end of a sentence (.,!,?).

    • quote Char is a quote-character (", ', `).

    • paren(Close) Char is an open-parenthesis and Close is the corresponding close-parenthesis.

    • code_type(? Code, ? Type)

As char_type/2, but uses character-codes rather than one-character atoms. Please note that both predicates are as flexible as possible. They handle either representation if the argument is instantiated and only will instantiate with an integer code or one-character atom depending of the version used. See also the prolog-flag double_quotes and the built-in predicates atom_chars/2 and atom_codes/2.

@} */

/** @defgroup Comparing_Terms Comparing Terms @ingroup YAPBuiltins @{

The following predicates are used to compare and order terms, using the standard ordering:

+ 

variables come before numbers, numbers come before atoms which in turn come before compound terms, i.e.: variables @< numbers @< atoms @< compound terms. + Variables are roughly ordered by "age" (the "oldest" variable is put first); + Floating point numbers are sorted in increasing order; + Rational numbers are sorted in increasing order; + Integers are sorted in increasing order; + Atoms are sorted in lexicographic order; + Compound terms are ordered first by arity of the main functor, then by the name of the main functor, and finally by their arguments in left-to-right order.

*/

/** @pred compare( C, X, Y) is iso

As a result of comparing X and Y, C may take one of the following values:

+ 

= if X and Y are identical; + \< if X precedes Y in the defined order; + \> if Y precedes X in the defined order;

+ _X_ ==  _Y_ is iso 

Succeeds if terms X and Y are strictly identical. The difference between this predicate and =/2 is that, if one of the arguments is a free variable, it only succeeds when they have already been unified.

?- X == Y.

fails, but,

?- X = Y, X == Y.

succeeds.

?- X == 2.

fails, but,

?- X = 2, X == 2.

succeeds.

*/

/** @pred X \== Y is iso

Terms X and Y are not strictly identical.

*/

/** @pred X @< Y is iso

Term X precedes term Y in the standard order.

*/

/** @pred X @=< Y is iso

Term X does not follow term Y in the standard order.

*/

/** @pred X @> Y is iso

Term X follows term Y in the standard order.

*/

/** @pred X @>= Y is iso

Term X does not precede term Y in the standard order.

*/

/** @pred sort(+ L,- S) is iso

Unifies S with the list obtained by sorting L and merging identical (in the sense of ==) elements.

*/

/** @pred keysort(+ L, S) is iso

Assuming L is a list of the form _Key_- _Value_, keysort(+ _L_, _S_) unifies S with the list obtained from L, by sorting its elements according to the value of Key.

?- keysort([3-a,1-b,2-c,1-a,1-b],S).

would return:

S = [1-b,1-a,1-b,2-c,3-a]

*/

/** @pred predsort(+ Pred, + List, - Sorted)

Sorts similar to sort/2, but determines the order of two terms by calling Pred(- Delta, + E1, + E2) . This call must unify Delta with one of \<, \> or =. If built-in predicate compare/3 is used, the result is the same as sort/2.

*/

/** @pred length(? L,? S)

Unify the well-defined list L with its length. The procedure can be used to find the length of a pre-defined list, or to build a list of length S.

@} */

/** @defgroup Arithmetic Arithmetic @ingroup YAPBuiltins @{

@copydoc arithmetic

  • See @ref arithmetic_preds for the predicates that implement arithment

  • See @ref arithmetic_cmps for the arithmetic comparisons supported in YAP

  • See @ref arithmetic_operators for how to call arithmetic operations in YAP

@} */

/** @defgroup InputOutput Input/Output Predicates @ingroup YAPBuiltins @{

Some of the Input/Output predicates described below will in certain conditions provide error messages and abort only if the file_errors flag is set. If this flag is cleared the same predicates will just fail. Details on setting and clearing this flag are given under 7.7.

@} */

/** @defgroup Streams_and_Files Handling Streams and Files @ingroup YAPBuiltins @{

*/

/** @pred open(+ F,+ M,- S) is iso

Opens the file with name F in mode M ('read', 'write' or 'append'), returning S unified with the stream name.

At most, there are 17 streams opened at the same time. Each stream is either an input or an output stream but not both. There are always 3 open streams: user_input for reading, user_output for writing and user_error for writing. If there is no ambiguity, the atoms user_input and user_output may be referred to as user.

The file_errors flag controls whether errors are reported when in mode 'read' or 'append' the file F does not exist or is not readable, and whether in mode 'write' or 'append' the file is not writable.

+ open(+ _F_,+ _M_,- _S_,+ _Opts_) is iso

Opens the file with name F in mode M ('read', 'write' or 'append'), returning S unified with the stream name, and following these options:

+ type(+ _T_) is iso

Specify whether the stream is a text stream (default), or a binary stream.

+ reposition(+ _Bool_) is iso

Specify whether it is possible to reposition the stream (true), or not (false). By default, YAP enables repositioning for all files, except terminal files and sockets.

+ eof_a

*/

/** @pred n(+ Action) is iso Specify the action to take if attempting to input characters from a stream where we have previously found an end_of_file. The possible actions are error, that raises an error, reset, that tries to reset the stream and is used for tty type files, and eof_code, which generates a new end_of_file (default for non-tty files).

+ alias(+ _Name_) is iso

Specify an alias to the stream. The alias Name must be an atom. The alias can be used instead of the stream descriptor for every operation concerning the stream.

The operation will fail and give an error if the alias name is already in use. YAP allows several aliases for the same file, but only one is returned by stream_property/2

+ bom(+ _Bool_)

If present and true, a BOM (Byte Order Mark) was detected while opening the file for reading or a BOM was written while opening the stream. See BOM for details.

+ encoding(+ _Encoding_)

Set the encoding used for text. See Encoding for an overview of wide character and encoding issues.

+ representation_errors(+ _Mode_)

Change the behaviour when writing characters to the stream that cannot be represented by the encoding. The behaviour is one of error (throw and Input/Output error exception), prolog (write \\u...\\ escape code or xml (write \&#...; XML character entity). The initial mode is prolog for the user streams and error for all other streams. See also Encoding.

+ expand_filename(+ _Mode_)

If Mode is true then do filename expansion, then ask Prolog to do file name expansion before actually trying to opening the file: this includes processing ~ characters and processing $ environment variables at the beginning of the file. Otherwise, just try to open the file using the given name.

The default behavior is given by the Prolog flag open_expands_filename.

*/

/** @pred close(+ S) is iso

Closes the stream S. If S does not stand for a stream currently opened an error is reported. The streams user_input, user_output, and user_error can never be closed.

*/

/** @pred close(+ S,+ O) is iso

Closes the stream S, following options O.

The only valid options are force(true) and force(false). YAP currently ignores these options.

*/

/** @pred time_file(+ File,- Time)

Unify the last modification time of File with Time. Time is a floating point number expressing the seconds elapsed since Jan 1, 1970.

*/

/** @pred access_file(+ F,+ M)

Is the file accessible?

*/

/** @pred file_base_name(+ Name,- FileName)

Give the path a full path FullPath extract the FileName.

*/

/** @pred file_name_extension(? Base,? Extension, ? Name)

This predicate is used to add, remove or test filename extensions. The main reason for its introduction is to deal with different filename properties in a portable manner. If the file system is case-insensitive, testing for an extension will be done case-insensitive too. Extension may be specified with or without a leading dot (.). If an Extension is generated, it will not have a leading dot.

*/

/** @pred current_stream( F, M, S)

Defines the relation: The stream S is opened on the file F in mode M. It might be used to obtain all open streams (by backtracking) or to access the stream for a file F in mode M, or to find properties for a stream S. Notice that some streams might not be associated to a file: in this case YAP tries to return the file number. If that is not available, YAP unifies F with S.

*/

/** @pred is_stream( S)

Succeeds if S is a currently open stream.

*/

/** @pred flush_output is iso

Send out all data in the output buffer of the current output stream.

*/

/** @pred flush_output(+ S) is iso

Send all data in the output buffer for stream S.

*/

/** @pred set_input(+ S) is iso

Set stream S as the current input stream. Predicates like read/1 and get/1 will start using stream S.

*/

/** @pred set_output(+ S) is iso

Set stream S as the current output stream. Predicates like write/1 and put/1 will start using stream S.

*/

/** @pred stream_select(+ STREAMS,+ TIMEOUT,- READSTREAMS)

Given a list of open STREAMS opened in read mode and a TIMEOUT return a list of streams who are now available for reading.

If the TIMEOUT is instantiated to off, stream_select/3 will wait indefinitely for a stream to become open. Otherwise the timeout must be of the form SECS:USECS where SECS is an integer gives the number of seconds to wait for a timeout and USECS adds the number of micro-seconds.

This built-in is only defined if the system call select is available in the system.

*/

/** @pred current_input(- S) is iso

Unify S with the current input stream.

*/

/** @pred current_output(- S) is iso

Unify S with the current output stream.

*/

/** @pred at_end_of_stream is iso

Succeed if the current stream has stream position end-of-stream or past-end-of-stream.

*/

/** @pred at_end_of_stream(+ S) is iso

Succeed if the stream S has stream position end-of-stream or past-end-of-stream. Note that S must be a readable stream.

*/

/** @pred set_stream_position(+ S, + POS) is iso

Given a stream position POS for a stream S, set the current stream position for S to be POS.

*/

/** @pred stream_property(? Stream,? Prop) is iso

Obtain the properties for the open streams. If the first argument is unbound, the procedure will backtrack through all open streams. Otherwise, the first argument must be a stream term (you may use current_stream to obtain a current stream given a file name).

The following properties are recognized:

+ file_name( _P_)

An atom giving the file name for the current stream. The file names are user_input, user_output, and user_error for the standard streams.

+ mode( _P_)

The mode used to open the file. It may be one of append, read, or write.

+ input

The stream is readable.

+ output

The stream is writable.

+ alias( _A_)

ISO-Prolog primitive for stream aliases. YAP returns one of the existing aliases for the stream.

+ position( _P_)

A term describing the position in the stream.

+ end_of_stream( _E_)

Whether the stream is at the end of stream, or it has found the end of stream and is past, or whether it has not yet reached the end of stream.

+ eof_action( _A_)

The action to take when trying to read after reaching the end of stream. The action may be one of error, generate an error, eof_code, return character code -1, or reset the stream.

+ reposition( _B_)

Whether the stream can be repositioned or not, that is, whether it is seekable.

+ type( _T_)

Whether the stream is a text stream or a binary stream.

+ bom(+ _Bool_)

If present and true, a BOM (Byte Order Mark) was detected while opening the file for reading or a BOM was written while opening the stream. See BOM for details.

+ encoding(+ _Encoding_)

Query the encoding used for text. See Encoding for an overview of wide character and encoding issues in YAP.

+ representation_errors(+ _Mode_)

Behaviour when writing characters to the stream that cannot be represented by the encoding. The behaviour is one of error (throw and Input/Output error exception), prolog (write \\u...\\ escape code or xml (write \&#...; XML character entity). The initial mode is prolog for the user streams and error for all other streams. See also Encoding and open/4.

+ current_line_number(- _LineNumber_) 

Unify LineNumber with the line number for the current stream.

*/

/** @pred current_line_number(+ Stream,- LineNumber)

Unify LineNumber with the line number for the Stream.

*/

/** @pred line_count(+ Stream,- LineNumber)

Unify LineNumber with the line number for the Stream.

*/

/** @pred character_count(+ Stream,- CharacterCount)

Unify CharacterCount with the number of characters written to or read to Stream.

*/

/** @pred line_position(+ Stream,- LinePosition)

Unify LinePosition with the position on current text stream Stream.

*/

/** @pred stream_position(+ Stream,- StreamPosition)

Unify StreamPosition with the packaged information of position on current stream Stream. Use stream_position_data/3 to retrieve information on character or line count.

*/

/** @pred stream_position_data(+ Field,+ StreamPosition,- Info)

Given the packaged stream position term StreamPosition, unify Info with Field line_count, byte_count, or char_count.

@} */

/** @defgroup ChYProlog_File_Handling C-Prolog File Handling @ingroup YAPBuiltins @{

*/

/** @pred tell(+ S)

If S is a currently opened stream for output, it becomes the current output stream. If S is an atom it is taken to be a filename. If there is no output stream currently associated with it, then it is opened for output, and the new output stream created becomes the current output stream. If it is not possible to open the file, an error occurs. If there is a single opened output stream currently associated with the file, then it becomes the current output stream; if there are more than one in that condition, one of them is chosen.

Whenever S is a stream not currently opened for output, an error may be reported, depending on the state of the file_errors flag. The predicate just fails, if S is neither a stream nor an atom.

*/

/** @pred telling(- S)

The current output stream is unified with S.

*/

/** @pred told

Closes the current output stream, and the user's terminal becomes again the current output stream. It is important to remember to close streams after having finished using them, as the maximum number of simultaneously opened streams is 17.

*/

/** @pred see(+ S)

If S is a currently opened input stream then it is assumed to be the current input stream. If S is an atom it is taken as a filename. If there is no input stream currently associated with it, then it is opened for input, and the new input stream thus created becomes the current input stream. If it is not possible to open the file, an error occurs. If there is a single opened input stream currently associated with the file, it becomes the current input stream; if there are more than one in that condition, then one of them is chosen.

When S is a stream not currently opened for input, an error may be reported, depending on the state of the file_errors flag. If S is neither a stream nor an atom the predicates just fails.

*/

/** @pred seeing(- S)

The current input stream is unified with S.

*/

/** @pred seen

Closes the current input stream (see 6.7.).

@} */

/** @defgroup InputOutput_of_Terms Handling Input/Output of Terms @ingroup YAPBuiltins @{

*/

/** @pred read(- T) is iso

Reads the next term from the current input stream, and unifies it with T. The term must be followed by a dot ('.') and any blank-character as previously defined. The syntax of the term must match the current declarations for operators (see op). If the end-of-stream is reached, T is unified with the atom end_of_file. Further reads from of the same stream may cause an error failure (see open/3).

+ read_term(- _T_,+ _Options_) is iso 

Reads term T from the current input stream with execution controlled by the following options:

*/

/** @pred term_position(- Position)

Unify Position with a term describing the position of the stream at the start of parse. Use stream_position_data/3 to obtain extra information.

+ singletons(- _Names_) 

Unify Names with a list of the form Name=Var, where Name is the name of a non-anonymous singleton variable in the original term, and Var is the variable's representation in YAP. The variables occur in left-to-right traversal order.

+ syntax_errors(+ _Val_) 

Control action to be taken after syntax errors. See yap_flag/2 for detailed information.

+ variable

*/

/** @pred es(- Names)

Unify Names with a list of the form Name=Var, where Name is the name of a non-anonymous variable in the original term, and Var is the variable's representation in YAP. The variables occur in left-to-right traversal order.

+ variables(- _Names_) 

Unify Names with a list of the variables in term T. The variables occur in left-to-right traversal order.

+ char_conversion(+ _IN_,+ _OUT_) is iso 

While reading terms convert unquoted occurrences of the character IN to the character OUT. Both IN and OUT must be bound to single characters atoms.

Character conversion only works if the flag char_conversion is on. This is default in the iso and sicstus language modes. As an example, character conversion can be used for instance to convert characters from the ISO-LATIN-1 character set to ASCII.

If IN is the same character as OUT, char_conversion/2 will remove this conversion from the table.

*/

/** @pred current_char_conversion(? IN,? OUT) is iso

If IN is unbound give all current character translations. Otherwise, give the translation for IN, if one exists.

*/

/** @pred write( T) is iso

The term T is written to the current output stream according to the operator declarations in force.

*/

/** @pred writeln( T) is iso

Same as write/1 followed by nl/0.

*/

/** @pred display(+ T)

Displays term T on the current output stream. All Prolog terms are written in standard parenthesized prefix notation.

*/

/** @pred write_canonical(+ T) is iso

Displays term T on the current output stream. Atoms are quoted when necessary, and operators are ignored, that is, the term is written in standard parenthesized prefix notation.

*/

/** @pred write_term(+ T, + Opts) is iso

Displays term T on the current output stream, according to the following options:

+ quoted(+ _Bool_) is iso

If true, quote atoms if this would be necessary for the atom to be recognized as an atom by YAP's parser. The default value is false.

+ ignore_ops(+ _Bool_) is iso

If true, ignore operator declarations when writing the term. The default value is false.

+ numbervars(+ _Bool_) is iso

If true, output terms of the form '$VAR'(N), where N is an integer, as a sequence of capital letters. The default value is false.

+ portrayed(+ _Bool_)

If true, use portray/1 to portray bound terms. The default value is false.

+ portray(+ _Bool_)

If true, use portray/1 to portray bound terms. The default value is false.

+ max_depth(+ _Depth_)

If Depth is a positive integer, use Depth as the maximum depth to portray a term. The default is 0, that is, unlimited depth.

+ priority(+ _Piority_)

If Priority is a positive integer smaller than 1200, give the context priority. The default is 1200.

+ cycles(+ _Bool_)

Do not loop in rational trees (default).

*/

/** @pred writeq( T) is iso

Writes the term T, quoting names to make the result acceptable to the predicate 'read' whenever necessary.

*/

/** @pred print( T)

Prints the term T to the current output stream using write/1 unless T is bound and a call to the user-defined predicate portray/1 succeeds. To do pretty printing of terms the user should define suitable clauses for portray/1 and use print/1.

*/

/** @pred format(+ T,+ L)

Print formatted output to the current output stream. The arguments in list L are output according to the string or atom T.

A control sequence is introduced by a w. The following control sequences are available in YAP:

+ '~~'

Print a single tilde.

+ '~a'

The next argument must be an atom, that will be printed as if by write.

+ '~Nc'

The next argument must be an integer, that will be printed as a character code. The number N is the number of times to print the character (default 1).

+ '~Ne'
+ '~NE'
+ '~Nf'
+ '~Ng'
+ '~NG'

The next argument must be a floating point number. The float F, the number N and the control code c will be passed to printf as:

    printf("%s.Nc", F)

As an example:

?- format("~8e, ~8E, ~8f, ~8g, ~8G~w",
          [3.14,3.14,3.14,3.14,3.14,3.14]).
3.140000e+00, 3.140000E+00, 3.140000, 3.14, 3.143.14
+ '~Nd'

The next argument must be an integer, and N is the number of digits after the decimal point. If N is 0 no decimal points will be printed. The default is N = 0.

?- format("~2d, ~d",[15000, 15000]).
150.00, 15000
+ '~ND'

Identical to '~Nd', except that commas are used to separate groups of three digits.

?- format("~2D, ~D",[150000, 150000]).
1,500.00, 150,000
+ '~i'

Ignore the next argument in the list of arguments:

?- format('The ~i met the boregrove',[mimsy]).
The  met the boregrove
+ '~k'

Print the next argument with write_canonical:

?- format("Good night ~k",a+[1,2]).
Good night +(a,[1,2])
+ '~Nn'

Print N newlines (where N defaults to 1).

+ '~NN'

Print N newlines if at the beginning of the line (where N defaults to 1).

+ '~Nr'

The next argument must be an integer, and N is interpreted as a radix, such that 2 \<= N \<= 36 (the default is 8).

?- format("~2r, 0x~16r, ~r",
          [150000, 150000, 150000]).
100100100111110000, 0x249f0, 444760

Note that the letters a-z denote digits larger than 9.

+ '~NR'

Similar to '~NR'. The next argument must be an integer, and N is interpreted as a radix, such that 2 \<= N \<= 36 (the default is 8).

?- format("~2r, 0x~16r, ~r",
          [150000, 150000, 150000]).
100100100111110000, 0x249F0, 444760

The only difference is that letters A-Z denote digits larger than 9.

+ '~p'

Print the next argument with print/1:

?- format("Good night ~p",a+[1,2]).
Good night a+[1,2]
+ '~q'

Print the next argument with writeq/1:

?- format("Good night ~q",'Hello'+[1,2]).
Good night 'Hello'+[1,2]
+ '~Ns'

The next argument must be a list of character codes. The system then outputs their representation as a string, where N is the maximum number of characters for the string ( N defaults to the length of the string).

?- format("The ~s are ~4s",["woods","lovely"]).
The woods are love
+ '~w'

Print the next argument with write/1:

?- format("Good night ~w",'Hello'+[1,2]).
Good night Hello+[1,2]

The number of arguments, N, may be given as an integer, or it may be given as an extra argument. The next example shows a small procedure to write a variable number of a characters:

write_many_as(N) :-
        format("~*c",[N,0'a]).

The format/2 built-in also allows for formatted output. One can specify column boundaries and fill the intermediate space by a padding character:

+ '~N|'

Set a column boundary at position N, where N defaults to the current position.

+ '~N+'

Set a column boundary at N characters past the current position, where N defaults to 8.

+ '~Nt'

Set padding for a column, where N is the fill code (default is SPC).

The next example shows how to align columns and padding. We first show left-alignment:

   ?- format("~n*Hello~16+*~n",[]).
*Hello          *

Note that we reserve 16 characters for the column.

The following example shows how to do right-alignment:

   ?- format("*~tHello~16+*~n",[]).
*          Hello*

The ~t escape sequence forces filling before Hello.

We next show how to do centering:

   ?- format("*~tHello~t~16+*~n",[]).
*     Hello     *

The two ~t escape sequence force filling both before and after Hello. Space is then evenly divided between the right and the left sides.

*/

/** @pred format(+ T)

Print formatted output to the current output stream.

*/

/** @pred format(+ S,+ T,+ L)

Print formatted output to stream S.

*/

/** @pred with_output_to(+ Ouput,: Goal)

Run Goal as once/1, while characters written to the current output are sent to Output. The predicate is SWI-Prolog specific.

Applications should generally avoid creating atoms by breaking and concatenating other atoms as the creation of large numbers of intermediate atoms generally leads to poor performance, even more so in multi-threaded applications. This predicate supports creating difference-lists from character data efficiently. The example below defines the DCG rule term/3 to insert a term in the output:

 term(Term, In, Tail) :-
        with_output_to(codes(In, Tail), write(Term)).

?- phrase(term(hello), X).

X = [104, 101, 108, 108, 111]
+ A Stream handle or alias

Temporary switch current output to the given stream. Redirection using with_output_to/2 guarantees the original output is restored, also if Goal fails or raises an exception. See also call_cleanup/2. + atom(- Atom) Create an atom from the emitted characters. Please note the remark above. + string(- String) Create a string-object (not supported in YAP). + codes(- Codes) Create a list of character codes from the emitted characters, similar to atom_codes/2. + codes(- Codes, - Tail) Create a list of character codes as a difference-list. + chars(- Chars) Create a list of one-character-atoms codes from the emitted characters, similar to atom_chars/2. + chars(- Chars, - Tail) Create a list of one-character-atoms as a difference-list.

@} */

/** @defgroup InputOutput_of_Characters Handling Input/Output of Characters @ingroup YAPBuiltins @{

*/

/** @pred put(+ N)

Outputs to the current output stream the character whose ASCII code is N. The character N must be a legal ASCII character code, an expression yielding such a code, or a list in which case only the first element is used.

*/

/** @pred put_byte(+ N) is iso

Outputs to the current output stream the character whose code is N. The current output stream must be a binary stream.

*/

/** @pred put_char(+ N) is iso

Outputs to the current output stream the character who is used to build the representation of atom A. The current output stream must be a text stream.

*/

/** @pred put_code(+ N) is iso

Outputs to the current output stream the character whose ASCII code is N. The current output stream must be a text stream. The character N must be a legal ASCII character code, an expression yielding such a code, or a list in which case only the first element is used.

*/

/** @pred get(- C)

The next non-blank character from the current input stream is unified with C. Blank characters are the ones whose ASCII codes are not greater than 32. If there are no more non-blank characters in the stream, C is unified with -1. If end_of_stream has already been reached in the previous reading, this call will give an error message.

*/

/** @pred get0(- C)

The next character from the current input stream is consumed, and then unified with C. There are no restrictions on the possible values of the ASCII code for the character, but the character will be internally converted by YAP.

*/

/** @pred get_byte(- C) is iso

If C is unbound, or is a character code, and the current stream is a binary stream, read the next byte from the current stream and unify its code with C.

*/

/** @pred get_char(- C) is iso

If C is unbound, or is an atom representation of a character, and the current stream is a text stream, read the next character from the current stream and unify its atom representation with C.

*/

/** @pred get_code(- C) is iso

If C is unbound, or is the code for a character, and the current stream is a text stream, read the next character from the current stream and unify its code with C.

*/

/** @pred peek_byte(- C) is iso

If C is unbound, or is a character code, and the current stream is a binary stream, read the next byte from the current stream and unify its code with C, while leaving the current stream position unaltered.

*/

/** @pred peek_char(- C) is iso

If C is unbound, or is an atom representation of a character, and the current stream is a text stream, read the next character from the current stream and unify its atom representation with C, while leaving the current stream position unaltered.

*/

/** @pred peek_code(- C) is iso

If C is unbound, or is the code for a character, and the current stream is a text stream, read the next character from the current stream and unify its code with C, while leaving the current stream position unaltered.

*/

/** @pred skip(+ N)

Skips input characters until the next occurrence of the character with ASCII code N. The argument to this predicate can take the same forms as those for put (see 6.11).

*/

/** @pred tab(+ N)

Outputs N spaces to the current output stream.

*/

/** @pred nl is iso

Outputs a new line to the current output stream.

@} */

/** @defgroup InputOutput_for_Streams Input/Output Predicates applied to Streams @ingroup YAPBuiltins @{

*/

/** @pred read(+ S,- T) is iso

Reads term T from the stream S instead of from the current input stream.

*/

/** @pred read_term(+ S,- T,+ Options) is iso

Reads term T from stream S with execution controlled by the same options as read_term/2.

*/

/** @pred write(+ S, T) is iso

Writes term T to stream S instead of to the current output stream.

*/

/** @pred write_canonical(+ S,+ T) is iso

Displays term T on the stream S. Atoms are quoted when necessary, and operators are ignored.

*/

/** @pred write_term(+ S, + T, + Opts) is iso

Displays term T on the current output stream, according to the same options used by write_term/3.

*/

/** @pred writeq(+ S, T) is iso

As writeq/1, but the output is sent to the stream S.

*/

/** @pred display(+ S, T)

Like display/1, but using stream S to display the term.

*/

/** @pred print(+ S, T)

Prints term T to the stream S instead of to the current output stream.

*/

/** @pred put(+ S,+ N)

As put(N), but to stream S.

*/

/** @pred put_byte(+ S,+ N) is iso

As put_byte(N), but to binary stream S.

*/

/** @pred put_char(+ S,+ A) is iso

As put_char(A), but to text stream S.

*/

/** @pred put_code(+ S,+ N) is iso

As put_code(N), but to text stream S.

*/

/** @pred get(+ S,- C)

The same as get(C), but from stream S.

*/

/** @pred get0(+ S,- C)

The same as get0(C), but from stream S.

*/

/** @pred get_byte(+ S,- C) is iso

If C is unbound, or is a character code, and the stream S is a binary stream, read the next byte from that stream and unify its code with C.

*/

/** @pred get_char(+ S,- C) is iso

If C is unbound, or is an atom representation of a character, and the stream S is a text stream, read the next character from that stream and unify its representation as an atom with C.

*/

/** @pred get_code(+ S,- C) is iso

If C is unbound, or is a character code, and the stream S is a text stream, read the next character from that stream and unify its code with C.

*/

/** @pred peek_byte(+ S,- C) is iso

If C is unbound, or is a character code, and S is a binary stream, read the next byte from the current stream and unify its code with C, while leaving the current stream position unaltered.

*/

/** @pred peek_char(+ S,- C) is iso

If C is unbound, or is an atom representation of a character, and the stream S is a text stream, read the next character from that stream and unify its representation as an atom with C, while leaving the current stream position unaltered.

*/

/** @pred peek_code(+ S,- C) is iso

If C is unbound, or is an atom representation of a character, and the stream S is a text stream, read the next character from that stream and unify its representation as an atom with C, while leaving the current stream position unaltered.

*/

/** @pred skip(+ S,- C)

Like skip/1, but using stream S instead of the current input stream.

*/

/** @pred tab(+ S,+ N)

The same as tab/1, but using stream S.

*/

/** @pred nl(+ S) is iso

Outputs a new line to stream S.

@} */

/** @defgroup ChYProlog_to_Terminal Compatible C-Prolog predicates for Terminal Input/Output @ingroup YAPBuiltins @{

*/

/** @pred ttyput(+ N)

As put(N) but always to user_output.

*/

/** @pred ttyget(- C)

The same as get(C), but from stream user_input.

*/

/** @pred ttyget0(- C)

The same as get0(C), but from stream user_input.

*/

/** @pred ttyskip(- C)

Like skip/1, but always using stream user_input. stream.

*/

/** @pred ttytab(+ N)

The same as tab/1, but using stream user_output.

*/

/** @pred ttynl

Outputs a new line to stream user_output.

@} */

/** @defgroup InputOutput_Control Controlling Input/Output @ingroup YAPBuiltins @{

*/

/** @pred exists(+ F)

Checks if file F exists in the current directory.

+ nofileerrors 

Switches off the file_errors flag, so that the predicates see/1, tell/1, open/3 and close/1 just fail, instead of producing an error message and aborting whenever the specified file cannot be opened or closed.

+ fileerrors 

Switches on the file_errors flag so that in certain error conditions Input/Output predicates will produce an appropriated message and abort.

+ always_prompt_user 

Force the system to prompt the user even if the user_input stream is not a terminal. This command is useful if you want to obtain interactive control from a pipe or a socket.

@} */

/** @defgroup Sockets Using Sockets From YAP @ingroup YAPBuiltins @{

YAP includes a SICStus Prolog compatible socket interface. In YAP-6.3 this uses the clib package to emulate the old low level interface that provides direct access to the major socket system calls. These calls can be used both to open a new connection in the network or connect to a networked server. Socket connections are described as read/write streams, and standard Input/Output built-ins can be used to write on or read from sockets. The following calls are available:

*/

/** @pred socket(+ DOMAIN,+ TYPE,+ PROTOCOL,- SOCKET)

Corresponds to the BSD system call socket. Create a socket for domain DOMAIN of type TYPE and protocol PROTOCOL. Both DOMAIN and TYPE should be atoms, whereas PROTOCOL must be an integer. The new socket object is accessible through a descriptor bound to the variable SOCKET.

The current implementation of YAP accepts socket domains 'AF_INET' and 'AF_UNIX'. Socket types depend on the underlying operating system, but at least the following types are supported: 'SOCK_STREAM' and 'SOCK_DGRAM' (untested in 6.3).

*/

/** @pred socket(+ DOMAIN,- SOCKET)

Call socket/4 with TYPE bound to 'SOCK_STREAM' and PROTOCOL bound to 0.

*/

/** @pred socket_close(+ SOCKET)

Close socket SOCKET. Note that sockets used in socket_connect (that is, client sockets) should not be closed with socket_close, as they will be automatically closed when the corresponding stream is closed with close/1 or close/2.

*/

/** @pred socket_bind(+ SOCKET, ? PORT)

Interface to system call bind, as used for servers: bind socket to a port. Port information depends on the domain:

+ 'AF_UNIX'(+ _FILENAME_) (unsupported)
+ 'AF_FILE'(+ _FILENAME_)

use file name FILENAME for UNIX or local sockets.

+ 'AF_INET'(? _HOST_,?PORT)

If HOST is bound to an atom, bind to host HOST, otherwise if unbound bind to local host ( HOST remains unbound). If port PORT is bound to an integer, try to bind to the corresponding port. If variable PORT is unbound allow operating systems to choose a port number, which is unified with PORT.

*/

/** @pred socket_connect(+ SOCKET, + PORT, - STREAM)

Interface to system call connect, used for clients: connect socket SOCKET to PORT. The connection results in the read/write stream STREAM.

Port information depends on the domain:

+ 'AF_UNIX'(+ _FILENAME_)
+ 'AF_FILE'(+ _FILENAME_)

connect to socket at file FILENAME.

+ 'AF_INET'(+ _HOST_,+ _PORT_)

Connect to socket at host HOST and port PORT.

*/

/** @pred socket_listen(+ SOCKET, + LENGTH)

Interface to system call listen, used for servers to indicate willingness to wait for connections at socket SOCKET. The integer LENGTH gives the queue limit for incoming connections, and should be limited to 5 for portable applications. The socket must be of type SOCK_STREAM or SOCK_SEQPACKET.

*/

/** @pred socket_accept(+ SOCKET, - CLIENT, - STREAM)

Interface to system call accept, used for servers to wait for connections at socket SOCKET. The stream descriptor STREAM represents the resulting connection. If the socket belongs to the domain 'AF_INET', CLIENT unifies with an atom containing the IP address for the client in numbers and dots notation.

*/

/** @pred socket_accept(+ SOCKET, - STREAM)

Accept a connection but do not return client information.

*/

/** @pred socket_buffering(+ SOCKET, - MODE, - OLD, + NEW)

Set buffering for SOCKET in read or write MODE. OLD is unified with the previous status, and NEW receives the new status which may be one of unbuf or fullbuf.

*/

/** @pred socket_select(+ SOCKETS, - NEWSTREAMS, + TIMEOUT,

  • STREAMS, - READSTREAMS) [unsupported in YAP-6.3]

Interface to system call select, used for servers to wait for connection requests or for data at sockets. The variable SOCKETS is a list of form KEY-SOCKET, where KEY is an user-defined identifier and SOCKET is a socket descriptor. The variable TIMEOUT is either off, indicating execution will wait until something is available, or of the form SEC-USEC, where SEC and USEC give the seconds and microseconds before socket_select/5 returns. The variable SOCKETS is a list of form KEY-STREAM, where KEY is an user-defined identifier and STREAM is a stream descriptor

Execution of socket_select/5 unifies READSTREAMS from STREAMS with readable data, and NEWSTREAMS with a list of the form KEY-STREAM, where KEY was the key for a socket with pending data, and STREAM the stream descriptor resulting from accepting the connection.

*/

/** @pred current_host(? HOSTNAME)

Unify HOSTNAME with an atom representing the fully qualified hostname for the current host. Also succeeds if HOSTNAME is bound to the unqualified hostname.

*/

/** @pred hostname_address(? HOSTNAME,? IP_ADDRESS)

HOSTNAME is an host name and IP_ADDRESS its IP address in number and dots notation.

@} */

/** @defgroup Database Using the Clausal Data Base @ingroup YAPBuiltins @{

Predicates in YAP may be dynamic or static. By default, when consulting or reconsulting, predicates are assumed to be static: execution is faster and the code will probably use less space. Static predicates impose some restrictions: in general there can be no addition or removal of clauses for a procedure if it is being used in the current execution.

Dynamic predicates allow programmers to change the Clausal Data Base with the same flexibility as in C-Prolog. With dynamic predicates it is always possible to add or remove clauses during execution and the semantics will be the same as for C-Prolog. But the programmer should be aware of the fact that asserting or retracting are still expensive operations, and therefore he should try to avoid them whenever possible.

*/

/** @pred dynamic + P

Declares predicate P or list of predicates [ P1,..., Pn] as a dynamic predicate. P must be written in form: name/arity.

:- dynamic god/1.

a more convenient form can be used:

:- dynamic son/3, father/2, mother/2.

or, equivalently,

:- dynamic [son/3, father/2, mother/2].

Note:

a predicate is assumed to be dynamic when asserted before being defined.

*/

/** @pred dynamic_predicate(+ P,+ Semantics)

Declares predicate P or list of predicates [ P1,..., Pn] as a dynamic predicate following either logical or immediate semantics.

*/

/** @pred compile_predicates(: ListOfNameArity)

Compile a list of specified dynamic predicates (see dynamic/1 and assert/1 into normal static predicates. This call tells the Prolog environment the definition will not change anymore and further calls to assert/1 or retract/1 on the named predicates raise a permission error. This predicate is designed to deal with parts of the program that is generated at runtime but does not change during the remainder of the program execution.

@} */

/** @defgroup Modifying_the_Database Modification of the Data Base @ingroup YAPBuiltins @{

These predicates can be used either for static or for dynamic predicates:

*/

/** @pred assert(+ C)

Same as assertz/1. Adds clause C to the program. If the predicate is undefined, declare it as dynamic. New code should use assertz/1 for better portability.

Most Prolog systems only allow asserting clauses for dynamic predicates. This is also as specified in the ISO standard. YAP allows asserting clauses for static predicates, as long as the predicate is not in use and the language flag is cprolog. Note that this feature is deprecated, if you want to assert clauses for static procedures you should use assert_static/1.

*/

/** @pred asserta(+ C) is iso

Adds clause C to the beginning of the program. If the predicate is undefined, declare it as dynamic.

*/

/** @pred assertz(+ C) is iso

Adds clause C to the end of the program. If the predicate is undefined, declare it as dynamic.

Most Prolog systems only allow asserting clauses for dynamic predicates. This is also as specified in the ISO standard. YAP allows asserting clauses for static predicates. The current version of YAP supports this feature, but this feature is deprecated and support may go away in future versions.

*/

/** @pred abolish(+ PredSpec) is iso

Deletes the predicate given by PredSpec from the database. If PredSpec is an unbound variable, delete all predicates for the current module. The specification must include the name and arity, and it may include module information. Under iso language mode this built-in will only abolish dynamic procedures. Under other modes it will abolish any procedures.

*/

/** @pred abolish(+ P,+ N)

Deletes the predicate with name P and arity N. It will remove both static and dynamic predicates.

*/

/** @pred assert_static(: C)

Adds clause C to a static procedure. Asserting a static clause for a predicate while choice-points for the predicate are available has undefined results.

*/

/** @pred asserta_static(: C)

Adds clause C to the beginning of a static procedure.

*/

/** @pred assertz_static(: C)

Adds clause C to the end of a static procedure. Asserting a static clause for a predicate while choice-points for the predicate are available has undefined results.

The following predicates can be used for dynamic predicates and for static predicates, if source mode was on when they were compiled:

*/

/** @pred clause(+ H, B) is iso

A clause whose head matches H is searched for in the program. Its head and body are respectively unified with H and B. If the clause is a unit clause, B is unified with true.

This predicate is applicable to static procedures compiled with source active, and to all dynamic procedures.

*/

/** @pred clause(+ H, B,- R)

The same as clause/2, plus R is unified with the reference to the clause in the database. You can use instance/2 to access the reference's value. Note that you may not use erase/1 on the reference on static procedures.

*/

/** @pred nth_clause(+ H, I,- R)

Find the _I_th clause in the predicate defining H, and give a reference to the clause. Alternatively, if the reference R is given the head H is unified with a description of the predicate and I is bound to its position.

The following predicates can only be used for dynamic predicates:

*/

/** @pred retract(+ C) is iso

Erases the first clause in the program that matches C. This predicate may also be used for the static predicates that have been compiled when the source mode was on. For more information on source/0 ( (see Setting the Compiler)).

*/

/** @pred retractall(+ G) is iso

Retract all the clauses whose head matches the goal G. Goal G must be a call to a dynamic predicate.

@} */

/** @defgroup Looking_at_the_Database Looking at the Data Base @ingroup YAPBuiltins @{

*/

/** @pred listing

Lists in the current output stream all the clauses for which source code is available (these include all clauses for dynamic predicates and clauses for static predicates compiled when source mode was on).

*/

/** @pred listing(+ P)

Lists predicate P if its source code is available.

*/

/** @pred portray_clause(+ C)

Write clause C as if written by listing/0.

*/

/** @pred portray_clause(+ S,+ C)

Write clause C on stream S as if written by listing/0.

*/

/** @pred current_atom( A)

Checks whether A is a currently defined atom. It is used to find all currently defined atoms by backtracking.

*/

/** @pred current_predicate( F) is iso

F is the predicate indicator for a currently defined user or library predicate. F is of the form Na/Ar, where the atom Na is the name of the predicate, and Ar its arity.

*/

/** @pred current_predicate( A, P)

Defines the relation: P is a currently defined predicate whose name is the atom A.

*/

/** @pred system_predicate( A, P)

Defines the relation: P is a built-in predicate whose name is the atom A.

*/

/** @pred predicate_property( P, Prop) is iso

For the predicates obeying the specification P unify Prop with a property of P. These properties may be:

+ built_in 

true for built-in predicates, + dynamic true if the predicate is dynamic + static

true if the predicate is static + meta_predicate( M)

true if the predicate has a meta_predicate declaration M. + multifile

true if the predicate was declared to be multifile + imported_from( Mod)

true if the predicate was imported from module Mod. + exported

true if the predicate is exported in the current module. + public true if the predicate is public; note that all dynamic predicates are public. + tabled

true if the predicate is tabled; note that only static predicates can be tabled in YAP. + source (predicate_property flag)

true if source for the predicate is available. + number_of_clauses( ClauseCount)

Number of clauses in the predicate definition. Always one if external or built-in.

*/

/** @pred predicate_statistics( P, NCls, Sz, IndexSz)

Given predicate P, NCls is the number of clauses for P, Sz is the amount of space taken to store those clauses (in bytes), and IndexSz is the amount of space required to store indices to those clauses (in bytes).

*/

/** @pred predicate_erased_statistics( P, NCls, Sz, IndexSz)

Given predicate P, NCls is the number of erased clauses for P that could not be discarded yet, Sz is the amount of space taken to store those clauses (in bytes), and IndexSz is the amount of space required to store indices to those clauses (in bytes).

@} */

/** @defgroup Database_References Using Data Base References @ingroup YAPBuiltins @{

Data Base references are a fast way of accessing terms. The predicates erase/1 and instance/1 also apply to these references and may sometimes be used instead of retract/1 and clause/2.

*/

/** @pred assert(+ C,- R)

The same as assert(C) ( (see Modifying the Database)) but unifies R with the database reference that identifies the new clause, in a one-to-one way. Note that asserta/2 only works for dynamic predicates. If the predicate is undefined, it will automatically be declared dynamic.

*/

/** @pred asserta(+ C,- R)

The same as asserta(C) but unifying R with the database reference that identifies the new clause, in a one-to-one way. Note that asserta/2 only works for dynamic predicates. If the predicate is undefined, it will automatically be declared dynamic.

*/

/** @pred assertz(+ C,- R)

The same as assertz(C) but unifying R with the database reference that identifies the new clause, in a one-to-one way. Note that asserta/2 only works for dynamic predicates. If the predicate is undefined, it will automatically be declared dynamic.

*/

/** @pred retract(+ C,- R)

Erases from the program the clause C whose database reference is R. The predicate must be dynamic.

@} */

/** @defgroup Internal_Database Internal Data Base @ingroup YAPBuiltins @{

Some programs need global information for, e.g. counting or collecting data obtained by backtracking. As a rule, to keep this information, the internal data base should be used instead of asserting and retracting clauses (as most novice programmers do), . In YAP (as in some other Prolog systems) the internal data base (i.d.b. for short) is faster, needs less space and provides a better insulation of program and data than using asserted/retracted clauses. The i.d.b. is implemented as a set of terms, accessed by keys that unlikely what happens in (non-Prolog) data bases are not part of the term. Under each key a list of terms is kept. References are provided so that terms can be identified: each term in the i.d.b. has a unique reference (references are also available for clauses of dynamic predicates).

*/

/** @pred recorda(+ K, T,- R)

Makes term T the first record under key K and unifies R with its reference.

*/

/** @pred recordz(+ K, T,- R)

Makes term T the last record under key K and unifies R with its reference.

*/

/** @pred recorda_at(+ R0, T,- R)

Makes term T the record preceding record with reference R0, and unifies R with its reference.

*/

/** @pred recordz_at(+ R0, T,- R)

Makes term T the record following record with reference R0, and unifies R with its reference.

*/

/** @pred recordaifnot(+ K, T,- R)

If a term equal to T up to variable renaming is stored under key K fail. Otherwise, make term T the first record under key K and unify R with its reference.

*/

/** @pred recordzifnot(+ K, T,- R)

If a term equal to T up to variable renaming is stored under key K fail. Otherwise, make term T the first record under key K and unify R with its reference.

This predicate is YAP specific.

*/

/** @pred recorded(+ K, T, R)

Searches in the internal database under the key K, a term that unifies with T and whose reference matches R. This built-in may be used in one of two ways:

+ _K_ may be given, in this case the built-in will return all

elements of the internal data-base that match the key. + R may be given, if so returning the key and element that match the reference.

*/

/** @pred erase(+ R)

The term referred to by R is erased from the internal database. If reference R does not exist in the database, erase just fails.

*/

/** @pred erased(+ R)

Succeeds if the object whose database reference is R has been erased.

*/

/** @pred instance(+ R,- T)

If R refers to a clause or a recorded term, T is unified with its most general instance. If R refers to an unit clause C, then T is unified with _C_ :- true. When R is not a reference to an existing clause or to a recorded term, this goal fails.

*/

/** @pred eraseall(+ K)

All terms belonging to the key K are erased from the internal database. The predicate always succeeds.

*/

/** @pred current_key(? A,? K)

Defines the relation: K is a currently defined database key whose name is the atom A. It can be used to generate all the keys for the internal data-base.

*/

/** @pred nth_instance(? Key,? Index,? R)

Fetches the _Index_nth entry in the internal database under the key Key. Entries are numbered from one. If the key Key or the Index are bound, a reference is unified with R. Otherwise, the reference R must be given, and YAP will find the matching key and index.

*/

/** @pred nth_instance(? Key,? Index, T,? R)

Fetches the _Index_nth entry in the internal database under the key Key. Entries are numbered from one. If the key Key or the Index are bound, a reference is unified with R. Otherwise, the reference R must be given, and YAP will find the matching key and index.

*/

/** @pred key_statistics(+ K,- Entries,- Size,- IndexSize)

Returns several statistics for a key K. Currently, it says how many entries we have for that key, Entries, what is the total size spent on entries, Size, and what is the amount of space spent in indices.

*/

/** @pred key_statistics(+ K,- Entries,- TotalSize)

Returns several statistics for a key K. Currently, it says how many entries we have for that key, Entries, what is the total size spent on this key.

*/

/** @pred get_value(+ A,- V)

In YAP, atoms can be associated with constants. If one such association exists for atom A, unify the second argument with the constant. Otherwise, unify V with [].

This predicate is YAP specific.

*/

/** @pred set_value(+ A,+ C)

Associate atom A with constant C.

The set_value and get_value built-ins give a fast alternative to the internal data-base. This is a simple form of implementing a global counter.

       read_and_increment_counter(Value) :-
                get_value(counter, Value),
                Value1 is Value+1,
                set_value(counter, Value1).

This predicate is YAP specific.

There is a strong analogy between the i.d.b. and the way dynamic predicates are stored. In fact, the main i.d.b. predicates might be implemented using dynamic predicates:

recorda(X,T,R) :- asserta(idb(X,T),R).
recordz(X,T,R) :- assertz(idb(X,T),R).
recorded(X,T,R) :- clause(idb(X,T),R).

We can take advantage of this, the other way around, as it is quite easy to write a simple Prolog interpreter, using the i.d.b.:

asserta(G) :- recorda(interpreter,G,_).
assertz(G) :- recordz(interpreter,G,_).
retract(G) :- recorded(interpreter,G,R), !, erase(R).
call(V) :- var(V), !, fail.
call((H :- B)) :- !, recorded(interpreter,(H :- B),_), call(B).
call(G) :- recorded(interpreter,G,_).

In YAP, much attention has been given to the implementation of the i.d.b., especially to the problem of accelerating the access to terms kept in a large list under the same key. Besides using the key, YAP uses an internal lookup function, transparent to the user, to find only the terms that might unify. For instance, in a data base containing the terms

b
b(a)
c(d)
e(g)
b(X)
e(h)

stored under the key k/1, when executing the query

:- recorded(k(_),c(_),R).

recorded would proceed directly to the third term, spending almost the time as if a(X) or b(X) was being searched. The lookup function uses the functor of the term, and its first three arguments (when they exist). So, recorded(k(_),e(h),_) would go directly to the last term, while recorded(k(_),e(_),_) would find first the fourth term, and then, after backtracking, the last one.

This mechanism may be useful to implement a sort of hierarchy, where the functors of the terms (and eventually the first arguments) work as secondary keys.

In the YAP's i.d.b. an optimized representation is used for terms without free variables. This results in a faster retrieval of terms and better space usage. Whenever possible, avoid variables in terms in terms stored in the i.d.b.

@} */

/** @defgroup BlackBoard The Blackboard @ingroup YAPBuiltins @{

YAP implements a blackboard in the style of the SICStus Prolog blackboard. The blackboard uses the same underlying mechanism as the internal data-base but has several important differences:

+ It is module aware, in contrast to the internal data-base.
+ Keys can only be atoms or integers, and not compound terms.
+ A single term can be stored per key.
+ An atomic update operation is provided; this is useful for

parallelism.

*/

/** @pred bb_put(+ Key,? Term)

Store term table Term in the blackboard under key Key. If a previous term was stored under key Key it is simply forgotten.

*/

/** @pred bb_get(+ Key,? Term)

Unify Term with a term stored in the blackboard under key Key, or fail silently if no such term exists.

*/

/** @pred bb_delete(+ Key,? Term)

Delete any term stored in the blackboard under key Key and unify it with Term. Fail silently if no such term exists.

*/

/** @pred bb_update(+ Key,? Term,? New)

Atomically unify a term stored in the blackboard under key Key with Term, and if the unification succeeds replace it by New. Fail silently if no such term exists or if unification fails.

@} */

/** @defgroup Sets Collecting Solutions to a Goal @ingroup YAPBuiltins @{

When there are several solutions to a goal, if the user wants to collect all the solutions he may be led to use the data base, because backtracking will forget previous solutions.

YAP allows the programmer to choose from several system predicates instead of writing his own routines. findall/3 gives you the fastest, but crudest solution. The other built-in predicates post-process the result of the query in several different ways:

*/

/** @pred findall( T,+ G,- L) is iso

Unifies L with a list that contains all the instantiations of the term T satisfying the goal G.

With the following program:

a(2,1).
a(1,1).
a(2,2).

the answer to the query

findall(X,a(X,Y),L).

would be:

X = _32
Y = _33
L = [2,1,2];
no

*/

/** @pred findall( T,+ G,+ L,- L0)

Similar to findall/3, but appends all answers to list L0.

*/

/** @pred all( T,+ G,- L)

Similar to findall( _T_, _G_, _L_) but eliminate repeated elements. Thus, assuming the same clauses as in the above example, the reply to the query

all(X,a(X,Y),L).

would be:

X = _32
Y = _33
L = [2,1];
no

Note that all/3 will fail if no answers are found.

*/

/** @pred bagof( T,+ G,- L) is iso

For each set of possible instances of the free variables occurring in G but not in T, generates the list L of the instances of T satisfying G. Again, assuming the same clauses as in the examples above, the reply to the query

bagof(X,a(X,Y),L).

would be:
X = _32
Y = 1
L = [2,1];
X = _32
Y = 2
L = [2];
no

*/

/** @pred setof( X,+ P,- B) is iso

Similar to bagof( _T_, _G_, _L_) but sorts list L and keeping only one copy of each element. Again, assuming the same clauses as in the examples above, the reply to the query

setof(X,a(X,Y),L).

would be:

X = _32
Y = 1
L = [1,2];
X = _32
Y = 2
L = [2];
no

@} */

/** @defgroup Grammars Grammar Rules @ingroup YAPBuiltins @{

Grammar rules in Prolog are both a convenient way to express definite clause grammars and an extension of the well known context-free grammars.

A grammar rule is of the form:

head --> body

where both \a head and \a body are sequences of one or more items linked by the standard conjunction operator ','.

Items can be:

+ 

a non-terminal symbol may be either a complex term or an atom. + a terminal symbol may be any Prolog symbol. Terminals are written as Prolog lists. + an empty body is written as the empty list '[ ]'. + extra conditions may be inserted as Prolog procedure calls, by being written inside curly brackets '{' and '}'. + the left side of a rule consists of a nonterminal and an optional list of terminals. + alternatives may be stated in the right-hand side of the rule by using the disjunction operator ';'. + the cut and conditional symbol ('->') may be inserted in the right hand side of a grammar rule

Grammar related built-in predicates:

*/

/** @pred expand_term( T,- X)

This predicate is used by YAP for preprocessing each top level term read when consulting a file and before asserting or executing it. It rewrites a term T to a term X according to the following rules: first try term_expansion/2 in the current module, and then try to use the user defined predicate user:term_expansion/2. If this call fails then the translating process for DCG rules is applied, together with the arithmetic optimizer whenever the compilation of arithmetic expressions is in progress.

*/

/** @pred CurrentModule:term_expansion( T,- X), user:term_expansion( T,- X)

This user-defined predicate is called by expand_term/3 to preprocess all terms read when consulting a file. If it succeeds:

+ 

If X is of the form :- G or ?- G, it is processed as a directive. + If X is of the form '$source_location'( _File_, _Line_): _Clause_ it is processed as if from File and line Line.

+ 

If X is a list, all terms of the list are asserted or processed as directives. + The term X is asserted instead of T.

*/

/** @pred CurrentModule:goal_expansion(+ G,+ M,- NG), user:goal_expansion(+ G,+ M,- NG)

YAP now supports goal_expansion/3. This is an user-defined procedure that is called after term expansion when compiling or asserting goals for each sub-goal in a clause. The first argument is bound to the goal and the second to the module under which the goal G will execute. If goal_expansion/3 succeeds the new sub-goal NG will replace G and will be processed in the same way. If goal_expansion/3 fails the system will use the default rules.

*/

/** @pred phrase(+ P, L, R)

This predicate succeeds when the difference list _L_- _R_ is a phrase of type P.

*/

/** @pred phrase(+ P, L)

This predicate succeeds when L is a phrase of type P. The same as phrase(P,L,[]).

Both this predicate and the previous are used as a convenient way to start execution of grammar rules.

*/

/** @pred 'C'( S1, T, S2)

This predicate is used by the grammar rules compiler and is defined as 'C'([H|T],H,T).

@} */

/** @defgroup OS Access to Operating System Functionality @ingroup YAPBuiltins @{

The following built-in predicates allow access to underlying Operating System functionality:

*/

/** @pred cd(+ D)

Changes the current directory (on UNIX environments).

*/

/** @pred cd

Changes the current directory (on UNIX environments) to the user's home directory.

*/

/** @pred environ(+ E,- S)

Given an environment variable E this predicate unifies the second argument S with its value.

*/

/** @pred getcwd(- D)

Unify the current directory, represented as an atom, with the argument D.

*/

/** @pred pwd

Prints the current directory.

*/

/** @pred ls

Prints a list of all files in the current directory.

*/

/** @pred putenv(+ E,+ S)

Set environment variable E to the value S. If the environment variable E does not exist, create a new one. Both the environment variable and the value must be atoms.

*/

/** @pred rename(+ F,+ G)

Renames file F to G.

*/

/** @pred sh

Creates a new shell interaction.

*/

/** @pred system(+ S)

Passes command S to the Bourne shell (on UNIX environments) or the current command interpreter in WIN32 environments.

*/

/** @pred unix(+ S)

Access to Unix-like functionality:

+ argv/1

Return a list of arguments to the program. These are the arguments that follow a --, as in the usual Unix convention. + cd/0 Change to home directory. + cd/1 Change to given directory. Acceptable directory names are strings or atoms. + environ/2 If the first argument is an atom, unify the second argument with the value of the corresponding environment variable. + getcwd/1 Unify the first argument with an atom representing the current directory. + putenv/2 Set environment variable E to the value S. If the environment variable E does not exist, create a new one. Both the environment variable and the value must be atoms. + shell/1 Execute command under current shell. Acceptable commands are strings or atoms. + system/1 Execute command with /bin/sh. Acceptable commands are strings or atoms. + shell/0 Execute a new shell.

*/

/** @pred working_directory(- CurDir,? NextDir)

Fetch the current directory at CurDir. If NextDir is bound to an atom, make its value the current working directory.

*/

/** @pred alarm(+ Seconds,+ Callable,+ OldAlarm)

Arranges for YAP to be interrupted in Seconds seconds, or in [ Seconds| MicroSeconds]. When interrupted, YAP will execute Callable and then return to the previous execution. If Seconds is 0, no new alarm is scheduled. In any event, any previously set alarm is canceled.

The variable OldAlarm unifies with the number of seconds remaining until any previously scheduled alarm was due to be delivered, or with 0 if there was no previously scheduled alarm.

Note that execution of Callable will wait if YAP is executing built-in predicates, such as Input/Output operations.

The next example shows how alarm/3 can be used to implement a simple clock:

loop :- loop.

ticker :- write('.'), flush_output,
          get_value(tick, yes),
          alarm(1,ticker,_).

:- set_value(tick, yes), alarm(1,ticker,_), loop.

The clock, ticker, writes a dot and then checks the flag tick to see whether it can continue ticking. If so, it calls itself again. Note that there is no guarantee that the each dot corresponds a second: for instance, if the YAP is waiting for user input, ticker will wait until the user types the entry in.

The next example shows how alarm/3 can be used to guarantee that a certain procedure does not take longer than a certain amount of time:

loop :- loop.

:-   catch((alarm(10, throw(ball), _),loop),
        ball,
        format('Quota exhausted.~n',[])).

In this case after 10 seconds our loop is interrupted, ball is thrown, and the handler writes Quota exhausted. Execution then continues from the handler.

Note that in this case loop/0 always executes until the alarm is sent. Often, the code you are executing succeeds or fails before the alarm is actually delivered. In this case, you probably want to disable the alarm when you leave the procedure. The next procedure does exactly so:

once_with_alarm(Time,Goal,DoOnAlarm) :-
   catch(execute_once_with_alarm(Time, Goal), alarm, DoOnAlarm).

execute_once_with_alarm(Time, Goal) :-
        alarm(Time, alarm, _),
        ( call(Goal) -> alarm(0, alarm, _) ; alarm(0, alarm, _), fail).

The procedure once_with_alarm/3 has three arguments: the Time to wait before the alarm is sent; the Goal to execute; and the goal DoOnAlarm to execute if the alarm is sent. It uses catch/3 to handle the case the alarm is sent. Then it starts the alarm, calls the goal Goal, and disables the alarm on success or failure.

*/

/** @pred on_signal(+ Signal,? OldAction,+ Callable)

Set the interrupt handler for soft interrupt Signal to be Callable. OldAction is unified with the previous handler.

Only a subset of the software interrupts (signals) can have their handlers manipulated through on_signal/3. Their POSIX names, YAP names and default behavior is given below. The "YAP name" of the signal is the atom that is associated with each signal, and should be used as the first argument to on_signal/3. It is chosen so that it matches the signal's POSIX name.

on_signal/3 succeeds, unless when called with an invalid signal name or one that is not supported on this platform. No checks are made on the handler provided by the user.

+ sig_up (Hangup)

SIGHUP in Unix/Linux; Reconsult the initialization files ~/.yaprc, ~/.prologrc and ~/prolog.ini. + sig_usr1 and sig_usr2 (User signals) SIGUSR1 and SIGUSR2 in Unix/Linux; Print a message and halt.

A special case is made, where if Callable is bound to default, then the default handler is restored for that signal.

A call in the form on_signal( _S_, _H_, _H_) can be used to retrieve a signal's current handler without changing it.

It must be noted that although a signal can be received at all times, the handler is not executed while YAP is waiting for a query at the prompt. The signal will be, however, registered and dealt with as soon as the user makes a query.

Please also note, that neither POSIX Operating Systems nor YAP guarantee that the order of delivery and handling is going to correspond with the order of dispatch.

@} */

/** @defgroup Term_Modification Term Modification @ingroup YAPBuiltins @{

It is sometimes useful to change the value of instantiated variables. Although, this is against the spirit of logic programming, it is sometimes useful. As in other Prolog systems, YAP has several primitives that allow updating Prolog terms. Note that these primitives are also backtrackable.

The setarg/3 primitive allows updating any argument of a Prolog compound terms. The mutable family of predicates provides mutable variables. They should be used instead of setarg/3, as they allow the encapsulation of accesses to updatable variables. Their implementation can also be more efficient for long deterministic computations.

*/

/** @pred setarg(+ I,+ S,? T)

Set the value of the _I_th argument of term S to term T.

*/

/** @pred create_mutable(+ D,- M)

Create new mutable variable M with initial value D.

*/

/** @pred is_mutable(? D)

Holds if D is a mutable term.

*/

/** @pred get_mutable(? D,+ M)

Unify the current value of mutable term M with term D.

*/

/** @pred update_mutable(+ D,+ M)

Set the current value of mutable term M to term D.

@} */

/** @defgroup Global_Variables Global Variables @ingroup YAPBuiltins @{

Global variables are associations between names (atoms) and terms. They differ in various ways from storing information using assert/1 or recorda/3.

+ The value lives on the Prolog (global) stack. This implies that

lookup time is independent from the size of the term. This is particularly interesting for large data structures such as parsed XML documents or the CHR global constraint store.

+ They support both global assignment using nb_setval/2 and

backtrackable assignment using b_setval/2.

+ Only one value (which can be an arbitrary complex Prolog term)

can be associated to a variable at a time.

+ Their value cannot be shared among threads. Each thread has its own

namespace and values for global variables.

Currently global variables are scoped globally. We may consider module scoping in future versions. Both b_setval/2 and nb_setval/2 implicitly create a variable if the referenced name does not already refer to a variable.

Global variables may be initialised from directives to make them available during the program lifetime, but some considerations are necessary for saved-states and threads. Saved-states to not store global variables, which implies they have to be declared with initialization/1 to recreate them after loading the saved state. Each thread has its own set of global variables, starting with an empty set. Using thread_initialization/1 to define a global variable it will be defined, restored after reloading a saved state and created in all threads that are created after the registration. Finally, global variables can be initialised using the exception hook called exception/3. The latter technique is used by CHR.

*/

/** @pred b_setval(+ Name, + Value)

Associate the term Value with the atom Name or replaces the currently associated value with Value. If Name does not refer to an existing global variable a variable with initial value [] is created (the empty list). On backtracking the assignment is reversed.

*/

/** @pred b_getval(+ Name, - Value)

Get the value associated with the global variable Name and unify it with Value. Note that this unification may further instantiate the value of the global variable. If this is undesirable the normal precautions (double negation or copy_term/2) must be taken. The b_getval/2 predicate generates errors if Name is not an atom or the requested variable does not exist.

Notice that for compatibility with other systems Name must be already associated with a term: otherwise the system will generate an error.

*/

/** @pred nb_setval(+ Name, + Value)

Associates a copy of Value created with duplicate_term/2 with the atom Name. Note that this can be used to set an initial value other than [] prior to backtrackable assignment.

*/

/** @pred nb_getval(+ Name, - Value)

The nb_getval/2 predicate is a synonym for b_getval/2, introduced for compatibility and symmetry. As most scenarios will use a particular global variable either using non-backtrackable or backtrackable assignment, using nb_getval/2 can be used to document that the variable is used non-backtrackable.

*/

/** @pred nb_linkval(+ Name, + Value)

Associates the term Value with the atom Name without copying it. This is a fast special-purpose variation of nb_setval/2 intended for expert users only because the semantics on backtracking to a point before creating the link are poorly defined for compound terms. The principal term is always left untouched, but backtracking behaviour on arguments is undone if the original assignment was trailed and left alone otherwise, which implies that the history that created the term affects the behaviour on backtracking. Please consider the following example:

demo_nb_linkval :-
        T = nice(N),
        (   N = world,
            nb_linkval(myvar, T),
            fail
        ;   nb_getval(myvar, V),
            writeln(V)
        ).

*/

/** @pred nb_set_shared_val(+ Name, + Value)

Associates the term Value with the atom Name, but sharing non-backtrackable terms. This may be useful if you want to rewrite a global variable so that the new copy will survive backtracking, but you want to share structure with the previous term.

The next example shows the differences between the three built-ins:

?- nb_setval(a,a(_)),nb_getval(a,A),nb_setval(b,t(C,A)),nb_getval(b,B).
A = a(_A),
B = t(_B,a(_C)) ? 

?- nb_setval(a,a(_)),nb_getval(a,A),nb_set_shared_val(b,t(C,A)),nb_getval(b,B).

?- nb_setval(a,a(_)),nb_getval(a,A),nb_linkval(b,t(C,A)),nb_getval(b,B).
A = a(_A),
B = t(C,a(_A)) ?

*/

/** @pred nb_setarg(+{Arg], + Term, + Value)

Assigns the Arg-th argument of the compound term Term with the given Value as setarg/3, but on backtracking the assignment is not reversed. If Term is not atomic, it is duplicated using duplicate_term/2. This predicate uses the same technique as nb_setval/2. We therefore refer to the description of nb_setval/2 for details on non-backtrackable assignment of terms. This predicate is compatible to GNU-Prolog setarg(A,T,V,false), removing the type-restriction on Value. See also nb_linkarg/3. Below is an example for counting the number of solutions of a goal. Note that this implementation is thread-safe, reentrant and capable of handling exceptions. Realising these features with a traditional implementation based on assert/retract or flag/3 is much more complicated.

    succeeds_n_times(Goal, Times) :-
            Counter = counter(0),
            (   Goal,
                arg(1, Counter, N0),
                N is N0 + 1,
                nb_setarg(1, Counter, N),
                fail
            ;   arg(1, Counter, Times)
            ).

*/

/** @pred nb_set_shared_arg(+ Arg, + Term, + Value)

As nb_setarg/3, but like nb_linkval/2 it does not duplicate the global sub-terms in Value. Use with extreme care and consult the documentation of nb_linkval/2 before use.

*/

/** @pred nb_linkarg(+ Arg, + Term, + Value)

As nb_setarg/3, but like nb_linkval/2 it does not duplicate Value. Use with extreme care and consult the documentation of nb_linkval/2 before use.

*/

/** @pred nb_current(? Name, ? Value)

Enumerate all defined variables with their value. The order of enumeration is undefined.

*/

/** @pred nb_delete(+ Name)

Delete the named global variable.

Global variables have been introduced by various Prolog implementations recently. We follow the implementation of them in SWI-Prolog, itself based on hProlog by Bart Demoen.

GNU-Prolog provides a rich set of global variables, including arrays. Arrays can be implemented easily in YAP and SWI-Prolog using functor/3 and setarg/3 due to the unrestricted arity of compound terms.

@} */

/** @defgroup Profiling Profiling Prolog Programs @ingroup YAPBuiltins @{

YAP includes two profilers. The count profiler keeps information on the number of times a predicate was called. This information can be used to detect what are the most commonly called predicates in the program. The count profiler can be compiled by setting YAP's flag profiling to on. The time-profiler is a gprof profiler, and counts how many ticks are being spent on specific predicates, or on other system functions such as internal data-base accesses or garbage collects.

The YAP profiling sub-system is currently under development. Functionality for this sub-system will increase with newer implementation.

@} */

/** @defgroup The_Count_Profiler The Count Profiler @ingroup YAPBuiltins @{

Notes:

The count profiler works by incrementing counters at procedure entry or backtracking. It provides exact information:

+ Profiling works for both static and dynamic predicates.
+ Currently only information on entries and retries to a predicate

are maintained. This may change in the future. + As an example, the following user-level program gives a list of the most often called procedures in a program. The procedure list_profile shows all procedures, irrespective of module, and the procedure list_profile/1 shows the procedures being used in a specific module.

list_profile :-
        % get number of calls for each profiled procedure
        setof(D-[M:P|D1],(current_module(M),profile_data(M:P,calls,D),profile_data(M:P,retries,D1)),LP),
        % output so that the most often called
        % predicates will come last:
        write_profile_data(LP).

list_profile(Module) :-
        % get number of calls for each profiled procedure
        setof(D-[Module:P|D1],(profile_data(Module:P,calls,D),profile_data(Module:P,retries,D1)),LP),
        % output so that the most often called
        % predicates will come last:
        write_profile_data(LP).

write_profile_data([]).
write_profile_data([D-[M:P|R]|SLP]) :-
        % swap the two calls if you want the most often
        %  called predicates first.
        format('~a:~w: ~32+~t~d~12+~t~d~12+~n', [M,P,D,R]),
        write_profile_data(SLP).

These are the current predicates to access and clear profiling data:

*/

/** @pred profile_data(? Na/Ar, ? Parameter, - Data)

Give current profile data on Parameter for a predicate described by the predicate indicator Na/Ar. If any of Na/Ar or Parameter are unbound, backtrack through all profiled predicates or stored parameters. Current parameters are:

+ calls

Number of times a procedure was called.

+ retries

Number of times a call to the procedure was backtracked to and retried.

+ profile_reset 

Reset all profiling information.

@} */

/** @defgroup Tick_Profiler Tick Profiler @ingroup YAPBuiltins @{

The tick profiler works by interrupting the Prolog code every so often and checking at each point the code was. The profiler must be able to retrace the state of the abstract machine at every moment. The major advantage of this approach is that it gives the actual amount of time being spent per procedure, or whether garbage collection dominates execution time. The major drawback is that tracking down the state of the abstract machine may take significant time, and in the worst case may slow down the whole execution.

The following procedures are available:

+ profinit 

Initialise the data-structures for the profiler. Unnecessary for dynamic profiler.

+ profon 

Start profiling.

+ profoff 

Stop profiling.

*/

/** @pred showprofres

Show profiling info.

*/

/** @pred showprofres( N)

Show profiling info for the top-most N predicates.

The showprofres/0 and showprofres/1 predicates call a user-defined multifile hook predicate, user:prolog_predicate_name/2, that can be used for converting a possibly explicitly-qualified callable term into an atom that will used when printing the profiling information.

@} */

/** @defgroup Call_Counting Counting Calls @ingroup YAPBuiltins @{

Predicates compiled with YAP's flag call_counting set to on update counters on the numbers of calls and of retries. Counters are actually decreasing counters, so that they can be used as timers. Three counters are available:

+ `calls`: number of predicate calls since execution started or since

system was reset; + retries: number of retries for predicates called since execution started or since counters were reset; + calls_and_retries: count both on predicate calls and retries.

These counters can be used to find out how many calls a certain goal takes to execute. They can also be used as timers.

The code for the call counters piggybacks on the profiling code. Therefore, activating the call counters also activates the profiling counters.

These are the predicates that access and manipulate the call counters:

*/

/** @pred call_count_data(- Calls, - Retries, - CallsAndRetries)

Give current call count data. The first argument gives the current value for the Calls counter, next the Retries counter, and last the CallsAndRetries counter.

+ call_count_reset 

Reset call count counters. All timers are also reset.

  • /** @pred l_count(? CallsMax, ? RetriesMax, ? CallsAndRetriesMax)

    Set call count counter as timers. YAP will generate an exception if one of the instantiated call counters decreases to 0. YAP will ignore unbound arguments:

    + _CallsMax_: throw the exception `call_counter` when the
    

    counter calls reaches 0; + RetriesMax: throw the exception retry_counter when the counter retries reaches 0; + CallsAndRetriesMax: throw the exception call_and_retry_counter when the counter calls_and_retries reaches 0.

    Next, we show a simple example of how to use call counters:

       ?- yap_flag(call_counting,on), [-user]. l :- l. end_of_file. yap_flag(call_counting,off).
    
    yes
    
    yes
       ?- catch((call_count(10000,_,_),l),call_counter,format("limit_exceeded.~n",[])).
    
    limit_exceeded.
    
    yes
    

    Notice that we first compile the looping predicate l/0 with call_counting on. Next, we catch/3 to handle an exception when l/0 performs more than 10000 reductions.

    @} */

    /** @defgroup Arrays Arrays @ingroup YAPBuiltins @{

    The YAP system includes experimental support for arrays. The support is enabled with the option YAP_ARRAYS.

    There are two very distinct forms of arrays in YAP. The dynamic arrays are a different way to access compound terms created during the execution. Like any other terms, any bindings to these terms and eventually the terms themselves will be destroyed during backtracking. Our goal in supporting dynamic arrays is twofold. First, they provide an alternative to the standard arg/3 built-in. Second, because dynamic arrays may have name that are globally visible, a dynamic array can be visible from any point in the program. In more detail, the clause

    g(X) :- array_element(a,2,X).
    

    will succeed as long as the programmer has used the built-in array/2 to create an array term with at least 3 elements in the current environment, and the array was associated with the name a. The element X is a Prolog term, so one can bind it and any such bindings will be undone when backtracking. Note that dynamic arrays do not have a type: each element may be any Prolog term.

    The static arrays are an extension of the database. They provide a compact way for manipulating data-structures formed by characters, integers, or floats imperatively. They can also be used to provide two-way communication between YAP and external programs through shared memory.

    In order to efficiently manage space elements in a static array must have a type. Currently, elements of static arrays in YAP should have one of the following predefined types:

    + `byte`: an 8-bit signed character.
    + `unsigned_byte`: an 8-bit unsigned character.
    + `int`: Prolog integers. Size would be the natural size for
    

    the machine's architecture. + float: Prolog floating point number. Size would be equivalent to a double in C. + atom: a Prolog atom. + dbref: an internal database reference. + term: a generic Prolog term. Note that this will term will not be stored in the array itself, but instead will be stored in the Prolog internal database.

    Arrays may be named or anonymous. Most arrays will be named, that is associated with an atom that will be used to find the array. Anonymous arrays do not have a name, and they are only of interest if the TERM_EXTENSIONS compilation flag is enabled. In this case, the unification and parser are extended to replace occurrences of Prolog terms of the form X[I] by run-time calls to array_element/3, so that one can use array references instead of extra calls to arg/3. As an example:

    g(X,Y,Z,I,J) :- X[I] is Y[J]+Z[I].
    

    should give the same results as:

    G(X,Y,Z,I,J) :-
            array_element(X,I,E1),
            array_element(Y,J,E2),  
            array_element(Z,I,E3),  
            E1 is E2+E3.
    

    Note that the only limitation on array size are the stack size for dynamic arrays; and, the heap size for static (not memory mapped) arrays. Memory mapped arrays are limited by available space in the file system and in the virtual memory space.

    The following predicates manipulate arrays:

    */

    /** @pred array(+ Name, + Size)

    Creates a new dynamic array. The Size must evaluate to an integer. The Name may be either an atom (named array) or an unbound variable (anonymous array).

    Dynamic arrays work as standard compound terms, hence space for the array is recovered automatically on backtracking.

    */

    /** @pred static_array(+ Name, + Size, + Type)

    Create a new static array with name Name. Note that the Name must be an atom (named array). The Size must evaluate to an integer. The Type must be bound to one of types mentioned previously.

    */

    /** @pred reset_static_array(+ Name)

    Reset static array with name Name to its initial value.

    */

    /** @pred static_array_location(+ Name, - Ptr)

    Give the location for a static array with name Name.

    */

    /** @pred static_array_properties(? Name, ? Size, ? Type)

    Show the properties size and type of a static array with name Name. Can also be used to enumerate all current static arrays.

    This built-in will silently fail if the there is no static array with that name.

    */

    /** @pred static_array_to_term(? Name, ? Term)

    Convert a static array with name Name to a compound term of name Name.

    This built-in will silently fail if the there is no static array with that name.

    */

    /** @pred mmapped_array(+ Name, + Size, + Type, + File)

    Similar to static_array/3, but the array is memory mapped to file File. This means that the array is initialized from the file, and that any changes to the array will also be stored in the file.

    This built-in is only available in operating systems that support the system call mmap. Moreover, mmapped arrays do not store generic terms (type term).

    */

    /** @pred close_static_array(+ Name)

    Close an existing static array of name Name. The Name must be an atom (named array). Space for the array will be recovered and further accesses to the array will return an error.

    */

    /** @pred resize_static_array(+ Name, - OldSize, + NewSize)

    Expand or reduce a static array, The Size must evaluate to an integer. The Name must be an atom (named array). The Type must be bound to one of int, dbref, float or atom.

    Note that if the array is a mmapped array the size of the mmapped file will be actually adjusted to correspond to the size of the array.

    */

    /** @pred array_element(+ Name, + Index, ? Element)

    Unify Element with Name[ Index]. It works for both static and dynamic arrays, but it is read-only for static arrays, while it can be used to unify with an element of a dynamic array.

    */

    /** @pred update_array(+ Name, + Index, ? Value)

    Attribute value Value to Name[ Index]. Type restrictions must be respected for static arrays. This operation is available for dynamic arrays if MULTI_ASSIGNMENT_VARIABLES is enabled (true by default). Backtracking undoes update_array/3 for dynamic arrays, but not for static arrays.

    Note that update_array/3 actually uses setarg/3 to update elements of dynamic arrays, and setarg/3 spends an extra cell for every update. For intensive operations we suggest it may be less expensive to unify each element of the array with a mutable terms and to use the operations on mutable terms.

    */

    /** @pred add_to_array_element(+ Name, + Index, , + Number, ? NewValue)

    Add Number Name[ Index] and unify NewValue with the incremented value. Observe that Name[ Index] must be an number. If Name is a static array the type of the array must be int or float. If the type of the array is int you only may add integers, if it is float you may add integers or floats. If Name corresponds to a dynamic array the array element must have been previously bound to a number and Number can be any kind of number.

    The add_to_array_element/3 built-in actually uses setarg/3 to update elements of dynamic arrays. For intensive operations we suggest it may be less expensive to unify each element of the array with a mutable terms and to use the operations on mutable terms.

    @} */

    /** @defgroup Preds Predicate Information @ingroup YAPBuiltins @{

    Built-ins that return information on the current predicates and modules:

    */

    /** @pred current_module( M)

    Succeeds if M are defined modules. A module is defined as soon as some predicate defined in the module is loaded, as soon as a goal in the module is called, or as soon as it becomes the current type-in module.

    */

    /** @pred current_module( M, F)

    Succeeds if M are current modules associated to the file F.

    @} */

    /** @defgroup Misc Miscellaneous @ingroup YAPBuiltins @{

    */

    /** @pred statistics/0

    Send to the current user error stream general information on space used and time spent by the system.

    ?- statistics.
    memory (total)        4784124 bytes
       program space      3055616 bytes:    1392224 in use,      1663392 free
                                                                 2228132  max
       stack space        1531904 bytes:        464 in use,      1531440 free
         global stack:                           96 in use,       616684  max
          local stack:                          368 in use,       546208  max
       trail stack         196604 bytes:          8 in use,       196596 free
    
           0.010 sec. for 5 code, 2 stack, and 1 trail space overflows
           0.130 sec. for 3 garbage collections which collected 421000 bytes
           0.000 sec. for 0 atom garbage collections which collected 0 bytes
           0.880 sec. runtime
           1.020 sec. cputime
          25.055 sec. elapsed time
    
    

    The example shows how much memory the system spends. Memory is divided into Program Space, Stack Space and Trail. In the example we have 3MB allocated for program spaces, with less than half being actually used. YAP also shows the maximum amount of heap space having been used which was over 2MB.

    The stack space is divided into two stacks which grow against each other. We are in the top level so very little stack is being used. On the other hand, the system did use a lot of global and local stack during the previous execution (we refer the reader to a WAM tutorial in order to understand what are the global and local stacks).

    YAP also shows information on how many memory overflows and garbage collections the system executed, and statistics on total execution time. Cputime includes all running time, runtime excludes garbage collection and stack overflow time.

    */

    /** @pred statistics(? Param,- Info)

    Gives statistical information on the system parameter given by first argument:

    + atoms 
    

    [ _NumberOfAtoms_, _SpaceUsedBy Atoms_]

    This gives the total number of atoms NumberOfAtoms and how much space they require in bytes, SpaceUsedBy Atoms.

    + cputime 
    

    [ _Time since Boot_, _Time From Last Call to Cputime_]

    This gives the total cputime in milliseconds spent executing Prolog code, garbage collection and stack shifts time included.

    + dynamic_code 
    

    [ _Clause Size_, _Index Size_, _Tree Index Size_, _Choice Point Instructions Size_, _Expansion Nodes Size_, _Index Switch Size_]

    Size of static code in YAP in bytes: Clause Size, the number of bytes allocated for clauses, plus Index Size, the number of bytes spent in the indexing code. The indexing code is divided into main tree, Tree Index Size, tables that implement choice-point manipulation, Choice xsPoint Instructions Size, tables that cache clauses for future expansion of the index tree, Expansion Nodes Size, and tables such as hash tables that select according to value, Index Switch Size.

    + garbage_collection 
    

    [ _Number of GCs_, _Total Global Recovered_, _Total Time Spent_]

    Number of garbage collections, amount of space recovered in kbytes, and total time spent doing garbage collection in milliseconds. More detailed information is available using yap_flag(gc_trace,verbose).

    + global_stack 
    

    [ _Global Stack Used_, _Execution Stack Free_]

    Space in kbytes currently used in the global stack, and space available for expansion by the local and global stacks.

    + local_stack 
    

    [ _Local Stack Used_, _Execution Stack Free_]

    Space in kbytes currently used in the local stack, and space available for expansion by the local and global stacks.

    + heap 
    

    [ _Heap Used_, _Heap Free_]

    Total space in kbytes not recoverable in backtracking. It includes the program code, internal data base, and, atom symbol table.

    + program 
    

    [ _Program Space Used_, _Program Space Free_]

    Equivalent to heap.

    + runtime 
    

    [ _Time since Boot_, _Time From Last Call to Runtime_]

    This gives the total cputime in milliseconds spent executing Prolog code, not including garbage collections and stack shifts. Note that until YAP4.1.2 the runtime statistics would return time spent on garbage collection and stack shifting.

    + stack_shifts 
    

    [ _Number of Heap Shifts_, _Number of Stack Shifts_, _Number of Trail Shifts_]

    Number of times YAP had to expand the heap, the stacks, or the trail. More detailed information is available using yap_flag(gc_trace,verbose).

    + static_code 
    

    [ _Clause Size_, _Index Size_, _Tree Index Size_, _Expansion Nodes Size_, _Index Switch Size_]

    Size of static code in YAP in bytes: Clause Size, the number of bytes allocated for clauses, plus Index Size, the number of bytes spent in the indexing code. The indexing code is divided into a main tree, Tree Index Size, table that cache clauses for future expansion of the index tree, Expansion Nodes Size, and and tables such as hash tables that select according to value, Index Switch Size.

    + trail 
    

    [ _Trail Used_, _Trail Free_]

    Space in kbytes currently being used and still available for the trail.

    + walltime 
    

    [ _Time since Boot_, _Time From Last Call to Walltime_]

    This gives the clock time in milliseconds since starting Prolog.

    */

    /** @pred time(: Goal)

    Prints the CPU time and the wall time for the execution of Goal. Possible choice-points of Goal are removed. Based on the SWI-Prolog definition (minus reporting the number of inferences, which YAP currently does not support).

    */

    /** @pred yap_flag(? Param,? Value)

    Set or read system properties for Param:

    + argv 
    

    Read-only flag. It unifies with a list of atoms that gives the arguments to YAP after --.

    + agc_margin 
    

    An integer: if this amount of atoms has been created since the last atom-garbage collection, perform atom garbage collection at the first opportunity. Initial value is 10,000. May be changed. A value of 0 (zero) disables atom garbage collection.

    + associate 
    

    Read-write flag telling a suffix for files associated to Prolog sources. It is yap by default.

    + bounded is iso 
    

    Read-only flag telling whether integers are bounded. The value depends on whether YAP uses the GMP library or not.

    + profiling 
    

    If off (default) do not compile call counting information for procedures. If on compile predicates so that they calls and retries to the predicate may be counted. Profiling data can be read through the call_count_data/3 built-in.

    + char_conversion is iso
    

    Writable flag telling whether a character conversion table is used when reading terms. The default value for this flag is off except in sicstus and iso language modes, where it is on.

    + character_escapes is iso 
    

    Writable flag telling whether a character escapes are enables, true, or disabled, false. The default value for this flag is on.

    + debug is iso 
    

    If Value is unbound, tell whether debugging is true or false. If Value is bound to true enable debugging, and if it is bound to false disable debugging.

    + debugger_print_options 
    

    If bound, set the argument to the write_term/3 options the debugger uses to write terms. If unbound, show the current options.

    + dialect 
    

    Read-only flag that always returns yap.

    + discontiguous_warnings 
    

    If Value is unbound, tell whether warnings for discontiguous predicates are on or off. If Value is bound to on enable these warnings, and if it is bound to off disable them. The default for YAP is off, unless we are in sicstus or iso mode.

    + dollar_as_lower_case 
    

    If off (default) consider the character '$' a control character, if on consider '$' a lower case character.

    + double_quotes is iso 
    

    If Value is unbound, tell whether a double quoted list of characters token is converted to a list of atoms, chars, to a list of integers, codes, or to a single atom, atom. If Value is bound, set to the corresponding behavior. The default value is codes.

    + executable 
    

    Read-only flag. It unifies with an atom that gives the original program path.

    + fast 
    

    If on allow fast machine code, if off (default) disable it. Only available in experimental implementations.

    + fileerrors
    

    If on fileerrors is on, if off (default) fileerrors is disabled.

    + float_format 
    

    C-library printf() format specification used by write/1 and friends to determine how floating point numbers are printed. The default is %.15g. The specified value is passed to printf() without further checking. For example, if you want less digits printed, %g will print all floats using 6 digits instead of the default 15.

    + gc
    

    If on allow garbage collection (default), if off disable it.

    + gc_margin 
    

    Set or show the minimum free stack before starting garbage collection. The default depends on total stack size.

    + gc_trace 
    

    If off (default) do not show information on garbage collection and stack shifts, if on inform when a garbage collection or stack shift happened, if verbose give detailed information on garbage collection and stack shifts. Last, if very_verbose give detailed information on data-structures found during the garbage collection process, namely, on choice-points.

    + generate_debugging_info 
    

    If true (default) generate debugging information for procedures, including source mode. If false predicates no information is generated, although debugging is still possible, and source mode is disabled.

    + host_type 
    

    Return configure system information, including the machine-id for which YAP was compiled and Operating System information.

    + index 
    

    If on allow indexing (default), if off disable it, if single allow on first argument only.

    + index_sub_term_search_depth 
    

    Maximum bound on searching sub-terms for indexing, if 0 (default) no bound.

    + informational_messages 
    

    If on allow printing of informational messages, such as the ones that are printed when consulting. If off disable printing these messages. It is on by default except if YAP is booted with the -L flag.

    + integer_rounding_function is iso 
    

    Read-only flag telling the rounding function used for integers. Takes the value toward_zero for the current version of YAP.

    + language 
    

    Choose whether YAP is closer to C-Prolog, cprolog, iso-prolog, iso or SICStus Prolog, sicstus. The current default is cprolog. This flag affects update semantics, leashing mode, style checking, handling calls to undefined procedures, how directives are interpreted, when to use dynamic, character escapes, and how files are consulted.

    + max_arity is iso 
    

    Read-only flag telling the maximum arity of a functor. Takes the value unbounded for the current version of YAP.

    + max_integer is iso 
    

    Read-only flag telling the maximum integer in the implementation. Depends on machine and Operating System architecture, and on whether YAP uses the GMP multi-precision library. If bounded is false, requests for max_integer will fail.

    + max_tagged_integer  
    

    Read-only flag telling the maximum integer we can store as a single word. Depends on machine and Operating System architecture. It can be used to find the word size of the current machine.

    + min_integer is iso 
    

    Read-only flag telling the minimum integer in the implementation. Depends on machine and Operating System architecture, and on whether YAP uses the GMP multi-precision library. If bounded is false, requests for min_integer will fail.

    + min_tagged_integer  
    

    Read-only flag telling the minimum integer we can store as a single word. Depends on machine and Operating System architecture.

    + n_of_integer_keys_in_bb 
    

    Read or set the size of the hash table that is used for looking up the blackboard when the key is an integer.

    + occurs_check 
    

    Current read-only and set to false.

    + n_of_integer_keys_in_db 
    

    Read or set the size of the hash table that is used for looking up the internal data-base when the key is an integer.

    + open_expands_filename 
    

    If true the open/3 builtin performs filename-expansion before opening a file (SICStus Prolog like). If false it does not (SWI-Prolog like).

    + open_shared_object 
    

    If true, open_shared_object/2 and friends are implemented, providing access to shared libraries (.so files) or to dynamic link libraries (.DLL files).

    + profiling 
    

    If off (default) do not compile profiling information for procedures. If on compile predicates so that they will output profiling information. Profiling data can be read through the profile_data/3 built-in.

    + prompt_alternatives_on(atom, changeable) 
    

    SWI-Compatible option, determines prompting for alternatives in the Prolog toplevel. Default is groundness, YAP prompts for alternatives if and only if the query contains variables. The alternative, default in SWI-Prolog is determinism which implies the system prompts for alternatives if the goal succeeded while leaving choicepoints.

    + redefine_warnings 
    

    If Value is unbound, tell whether warnings for procedures defined in several different files are on or off. If Value is bound to on enable these warnings, and if it is bound to off disable them. The default for YAP is off, unless we are in sicstus or iso mode.

    + shared_object_search_path 
    

    Name of the environment variable used by the system to search for shared objects.

    + shared_object_extension 
    

    Suffix associated with loadable code.

    + single_var_warnings 
    

    If Value is unbound, tell whether warnings for singleton variables are on or off. If Value is bound to on enable these warnings, and if it is bound to off disable them. The default for YAP is off, unless we are in sicstus or iso mode.

    + strict_iso 
    

    If Value is unbound, tell whether strict ISO compatibility mode is on or off. If Value is bound to on set language mode to iso and enable strict mode. If Value is bound to off disable strict mode, and keep the current language mode. The default for YAP is off.

    Under strict ISO Prolog mode all calls to non-ISO built-ins generate an error. Compilation of clauses that would call non-ISO built-ins will also generate errors. Pre-processing for grammar rules is also disabled. Module expansion is still performed.

    Arguably, ISO Prolog does not provide all the functionality required from a modern Prolog system. Moreover, because most Prolog implementations do not fully implement the standard and because the standard itself gives the implementor latitude in a few important questions, such as the unification algorithm and maximum size for numbers there is no guarantee that programs compliant with this mode will work the same way in every Prolog and in every platform. We thus believe this mode is mostly useful when investigating how a program depends on a Prolog's platform specific features.

    + stack_dump_on_error 
    

    If on show a stack dump when YAP finds an error. The default is off.

    + syntax_errors
    

    Control action to be taken after syntax errors while executing read/1, read/2, or read_term/3:

    + dec10
    

    Report the syntax error and retry reading the term.

    + fail
    

    Report the syntax error and fail (default).

    + error
    

    Report the syntax error and generate an error.

    + quiet
    

    Just fail

    + system_options 
    

    This read only flag tells which options were used to compile YAP. Currently it informs whether the system supports big_numbers, coroutining, depth_limit, low_level_tracer, or-parallelism, rational_trees, readline, tabling, threads, or the wam_profiler.

    + tabling_mode
    

    Sets or reads the tabling mode for all tabled predicates. Please (see Tabling) for the list of options.

    + to_chars_mode 
    

    Define whether YAP should follow quintus-like semantics for the atom_chars/1 or number_chars/1 built-in, or whether it should follow the ISO standard (iso option).

    + toplevel_hook 
    

    +If bound, set the argument to a goal to be executed before entering the top-level. If unbound show the current goal or true if none is presented. Only the first solution is considered and the goal is not backtracked into.

    + toplevel_print_options 
    

    +If bound, set the argument to the write_term/3 options used to write terms from the top-level. If unbound, show the current options.

    + typein_module 
    

    If bound, set the current working or type-in module to the argument, which must be an atom. If unbound, unify the argument with the current working module.

    + unix
    

    Read-only Boolean flag that unifies with true if YAP is running on an Unix system. Defined if the C-compiler used to compile this version of YAP either defines __unix__ or unix.

    + unknown is iso
    

    Corresponds to calling the unknown/2 built-in. Possible values are error, fail, and warning.

    + update_semantics 
    

    Define whether YAP should follow immediate update semantics, as in C-Prolog (default), logical update semantics, as in Quintus Prolog, SICStus Prolog, or in the ISO standard. There is also an intermediate mode, logical_assert, where dynamic procedures follow logical semantics but the internal data base still follows immediate semantics.

    + user_error 
    

    If the second argument is bound to a stream, set user_error to this stream. If the second argument is unbound, unify the argument with the current user_error stream.

    By default, the user_error stream is set to a stream corresponding to the Unix stderr stream.

    The next example shows how to use this flag:

       ?- open( '/dev/null', append, Error,
               [alias(mauri_tripa)] ).
    
    Error = '$stream'(3) ? ;
    
    no
       ?- set_prolog_flag(user_error, mauri_tripa).
    
    close(mauri_tripa).
    
    yes
       ?- 
    

    We execute three commands. First, we open a stream in write mode and give it an alias, in this case mauri_tripa. Next, we set user_error to the stream via the alias. Note that after we did so prompts from the system were redirected to the stream mauri_tripa. Last, we close the stream. At this point, YAP automatically redirects the user_error alias to the original stderr.

    + user_flags 
    

    Define the behaviour of set_prolog_flag/2 if the flag is not known. Values are silent, warning and error. The first two create the flag on-the-fly, with warning printing a message. The value error is consistent with ISO: it raises an existence error and does not create the flag. See also create_prolog_flag/3. The default iserror, and developers are encouraged to use create_prolog_flag/3 to create flags for their library.

    + user_input 
    

    If the second argument is bound to a stream, set user_input to this stream. If the second argument is unbound, unify the argument with the current user_input stream.

    By default, the user_input stream is set to a stream corresponding to the Unix stdin stream.

    + user_output 
    

    If the second argument is bound to a stream, set user_output to this stream. If the second argument is unbound, unify the argument with the current user_output stream.

    By default, the user_output stream is set to a stream corresponding to the Unix stdout stream.

    + verbose 
    

    If normal allow printing of informational and banner messages, such as the ones that are printed when consulting. If silent disable printing these messages. It is normal by default except if YAP is booted with the -q or -L flag.

    + verbose_load 
    

    If true allow printing of informational messages when consulting files. If false disable printing these messages. It is normal by default except if YAP is booted with the -L flag.

    + version 
    

    Read-only flag that returns an atom with the current version of YAP.

    + version_data 
    

    Read-only flag that reads a term of the form yap( Major, Minor, Patch, Undefined), where Major is the major version, Minor is the minor version, and Patch is the patch number.

    + windows 
    

    Read-only boolean flag that unifies with tr true if YAP is running on an Windows machine.

    + write_strings 
    

    Writable flag telling whether the system should write lists of integers that are writable character codes using the list notation. It is on if enables or off if disabled. The default value for this flag is off.

    + max_workers 
    

    Read-only flag telling the maximum number of parallel processes.

    + max_threads 
    

    Read-only flag telling the maximum number of Prolog threads that can be created.

    */

    /** @pred current_prolog_flag(? Flag,- Value) is iso

    Obtain the value for a YAP Prolog flag. Equivalent to calling yap_flag/2 with the second argument unbound, and unifying the returned second argument with Value.

    */

    /** @pred prolog_flag(? Flag,- OldValue,+ NewValue)

    Obtain the value for a YAP Prolog flag and then set it to a new value. Equivalent to first calling current_prolog_flag/2 with the second argument OldValue unbound and then calling set_prolog_flag/2 with the third argument NewValue.

    */

    /** @pred set_prolog_flag(+ Flag,+ Value) is iso

    Set the value for YAP Prolog flag Flag. Equivalent to calling yap_flag/2 with both arguments bound.

    */

    /** @pred create_prolog_flag(+ Flag,+ Value,+ Options)

    Create a new YAP Prolog flag. Options include type(+Type) and access(+Access) with Access one of read_only or read_write and Type one of boolean, integer, float, atom and term (that is, no type).

    */

    /** @pred op(+ P,+ T,+ A) is iso

    Defines the operator A or the list of operators A with type T (which must be one of xfx, xfy,yfx, xf, yf, fx or fy) and precedence P (see appendix iv for a list of predefined operators).

    Note that if there is a preexisting operator with the same name and type, this operator will be discarded. Also, ',' may not be defined as an operator, and it is not allowed to have the same for an infix and a postfix operator.

    */

    /** @pred current_op( P, T, F) is iso

    Defines the relation: P is a currently defined operator of type T and precedence P.

    */

    /** @pred prompt(- A,+ B)

    Changes YAP input prompt from A to B.

    */

    /** @pred initialization

    Execute the goals defined by initialization/1. Only the first answer is considered.

    */

    /** @pred prolog_initialization( G)

    Add a goal to be executed on system initialization. This is compatible with SICStus Prolog's initialization/1.

    */

    /** @pred version

    Write YAP's boot message.

    */

    /** @pred version(- Message)

    Add a message to be written when yap boots or after aborting. It is not possible to remove messages.

    */

    /** @pred prolog_load_context(? Key, ? Value)

    Obtain information on what is going on in the compilation process. The following keys are available:

    + directory 
    

    Full name for the directory where YAP is currently consulting the file.

    + file 
    

    Full name for the file currently being consulted. Notice that included filed are ignored.

    + module 
    

    Current source module.

    + source (prolog_load_context/2 option) 
    

    Full name for the file currently being read in, which may be consulted, reconsulted, or included.

    + stream 
    

    Stream currently being read in.

    + term_position 
    

    Stream position at the stream currently being read in. For SWI compatibility, it is a term of the form '$stream_position'(0,Line,0,0,0).

    + source_location(? _FileName_, ? _Line_) 
    

    SWI-compatible predicate. If the last term has been read from a physical file (i.e., not from the file user or a string), unify File with an absolute path to the file and Line with the line-number in the file. Please use prolog_load_context/2.

    + source_file(? _File_) 
    

    SWI-compatible predicate. True if File is a loaded Prolog source file.

    + source_file(? _ModuleAndPred_,? _File_)
    

    SWI-compatible predicate. True if the predicate specified by ModuleAndPred was loaded from file File, where File is an absolute path name (see absolute_file_name/2).

    @section YAPLibrary Library Predicates

    Library files reside in the library_directory path (set by the LIBDIR variable in the Makefile for YAP). Currently, most files in the library are from the Edinburgh Prolog library.

    @} */

    /** @defgroup Aggregate Aggregate @ingroup YAPLibrary @{

    This is the SWI-Prolog library based on the Quintus and SICStus 4 library. @c To be done - Analysing the aggregation template.

    This library provides aggregating operators over the solutions of a predicate. The operations are a generalisation of the bagof/3, setof/3 and findall/3 built-in predicates. The defined aggregation operations are counting, computing the sum, minimum, maximum, a bag of solutions and a set of solutions. We first give a simple example, computing the country with the smallest area:

    smallest_country(Name, Area) :-
            aggregate(min(A, N), country(N, A), min(Area, Name)).
    

    There are four aggregation predicates, distinguished on two properties.

    @pred aggregate vs. aggregate_all The aggregate predicates use setof/3 (aggregate/4) or bagof/3 (aggregate/3), dealing with existential qualified variables ( Var/\ Goal) and providing multiple solutions for the remaining free variables in Goal. The aggregate_all/3 predicate uses findall/3, implicitly qualifying all free variables and providing exactly one solution, while aggregate_all/4 uses sort/2 over solutions and Distinguish (see below) generated using findall/3. + The Distinguish argument The versions with 4 arguments provide a Distinguish argument that allow for keeping duplicate bindings of a variable in the result. For example, if we wish to compute the total population of all countries we do not want to lose results because two countries have the same population. Therefore we use:

            aggregate(sum(P), Name, country(Name, P), Total)
    

    All aggregation predicates support the following operator below in Template. In addition, they allow for an arbitrary named compound term where each of the arguments is a term from the list below. I.e. the term r(min(X), max(X)) computes both the minimum and maximum binding for X.

    @pred count Count number of solutions. Same as sum(1). + sum( Expr) Sum of Expr for all solutions. + min( Expr) Minimum of Expr for all solutions. + min( Expr, Witness) A term min( Min, Witness), where Min is the minimal version of Expr over all Solution and Witness is any other template applied to Solution that produced Min. If multiple solutions provide the same minimum, Witness corresponds to the first solution. + max( Expr) Maximum of Expr for all solutions. + max( Expr, Witness) As min( Expr, Witness), but producing the maximum result. + set( X) An ordered set with all solutions for X. + bag( X) A list of all solutions for X.

    The predicates are:

    @pred [nondet]aggregate(+ Template, : Goal, - Result)

    Aggregate bindings in Goal according to Template. The aggregate/3 version performs bagof/3 on Goal.

    */

    /** @pred [nondet]aggregate(+ Template, + Discriminator, : Goal, - Result)

    Aggregate bindings in Goal according to Template. The aggregate/3 version performs setof/3 on Goal.

    */

    /** @pred [semidet]aggregate_all(+ Template, : Goal, - Result)

    Aggregate bindings in Goal according to Template. The aggregate_all/3 version performs findall/3 on Goal.

    */

    /** @pred [semidet]aggregate_all(+ Template, + Discriminator, : Goal, - Result)

    Aggregate bindings in Goal according to Template. The aggregate_all/3 version performs findall/3 followed by sort/2 on Goal.

    */

    /** @pred foreach(:Generator, : Goal)

    True if the conjunction of instances of Goal using the bindings from Generator is true. Unlike forall/2, which runs a failure-driven loop that proves Goal for each solution of Generator, foreach creates a conjunction. Each member of the conjunction is a copy of Goal, where the variables it shares with Generator are filled with the values from the corresponding solution.

    The implementation executes forall/2 if Goal does not contain any variables that are not shared with Generator.

    Here is an example:

        ?- foreach(between(1,4,X), dif(X,Y)), Y = 5.
        Y = 5
        ?- foreach(between(1,4,X), dif(X,Y)), Y = 3.
        No
    

    Notice that Goal is copied repeatedly, which may cause problems if attributed variables are involved.

    */

    /** @pred [det]free_variables(:Generator, + Template, +VarList0, -VarList)

    In order to handle variables properly, we have to find all the universally quantified variables in the Generator. All variables as yet unbound are universally quantified, unless

      + they occur in the template + they are bound by X/\\P, setof, or bagof

    free_variables(Generator, Template, OldList, NewList) finds this set, using OldList as an accumulator.

    The original author of this code was Richard O'Keefe. Jan Wielemaker made some SWI-Prolog enhancements, sponsored by SecuritEase, http://www.securitease.com. The code is public domain (from DEC10 library).

    @} */

    /** @defgroup Apply Apply Macros @ingroup YAPLibrary @{

    This library provides a SWI-compatible set of utilities for applying a predicate to all elements of a list. The library just forwards definitions from the maplist library.

    @} */

    /** @defgroup Association_Lists Association Lists @ingroup YAPLibrary @{

    The following association list manipulation predicates are available once included with the use_module(library(assoc)) command. The original library used Richard O'Keefe's implementation, on top of unbalanced binary trees. The current code utilises code from the red-black trees library and emulates the SICStus Prolog interface.

    */

    /** @pred assoc_to_list(+ Assoc,? List)

    Given an association list Assoc unify List with a list of the form Key-Val, where the elements Key are in ascending order.

    */

    /** @pred del_assoc(+ Key, + Assoc, ? Val, ? NewAssoc)

    Succeeds if NewAssoc is an association list, obtained by removing the element with Key and Val from the list Assoc.

    */

    /** @pred del_max_assoc(+ Assoc, ? Key, ? Val, ? NewAssoc)

    Succeeds if NewAssoc is an association list, obtained by removing the largest element of the list, with Key and Val from the list Assoc.

    */

    /** @pred del_min_assoc(+ Assoc, ? Key, ? Val, ? NewAssoc)

    Succeeds if NewAssoc is an association list, obtained by removing the smallest element of the list, with Key and Val from the list Assoc.

    */

    /** @pred empty_assoc(+ Assoc)

    Succeeds if association list Assoc is empty.

    */

    /** @pred gen_assoc(+ Assoc,? Key,? Value)

    Given the association list Assoc, unify Key and Value with two associated elements. It can be used to enumerate all elements in the association list.

    */

    /** @pred get_assoc(+ Key,+ Assoc,? Value)

    If Key is one of the elements in the association list Assoc, return the associated value.

    */

    /** @pred get_assoc(+ Key,+ Assoc,? Value,+ NAssoc,? NValue)

    If Key is one of the elements in the association list Assoc, return the associated value Value and a new association list NAssoc where Key is associated with NValue.

    */

    /** @pred get_prev_assoc(+ Key,+ Assoc,? Next,? Value)

    If Key is one of the elements in the association list Assoc, return the previous key, Next, and its value, Value.

    */

    /** @pred get_next_assoc(+ Key,+ Assoc,? Next,? Value)

    If Key is one of the elements in the association list Assoc, return the next key, Next, and its value, Value.

    */

    /** @pred is_assoc(+ Assoc)

    Succeeds if Assoc is an association list, that is, if it is a red-black tree.

    */

    /** @pred list_to_assoc(+ List,? Assoc)

    Given a list List such that each element of List is of the form Key-Val, and all the Keys are unique, Assoc is the corresponding association list.

    */

    /** @pred map_assoc(+ Pred,+ Assoc)

    Succeeds if the unary predicate name Pred( Val) holds for every element in the association list.

    */

    /** @pred map_assoc(+ Pred,+ Assoc,? New)

    Given the binary predicate name Pred and the association list Assoc, New in an association list with keys in Assoc, and such that if Key-Val is in Assoc, and Key-Ans is in New, then Pred( Val, Ans) holds.

    */

    /** @pred max_assoc(+ Assoc,- Key,? Value)

    Given the association list Assoc, Key in the largest key in the list, and Value the associated value.

    */

    /** @pred min_assoc(+ Assoc,- Key,? Value)

    Given the association list Assoc, Key in the smallest key in the list, and Value the associated value.

    */

    /** @pred ord_list_to_assoc(+ List,? Assoc)

    Given an ordered list List such that each element of List is of the form Key-Val, and all the Keys are unique, Assoc is the corresponding association list.

    */

    /** @pred put_assoc(+ Key,+ Assoc,+ Val,+ New)

    The association list New includes and element of association key with Val, and all elements of Assoc that did not have key Key.

    @} */

    /** @defgroup AVL_Trees AVL Trees @ingroup YAPLibrary @{

    AVL trees are balanced search binary trees. They are named after their inventors, Adelson-Velskii and Landis, and they were the first dynamically balanced trees to be proposed. The YAP AVL tree manipulation predicates library uses code originally written by Martin van Emdem and published in the Logic Programming Newsletter, Autumn 1981. A bug in this code was fixed by Philip Vasey, in the Logic Programming Newsletter, Summer 1982. The library currently only includes routines to insert and lookup elements in the tree. Please try red-black trees if you need deletion.

    */

    /** @pred avl_new(+ T)

    Create a new tree.

    */

    /** @pred avl_insert(+ Key,? Value,+ T0,- TF)

    Add an element with key Key and Value to the AVL tree T0 creating a new AVL tree TF. Duplicated elements are allowed.

    */

    /** @pred avl_lookup(+ Key,- Value,+ T)

    Lookup an element with key Key in the AVL tree T, returning the value Value.

    @} */

    /** @defgroup Exo_Intervals Exo Intervals @ingroup YAPLibrary @{

    This package assumes you use exo-compilation, that is, that you loaded the pedicate using the exo option to load_files/2, In this case, YAP includes a package for improved search on intervals of integers.

    The package is activated by udi declarations that state what is the argument of interest:

    :- udi(diagnoses(exo_interval,?,?)).
    
    :- load_files(db, [consult(exo)]).
    

    It is designed to optimise the following type of queries:

    ?- max(X, diagnoses(X, 9, Y), X).
    
    ?- min(X, diagnoses(X, 9, 36211117), X).
    
    ?- X #< Y, min(X, diagnoses(X, 9, 36211117), X ), diagnoses(Y, 9, _).
    

    The first argument gives the time, the second the patient, and the third the condition code. The first query should find the last time the patient 9 had any code reported, the second looks for the first report of code 36211117, and the last searches for reports after this one. All queries run in constant or log(n) time.

    @} */

    /** @defgroup Gecode Gecode Interface @ingroup YAPPackages @{

    The gecode library intreface was designed and implemented by Denis Duchier, with recent work by Vítor Santos Costa to port it to version 4 of gecode and to have an higher level interface,

    @} */

    /** @defgroup The_Gecode_Interface The Gecode Interface @ingroup Gecode @{

    This text is due to Denys Duchier. The gecode interface requires

    :- use_module(library(gecode)).
    

    Several example programs are available with the distribution.

    + CREATING A SPACE
    

    A space is gecodes data representation for a store of constraints:

        Space := space
    
    + CREATING VARIABLES
    

    Unlike in Gecode, variable objects are not bound to a specific Space. Each one actually contains an index with which it is possible to access a Space-bound Gecode variable. Variables can be created using the following expressions:

       IVar := intvar(Space,SPEC...)
       BVar := boolvar(Space)
       SVar := setvar(Space,SPEC...)
    

    where SPEC... is the same as in Gecode. For creating lists of variables use the following variants:

       IVars := intvars(Space,N,SPEC...)
       BVars := boolvars(Space,N,SPEC...)
       SVars := setvars(Space,N,SPEC...)
    

    where N is the number of variables to create (just like for XXXVarArray in Gecode). Sometimes an IntSet is necessary:

       ISet := intset([SPEC...])
    

    where each SPEC is either an integer or a pair (I,J) of integers. An IntSet describes a set of ints by providing either intervals, or integers (which stand for an interval of themselves). It might be tempting to simply represent an IntSet as a list of specs, but this would be ambiguous with IntArgs which, here, are represented as lists of ints.

       Space += keep(Var)
       Space += keep(Vars)
    

    Variables can be marked as "kept". In this case, only such variables will be explicitly copied during search. This could bring substantial benefits in memory usage. Of course, in a solution, you can then only look at variables that have been "kept". If no variable is marked as "kept", then they are all kept. Thus marking variables as "kept" is purely an optimization.

    + CONSTRAINTS AND BRANCHINGS
    

    all constraint and branching posting functions are available just like in Gecode. Wherever a XXXArgs or YYYSharedArray is expected, simply use a list. At present, there is no support for minimodel-like constraint posting. Constraints and branchings are added to a space using:

        Space += CONSTRAINT
        Space += BRANCHING
    

    For example:

        Space += rel(X,'IRT_EQ',Y)
    

    arrays of variables are represented by lists of variables, and constants are represented by atoms with the same name as the Gecode constant (e.g. 'INT_VAR_SIZE_MIN').

    + SEARCHING FOR SOLUTIONS
    
        SolSpace := search(Space)
    

    This is a backtrackable predicate that enumerates all solution spaces (SolSpace). It may also take options:

        SolSpace := search(Space,Options)
    

    Options is a list whose elements maybe:

    + restart
    

    to select the Restart search engine + threads=N to activate the parallel search engine and control the number of workers (see Gecode doc) + c_d=N to set the commit distance for recomputation + a_d=N to set the adaptive distance for recomputation

    + EXTRACTING INFO FROM A SOLUTION
    

    An advantage of non Space-bound variables, is that you can use them both to post constraints in the original space AND to consult their values in solutions. Below are methods for looking up information about variables. Each of these methods can either take a variable as argument, or a list of variables, and returns resp. either a value, or a list of values:

        Val := assigned(Space,X)
    
        Val := min(Space,X)
        Val := max(Space,X)
        Val := med(Space,X)
        Val := val(Space,X)
        Val := size(Space,X)
        Val := width(Space,X)
        Val := regret_min(Space,X)
        Val := regret_max(Space,X)
    
        Val := glbSize(Space,V)
        Val := lubSize(Space,V)
        Val := unknownSize(Space,V)
        Val := cardMin(Space,V)
        Val := cardMax(Space,V)
        Val := lubMin(Space,V)
        Val := lubMax(Space,V)
        Val := glbMin(Space,V)
        Val := glbMax(Space,V)
        Val := glb_ranges(Space,V)
        Val := lub_ranges(Space,V)
        Val := unknown_ranges(Space,V)
        Val := glb_values(Space,V)
        Val := lub_values(Space,V)
        Val := unknown_values(Space,V)
    
    + DISJUNCTORS
    

    Disjunctors provide support for disjunctions of clauses, where each clause is a conjunction of constraints:

        C1 or C2 or ... or Cn
    

    Each clause is executed "speculatively": this means it does not affect the main space. When a clause becomes failed, it is discarded. When only one clause remains, it is committed: this means that it now affects the main space.

    Example:

    Consider the problem where either X=Y=0 or X=Y+(1 or 2) for variable X and Y that take values in 0..3.

        Space := space,
        [X,Y] := intvars(Space,2,0,3),
    

    First, we must create a disjunctor as a manager for our 2 clauses:

        Disj := disjunctor(Space),
    

    We can now create our first clause:

        C1 := clause(Disj),
    

    This clause wants to constrain X and Y to 0. However, since it must be executed "speculatively", it must operate on new variables X1 and Y1 that shadow X and Y:

        [X1,Y1] := intvars(C1,2,0,3),
        C1 += forward([X,Y],[X1,Y1]),
    

    The forward(...) stipulation indicates which global variable is shadowed by which clause-local variable. Now we can post the speculative clause-local constraints for X=Y=0:

        C1 += rel(X1,'IRT_EQ',0),
        C1 += rel(Y1,'IRT_EQ',0),
    

    We now create the second clause which uses X2 and Y2 to shadow X and Y:

        C2 := clause(Disj),
        [X2,Y2] := intvars(C2,2,0,3),
        C2 += forward([X,Y],[X2,Y2]),
    

    However, this clause also needs a clause-local variable Z2 taking values 1 or 2 in order to post the clause-local constraint X2=Y2+Z2:

        Z2 := intvar(C2,1,2),
        C2 += linear([-1,1,1],[X2,Y2,Z2],'IRT_EQ',0),
    

    Finally, we can branch and search:

        Space += branch([X,Y],'INT_VAR_SIZE_MIN','INT_VAL_MIN'),
        SolSpace := search(Space),
    

    and lookup values of variables in each solution:

        [X_,Y_] := val(SolSpace,[X,Y]).
    

    @} */

    /** @defgroup Gecode_and_ClPbBFDbC Programming Finite Domain Constraints in YAP/Gecode @ingroup Gecode @{

    The gecode/clp(fd) interface is designed to use the GECODE functionality in a more CLP like style. It requires

    :- use_module(library(gecode/clpfd)).
    

    Several example programs are available with the distribution.

    Integer variables are declared as:

    + _V_ in  _A_.. _B_
    

    declares an integer variable V with range A to B. + Vs ins A.. B declares a set of integer variabless Vs with range A to B. + boolvar( V) declares a boolean variable. + boolvars( Vs) declares a set of boolean variable.

    Constraints supported are:

    */

    /** @pred X #= Y equality

    */

    /** @pred X #\= Y disequality

    */

    /** @pred X #> Y larger

    */

    /** @pred X #>= Y larger or equal

    */

    /** @pred X #=< Y smaller

    */

    /** @pred X #< Y smaller or equal

    Arguments to this constraint may be an arithmetic expression with +, -, \*, integer division /, min, max, sum, count, and abs. Boolean variables support conjunction (/\), disjunction (\/), implication (=>), equivalence (<=>), and xor. The sum constraint allows a two argument version using the where conditional, in Zinc style.

    The send more money equation may be written as:

              1000*S + 100*E + 10*N + D +
              1000*M + 100*O + 10*R + E #=
    10000*M + 1000*O + 100*N + 10*E + Y,
    

    This example uses where to select from column I the elements that have value under M:

    OutFlow[I] #= sum(J in 1..N where D[J,I]<M, X[J,I])
    

    The count constraint counts the number of elements that match a certain constant or variable (integer sets are not available).

    */

    /** @pred all_different( Vs )

    */

    /** @pred all_distinct( Vs)

    */

    /** @pred all_different( Cs, Vs)

    */

    /** @pred all_distinct( Cs, Vs) verifies whether all elements of a list are different. In the second case, tests if all the sums between a list of constants and a list of variables are different.

    This is a formulation of the queens problem that uses both versions of all_different:

    queens(N, Queens) :-
        length(Queens, N),
        Queens ins 1..N,
        all_distinct(Queens),
        foldl(inc, Queens, Inc, 0, _), % [0, 1, 2, .... ]
        foldl(dec, Queens, Dec, 0, _), % [0, -1, -2, ... ]
        all_distinct(Inc,Queens),
        all_distinct(Dec,Queens),
        labeling([], Queens).
    
    inc(_, I0, I0, I) :-
        I is I0+1.
    
    dec(_, I0, I0, I) :-
        I is I0-1.
    

    The next example uses all_different/1 and the functionality of the matrix package to verify that all squares in sudoku have a different value:

        foreach( [I,J] ins 0..2 ,
               all_different(M[I*3+(0..2),J*3+(0..2)]) ),
    

    */

    /** @pred scalar_product(+ Cs, + Vs, + Rel, ? V )

    The product of constant Cs by Vs must be in relation Rel with V .

    */

    /** @pred X #= all elements of X must take the same value

    */

    /** @pred X #\= not all elements of X take the same value

    */

    /** @pred X #> elements of X must be increasing

    */

    /** @pred X #>= elements of X must be increasinga or equal

    */

    /** @pred X #=< elements of X must be decreasing

    */

    /** @pred X #< elements of X must be decreasing or equal

    */

    /** @pred X #<==> B reified equivalence

    */

    /** @pred X #==> B reified implication

    */

    /** @pred X #< B reified implication

    As an example. consider finding out the people who wanted to sit next to a friend and that are are actually sitting together:

    preference_satisfied(X-Y, B) :-
        abs(X - Y) #= 1 #<==> B.
    

    Note that not all constraints may be reifiable.

    */

    /** @pred element( X, Vs ) X is an element of list Vs

    */

    /** @pred clause( Type, Ps , Ns, V ) If Type is and it is the conjunction of boolean variables Ps and the negation of boolean variables Ns and must have result V. If Type is or it is a disjunction.

    + DFA
    

    the interface allows creating and manipulation deterministic finite automata. A DFA has a set of states, represented as integers and is initialised with an initial state, a set of transitions from the first to the last argument emitting the middle argument, and a final state.

    The swedish-drinkers protocol is represented as follows:

        A = [X,Y,Z],
        dfa( 0, [t(0,0,0),t(0,1,1),t(1,0,0),t(-1,0,0)], [0], C),
        in_dfa( A, C ),
    

    This code will enumeratae the valid tuples of three emissions.

    + extensional constraints
    

    Constraints can also be represented as lists of tuples.

    The previous example would be written as:

        extensional_constraint([[0,0,0],[0,1,0],[1,0,0]], C),
        in_relation( A, C ),
    

    */

    /** @pred minimum( X, Vs)

    */

    /** @pred min( X, Vs) First Argument is the least element of a list.

    */

    /** @pred maximum( X, Vs)

    */

    /** @pred max( X, Vs) First Argument is the greatest element of a list.

    + lex_order( _Vs_)
    

    All elements must be ordered.

    The following predicates control search:

    */

    /** @pred labeling( Opts, Xs) performs labeling, several variable and value selection options are available. The defaults are min and min_step.

    Variable selection options are as follows:

    + leftmost
    

    choose the first variable + min choose one of the variables with smallest minimum value + max choose one of the variables with greatest maximum value + ff choose one of the most constrained variables, that is, with the smallest domain.

    Given that we selected a variable, the values chosen for branching may be:

    + min_step
    

    smallest value + max_step largest value + bisect median + enum all value starting from the minimum.

    */

    /** @pred maximize( V) maximise variable V

    */

    /** @pred minimize(V) minimise variable V

    @} */

    /** @defgroup Heaps Heaps @ingroup YAPLibrary @{

    A heap is a labelled binary tree where the key of each node is less than or equal to the keys of its sons. The point of a heap is that we can keep on adding new elements to the heap and we can keep on taking out the minimum element. If there are N elements total, the total time is O(NlgN). If you know all the elements in advance, you are better off doing a merge-sort, but this file is for when you want to do say a best-first search, and have no idea when you start how many elements there will be, let alone what they are.

    The following heap manipulation routines are available once included with the use_module(library(heaps)) command.

    @pred add_to_heap(+ Heap,+ key,+ Datum,- NewHeap)

    Inserts the new Key-Datum pair into the heap. The insertion is not stable, that is, if you insert several pairs with the same Key it is not defined which of them will come out first, and it is possible for any of them to come out first depending on the history of the heap.

    */

    /** @pred empty_heap(? Heap)

    Succeeds if Heap is an empty heap.

    */

    /** @pred get_from_heap(+ Heap,- key,- Datum,- Heap)

    Returns the Key-Datum pair in OldHeap with the smallest Key, and also a Heap which is the OldHeap with that pair deleted.

    */

    /** @pred heap_size(+ Heap, - Size)

    Reports the number of elements currently in the heap.

    */

    /** @pred heap_to_list(+ Heap, - List)

    Returns the current set of Key-Datum pairs in the Heap as a List, sorted into ascending order of Keys.

    */

    /** @pred list_to_heap(+ List, - Heap)

    Takes a list of Key-Datum pairs (such as keysort could be used to sort) and forms them into a heap.

    */

    /** @pred min_of_heap(+ Heap, - Key, - Datum)

    Returns the Key-Datum pair at the top of the heap (which is of course the pair with the smallest Key), but does not remove it from the heap.

    */

    /** @pred min_of_heap(+ Heap, - Key1, - Datum1,

    • Key2, - Datum2)

    Returns the smallest (Key1) and second smallest (Key2) pairs in the heap, without deleting them.

    @} */

    /** @defgroup Lists List Manipulation @ingroup YAPLibrary @{

    The following list manipulation routines are available once included with the use_module(library(lists)) command.

    @pred append(? Prefix,? Suffix,? Combined)

    True when all three arguments are lists, and the members of Combined are the members of Prefix followed by the members of Suffix. It may be used to form Combined from a given Prefix, Suffix or to take a given Combined apart.

    */

    /** @pred append(? Lists,? Combined)

    Holds if the lists of Lists can be concatenated as a Combined list.

    */

    /** @pred delete(+ List, ? Element, ? Residue)

    True when List is a list, in which Element may or may not occur, and Residue is a copy of List with all elements identical to Element deleted.

    */

    /** @pred flatten(+ List, ? FlattenedList)

    Flatten a list of lists List into a single list FlattenedList.

    ?- flatten([[1],[2,3],[4,[5,6],7,8]],L).
    
    L = [1,2,3,4,5,6,7,8] ? ;
    
    no
    

    */

    /** @pred last(+ List,? Last)

    True when List is a list and Last is identical to its last element.

    */

    /** @pred list_concat(+ Lists,? List)

    True when Lists is a list of lists and List is the concatenation of Lists.

    */

    /** @pred member(? Element, ? Set)

    True when Set is a list, and Element occurs in it. It may be used to test for an element or to enumerate all the elements by backtracking.

    */

    /** @pred memberchk(+ Element, + Set)

    As member/2, but may only be used to test whether a known Element occurs in a known Set. In return for this limited use, it is more efficient when it is applicable.

    */

    /** @pred nth0(? N, ? List, ? Elem)

    True when Elem is the Nth member of List, counting the first as element 0. (That is, throw away the first N elements and unify Elem with the next.) It can only be used to select a particular element given the list and index. For that task it is more efficient than member/2

    */

    /** @pred nth1(? N, ? List, ? Elem)

    The same as nth0/3, except that it counts from 1, that is nth(1, [H|_], H).

    */

    /** @pred nth(? N, ? List, ? Elem)

    The same as nth1/3.

    */

    /** @pred nth0(? N, ? List, ? Elem, ? Rest)

    Unifies Elem with the Nth element of List, counting from 0, and Rest with the other elements. It can be used to select the Nth element of List (yielding Elem and Rest), or to insert Elem before the Nth (counting from 1) element of Rest, when it yields List, e.g. nth0(2, List, c, [a,b,d,e]) unifies List with [a,b,c,d,e]. nth/4 is the same except that it counts from 1. nth0/4 can be used to insert Elem after the Nth element of Rest.

    */

    /** @pred nth1(? N, ? List, ? Elem, ? Rest)

    Unifies Elem with the Nth element of List, counting from 1, and Rest with the other elements. It can be used to select the Nth element of List (yielding Elem and Rest), or to insert Elem before the Nth (counting from 1) element of Rest, when it yields List, e.g. nth(3, List, c, [a,b,d,e]) unifies List with [a,b,c,d,e]. nth/4 can be used to insert Elem after the Nth element of Rest.

    */

    /** @pred nth(? N, ? List, ? Elem, ? Rest)

    Same as nth1/4.

    */

    /** @pred permutation(+ List,? Perm)

    True when List and Perm are permutations of each other.

    */

    /** @pred remove_duplicates(+ List, ? Pruned)

    Removes duplicated elements from List. Beware: if the List has non-ground elements, the result may surprise you.

    */

    /** @pred reverse(+ List, ? Reversed)

    True when List and Reversed are lists with the same elements but in opposite orders.

    */

    /** @pred same_length(? List1, ? List2)

    True when List1 and List2 are both lists and have the same number of elements. No relation between the values of their elements is implied. Modes same_length(-,+) and same_length(+,-) generate either list given the other; mode same_length(-,-) generates two lists of the same length, in which case the arguments will be bound to lists of length 0, 1, 2, ...

    */

    /** @pred select(? Element, ? List, ? Residue)

    True when Set is a list, Element occurs in List, and Residue is everything in List except Element (things stay in the same order).

    */

    /** @pred selectchk(? Element, ? List, ? Residue)

    Semi-deterministic selection from a list. Steadfast: defines as

    selectchk(Elem, List, Residue) :-
            select(Elem, List, Rest0), !,
            Rest = Rest0.
    

    */

    /** @pred sublist(? Sublist, ? List)

    True when both append(_,Sublist,S) and append(S,_,List) hold.

    */

    /** @pred suffix(? Suffix, ? List)

    Holds when append(_,Suffix,List) holds.

    */

    /** @pred sum_list(? Numbers, ? Total)

    True when Numbers is a list of numbers, and Total is their sum.

    */

    /** @pred sum_list(? Numbers, + SoFar, ? Total)

    True when Numbers is a list of numbers, and Total is the sum of their total plus SoFar.

    */

    /** @pred sumlist(? Numbers, ? Total)

    True when Numbers is a list of integers, and Total is their sum. The same as sum_list/2, please do use sum_list/2 instead.

    */

    /** @pred max_list(? Numbers, ? Max)

    True when Numbers is a list of numbers, and Max is the maximum.

    */

    /** @pred min_list(? Numbers, ? Min)

    True when Numbers is a list of numbers, and Min is the minimum.

    */

    /** @pred numlist(+ Low, + High, + List)

    If Low and High are integers with Low =< High, unify List to a list [Low, Low+1, ...High]. See also between/3.

    */

    /** @pred intersection(+ Set1, + Set2, + Set3)

    Succeeds if Set3 unifies with the intersection of Set1 and Set2. Set1 and Set2 are lists without duplicates. They need not be ordered.

    */

    /** @pred subtract(+ Set, + Delete, ? Result)

    Delete all elements from Set that occur in Delete (a set) and unify the result with Result. Deletion is based on unification using memberchk/2. The complexity is |Delete|\*|Set|.

    See ord_subtract/3.

    @} */

    /** @defgroup LineUtilities Line Manipulation Utilities @ingroup YAPLibrary @{

    This package provides a set of useful predicates to manipulate sequences of characters codes, usually first read in as a line. It is available by loading the library library(lineutils).

    @pred search_for(+ Char,+ Line)

    Search for a character Char in the list of codes Line.

    */

    /** @pred search_for(+ Char,+ Line,- RestOfine)

    Search for a character Char in the list of codes Line, RestOfLine has the line to the right.

    */

    /** @pred scan_natural(? Nat,+ Line,+ RestOfLine)

    Scan the list of codes Line for a natural number Nat, zero or a positive integer, and unify RestOfLine with the remainder of the line.

    */

    /** @pred scan_integer(? Int,+ Line,+ RestOfLine)

    Scan the list of codes Line for an integer Nat, either a positive, zero, or negative integer, and unify RestOfLine with the remainder of the line.

    */

    /** @pred split(+ Line,+ Separators,- Split)

    Unify Words with a set of strings obtained from Line by using the character codes in Separators as separators. As an example, consider:

    ?- split("Hello * I am free"," *",S).
    
    S = ["Hello","I","am","free"] ?
    
    no
    

    */

    /** @pred split(+ Line,- Split)

    Unify Words with a set of strings obtained from Line by using the blank characters as separators.

    */

    /** @pred fields(+ Line,+ Separators,- Split)

    Unify Words with a set of strings obtained from Line by using the character codes in Separators as separators for fields. If two separators occur in a row, the field is considered empty. As an example, consider:

    ?- fields("Hello  I am  free"," *",S).
    
    S = ["Hello","","I","am","","free"] ?
    

    */

    /** @pred fields(+ Line,- Split)

    Unify Words with a set of strings obtained from Line by using the blank characters as field separators.

    */

    /** @pred glue(+ Words,+ Separator,- Line)

    Unify Line with string obtained by glueing Words with the character code Separator.

    */

    /** @pred copy_line(+ StreamInput,+ StreamOutput)

    Copy a line from StreamInput to StreamOutput.

    */

    /** @pred process(+ StreamInp, + Goal)

    For every line LineIn in stream StreamInp, call call(Goal,LineIn).

    */

    /** @pred filter(+ StreamInp, + StreamOut, + Goal)

    For every line LineIn in stream StreamInp, execute call(Goal,LineIn,LineOut), and output LineOut to stream StreamOut.

    */

    /** @pred file_filter(+ FileIn, + FileOut, + Goal)

    For every line LineIn in file FileIn, execute call(Goal,LineIn,LineOut), and output LineOut to file FileOut.

    */

    /** @pred file_filter(+ FileIn, + FileOut, + Goal,

    • FormatCommand, + Arguments)

    Same as file_filter/3, but before starting the filter execute format/3 on the output stream, using FormatCommand and Arguments.

    @} */

    /** @defgroup matrix Matrix Library @ingroup YAPLibrary @{

    This package provides a fast implementation of multi-dimensional matrices of integers and floats. In contrast to dynamic arrays, these matrices are multi-dimensional and compact. In contrast to static arrays. these arrays are allocated in the stack. Matrices are available by loading the library library(matrix). They are multimensional objects of type:

    + <tt>terms</tt>: Prolog terms
    + <tt>ints</tt>: bounded integers, represented as an opaque term. The
    

    maximum integer depends on hardware, but should be obtained from the natural size of the machine. + floats: floating-poiny numbers, represented as an opaque term.

    Matrix elements can be accessed through the matrix_get/2 predicate or through an R-inspired access notation (that uses the ciao style extension to []. Examples include:

    */

    /** @pred E <== X[2,3] Access the second row, third column of matrix X. Indices start from 0,

    */

    /** @pred L <== X[2,_] Access all the second row, the output is a list ofe elements.

    */

    /** @pred L <== X[2..4,_] Access all the second, thrd and fourth rows, the output is a list of elements.

    */

    /** @pred L <== X[2..4+3,_] Access all the fifth, sixth and eight rows, the output is a list of elements.

    The matrix library also supports a B-Prolog/ECliPSe inspired foreach ITerator to iterate over elements of a matrix:

    */

    /** @pred foreach(I in 0..N1, X[I] <== Y[I]) Copies a vector, element by element.

    */

    /** @pred foreach([I in 0..N1, J in I..N1], Z[I,J] <== X[I,J] - X[I,J]) The lower-triangular matrix Z is the difference between the lower-triangular and upper-triangular parts of X.

    */

    /** @pred foreach([I in 0..N1, J in 0..N1], plus(X[I,J]), 0, Sum) Add all elements of a matrix by using Sum as an accumulator.

    Notice that the library does not support all known matrix operations. Please contact the YAP maintainers if you require extra functionality.

    + _X_ = array[ _Dim1_,..., _Dimn_] of  _Objects_ 
    

    The of/2 operator can be used to create a new array of Objects. The objects supported are:

    + Unbound Variable
    

    create an array of free variables + ints create an array of integers + floats create an array of floating-point numbers + I: J create an array with integers from I to J + [..] create an array from the values in a list

    The dimensions can be given as an integer, and the matrix will be indexed C-style from 0..( _Max_-1), or can be given as an interval _Base_.. _Limit_. In the latter case, matrices of integers and of floating-point numbers should have the same Base on every dimension.

    */

    /** @pred ? LHS <== RHS

    General matrix assignment operation. It evaluates the right-hand side and then acts different according to the left-hand side and to the matrix:

    + if  _LHS_ is part of an integer or floating-point matrix,
    

    perform non-backtrackable assignment. + other unify left-hand side and right-hand size.

    The right-hand side supports the following operators:

    + []/2
    

    written as M[ Offset]: obtain an element or list of elements of matrix M at offset Offset. + matrix/1 create a vector from a list + matrix/2 create a matrix from a list. Oprions are:

    + dim=
    

    a list of dimensiona + type= integers, floating-point or terms + base= a list of base offsets per dimension (all must be the same for arrays of integers and floating-points

    + matrix/3
    

    create matrix giving two options + dim/1 list with matrix dimensions + nrow/1 number of rows in bi-dimensional matrix + ncol/1 number of columns in bi-dimensional matrix + length/1 size of a matrix + size/1 size of a matrix + max/1 maximum element of a numeric matrix + maxarg/1 argument of maximum element of a numeric matrix + min/1 minimum element of a numeric matrix + minarg/1 argument of minimum element of a numeric matrix + list/1 represent matrix as a list + lists/2 represent matrix as list of embedded lists + ../2 I.. J generates a list with all integers from I to J, included. + +/2 add two numbers, add two matrices element-by-element, or add a number to all elements of a matrix or list + -/2 subtract two numbers, subtract two matrices or lists element-by-element, or subtract a number from all elements of a matrix or list + * /2 multiply two numbers, multiply two matrices or lists element-by-element, or multiply a number from all elements of a matrix or list + log/1 natural logarithm of a number, matrix or list + exp/1 natural exponentiation of a number, matrix or list

    */

    /** @pred foreach( Sequence, Goal)

    Deterministic iterator. The ranges are given by Sequence that is either _I_ in _M_.. _N_, or of the form [ _I_, _J_] ins _M_.. _N_, or a list of the above conditions.

    Variables in the goal are assumed to be global, ie, share a single value in the execution. The exceptions are the iteration indices. Moreover, if the goal is of the form _Locals_^ _G_ all variables occurring in Locals are marked as local. As an example:

    foreach([I,J] ins 1..N, A^(A <==M[I,J], N[I] <== N[I] + A*A) )
    

    the variables I, J and A are duplicated for every call (local), whereas the matrices M and N are shared throughout the execution (global).

    */

    /** @pred foreach( Sequence, Goal, Acc0, AccF)

    Deterministic iterator with accumulator style arguments.

    */

    /** @pred matrix_new(+ Type,+ Dims,- Matrix)

    Create a new matrix Matrix of type Type, which may be one of ints or floats, and with a list of dimensions Dims. The matrix will be initialised to zeros.

    ?- matrix_new(ints,[2,3],Matrix).
    
    Matrix = {..}
    

    Notice that currently YAP will always write a matrix of numbers as {..}.

    */

    /** @pred matrix_new(+ Type,+ Dims,+ List,- Matrix)

    Create a new matrix Matrix of type Type, which may be one of ints or floats, with dimensions Dims, and initialised from list List.

    */

    /** @pred matrix_new_set(? Dims,+ OldMatrix,+ Value,- NewMatrix)

    Create a new matrix NewMatrix of type Type, with dimensions Dims. The elements of NewMatrix are set to Value.

    */

    /** @pred matrix_dims(+ Matrix,- Dims)

    Unify Dims with a list of dimensions for Matrix.

    */

    /** @pred matrix_ndims(+ Matrix,- Dims)

    Unify NDims with the number of dimensions for Matrix.

    */

    /** @pred matrix_size(+ Matrix,- NElems)

    Unify NElems with the number of elements for Matrix.

    */

    /** @pred matrix_type(+ Matrix,- Type)

    Unify NElems with the type of the elements in Matrix.

    */

    /** @pred matrix_to_list(+ Matrix,- Elems)

    Unify Elems with the list including all the elements in Matrix.

    */

    /** @pred matrix_get(+ Matrix,+ Position,- Elem)

    Unify Elem with the element of Matrix at position Position.

    */

    /** @pred matrix_get(+ Matrix[+ Position],- Elem)

    Unify Elem with the element Matrix[ Position].

    */

    /** @pred matrix_set(+ Matrix,+ Position,+ Elem)

    Set the element of Matrix at position Position to Elem.

    */

    /** @pred matrix_set(+ Matrix[+ Position],+ Elem)

    Set the element of Matrix[ Position] to Elem.

    */

    /** @pred matrix_set_all(+ Matrix,+ Elem)

    Set all element of Matrix to Elem.

    */

    /** @pred matrix_add(+ Matrix,+ Position,+ Operand)

    Add Operand to the element of Matrix at position Position.

    */

    /** @pred matrix_inc(+ Matrix,+ Position)

    Increment the element of Matrix at position Position.

    */

    /** @pred matrix_inc(+ Matrix,+ Position,- Element)

    Increment the element of Matrix at position Position and unify with Element.

    */

    /** @pred matrix_dec(+ Matrix,+ Position)

    Decrement the element of Matrix at position Position.

    */

    /** @pred matrix_dec(+ Matrix,+ Position,- Element)

    Decrement the element of Matrix at position Position and unify with Element.

    */

    /** @pred matrix_arg_to_offset(+ Matrix,+ Position,- Offset)

    Given matrix Matrix return what is the numerical Offset of the element at Position.

    */

    /** @pred matrix_offset_to_arg(+ Matrix,- Offset,+ Position)

    Given a position _Position _ for matrix Matrix return the corresponding numerical Offset from the beginning of the matrix.

    */

    /** @pred matrix_max(+ Matrix,+ Max)

    Unify Max with the maximum in matrix Matrix.

    */

    /** @pred matrix_maxarg(+ Matrix,+ Maxarg)

    Unify Max with the position of the maximum in matrix Matrix.

    */

    /** @pred matrix_min(+ Matrix,+ Min)

    Unify Min with the minimum in matrix Matrix.

    */

    /** @pred matrix_minarg(+ Matrix,+ Minarg)

    Unify Min with the position of the minimum in matrix Matrix.

    */

    /** @pred matrix_sum(+ Matrix,+ Sum)

    Unify Sum with the sum of all elements in matrix Matrix.

    */

    /** @pred matrix_agg_lines(+ Matrix,+ Aggregate)

    If Matrix is a n-dimensional matrix, unify Aggregate with the n-1 dimensional matrix where each element is obtained by adding all Matrix elements with same last n-1 index.

    */

    /** @pred matrix_agg_cols(+ Matrix,+ Aggregate)

    If Matrix is a n-dimensional matrix, unify Aggregate with the one dimensional matrix where each element is obtained by adding all Matrix elements with same first index.

    */

    /** @pred matrix_op(+ Matrix1,+ Matrix2,+ Op,- Result)

    Result is the result of applying Op to matrix Matrix1 and Matrix2. Currently, only addition (+) is supported.

    */

    /** @pred matrix_op_to_all(+ Matrix1,+ Op,+ Operand,- Result)

    Result is the result of applying Op to all elements of Matrix1, with Operand as the second argument. Currently, only addition (+), multiplication (\*), and division (/) are supported.

    */

    /** @pred matrix_op_to_lines(+ Matrix1,+ Lines,+ Op,- Result)

    Result is the result of applying Op to all elements of Matrix1, with the corresponding element in Lines as the second argument. Currently, only division (/) is supported.

    */

    /** @pred matrix_op_to_cols(+ Matrix1,+ Cols,+ Op,- Result)

    Result is the result of applying Op to all elements of Matrix1, with the corresponding element in Cols as the second argument. Currently, only addition (+) is supported. Notice that Cols will have n-1 dimensions.

    */

    /** @pred matrix_shuffle(+ Matrix,+ NewOrder,- Shuffle)

    Shuffle the dimensions of matrix Matrix according to NewOrder. The list NewOrder must have all the dimensions of Matrix, starting from 0.

    */

    /** @pred matrix_transpose(+ Matrix,- Transpose)

    Transpose matrix Matrix to Transpose. Equivalent to:

    matrix_transpose(Matrix,Transpose) :-
            matrix_shuffle(Matrix,[1,0],Transpose).
    

    */

    /** @pred matrix_expand(+ Matrix,+ NewDimensions,- New)

    Expand Matrix to occupy new dimensions. The elements in NewDimensions are either 0, for an existing dimension, or a positive integer with the size of the new dimension.

    */

    /** @pred matrix_select(+ Matrix,+ Dimension,+ Index,- New)

    Select from Matrix the elements who have Index at Dimension.

    */

    /** @pred matrix_row(+ Matrix,+ Column,- NewMatrix)

    Select from Matrix the row matching Column as new matrix NewMatrix. Column must have one less dimension than the original matrix. Dimension.

    @} */

    /** @defgroup MATLAB MATLAB Package Interface @ingroup YAPLibrary @{

    The MathWorks MATLAB is a widely used package for array processing. YAP now includes a straightforward interface to MATLAB. To actually use it, you need to install YAP calling configure with the --with-matlab=DIR option, and you need to call use_module(library(lists)) command.

    Accessing the matlab dynamic libraries can be complicated. In Linux machines, to use this interface, you may have to set the environment variable LD_LIBRARY_PATH. Next, follows an example using bash in a 64-bit Linux PC:

    export LD_LIBRARY_PATH=''$MATLAB_HOME"/sys/os/glnxa64:''$MATLAB_HOME"/bin/glnxa64:''$LD_LIBRARY_PATH"
    

    where MATLAB_HOME is the directory where matlab is installed at. Please replace ax64 for x86 on a 32-bit PC.

    @pred start_matlab(+ Options)

    Start a matlab session. The argument Options may either be the empty string/atom or the command to call matlab. The command may fail.

    */

    /** @pred close_matlab

    Stop the current matlab session.

    */

    /** @pred matlab_on

    Holds if a matlab session is on.

    */

    /** @pred matlab_eval_string(+ Command)

    Holds if matlab evaluated successfully the command Command.

    */

    /** @pred matlab_eval_string(+ Command, - Answer)

    MATLAB will evaluate the command Command and unify Answer with a string reporting the result.

    */

    /** @pred matlab_cells(+ Size, ? Array)

    MATLAB will create an empty vector of cells of size Size, and if Array is bound to an atom, store the array in the matlab variable with name Array. Corresponds to the MATLAB command cells.

    */

    /** @pred matlab_cells(+ SizeX, + SizeY, ? Array)

    MATLAB will create an empty array of cells of size SizeX and SizeY, and if Array is bound to an atom, store the array in the matlab variable with name Array. Corresponds to the MATLAB command cells.

    */

    /** @pred matlab_initialized_cells(+ SizeX, + SizeY, + List, ? Array)

    MATLAB will create an array of cells of size SizeX and SizeY, initialized from the list List, and if Array is bound to an atom, store the array in the matlab variable with name Array.

    */

    /** @pred matlab_matrix(+ SizeX, + SizeY, + List, ? Array)

    MATLAB will create an array of floats of size SizeX and SizeY, initialized from the list List, and if Array is bound to an atom, store the array in the matlab variable with name Array.

    */

    /** @pred matlab_set(+ MatVar, + X, + Y, + Value)

    Call MATLAB to set element MatVar( X, Y) to Value. Notice that this command uses the MATLAB array access convention.

    */

    /** @pred matlab_get_variable(+ MatVar, - List)

    Unify MATLAB variable MatVar with the List List.

    */

    /** @pred matlab_item(+ MatVar, + X, ? Val)

    Read or set MATLAB MatVar( X) from/to Val. Use C notation for matrix access (ie, starting from 0).

    */

    /** @pred matlab_item(+ MatVar, + X, + Y, ? Val)

    Read or set MATLAB MatVar( X, Y) from/to Val. Use C notation for matrix access (ie, starting from 0).

    */

    /** @pred matlab_item1(+ MatVar, + X, ? Val)

    Read or set MATLAB MatVar( X) from/to Val. Use MATLAB notation for matrix access (ie, starting from 1).

    */

    /** @pred matlab_item1(+ MatVar, + X, + Y, ? Val)

    Read or set MATLAB MatVar( X, Y) from/to Val. Use MATLAB notation for matrix access (ie, starting from 1).

    */

    /** @pred matlab_sequence(+ Min, + Max, ? Array)

    MATLAB will create a sequence going from Min to Max, and if Array is bound to an atom, store the sequence in the matlab variable with name Array.

    */

    /** @pred matlab_vector(+ Size, + List, ? Array)

    MATLAB will create a vector of floats of size Size, initialized from the list List, and if Array is bound to an atom, store the array in the matlab variable with name Array.

    */

    /** @pred matlab_zeros(+ Size, ? Array)

    MATLAB will create a vector of zeros of size Size, and if Array is bound to an atom, store the array in the matlab variable with name Array. Corresponds to the MATLAB command zeros.

    */

    /** @pred matlab_zeros(+ SizeX, + SizeY, ? Array)

    MATLAB will create an array of zeros of size SizeX and SizeY, and if Array is bound to an atom, store the array in the matlab variable with name Array. Corresponds to the MATLAB command zeros.

    */

    /** @pred matlab_zeros(+ SizeX, + SizeY, + SizeZ, ? Array)

    MATLAB will create an array of zeros of size SizeX, SizeY, and SizeZ. If Array is bound to an atom, store the array in the matlab variable with name Array. Corresponds to the MATLAB command zeros.

    @} */

    /** @defgroup NonhYBacktrackable_Data_Structures Non-Backtrackable Data Structures @ingroup YAPLibrary @{

    The following routines implement well-known data-structures using global non-backtrackable variables (implemented on the Prolog stack). The data-structures currently supported are Queues, Heaps, and Beam for Beam search. They are allowed through library(nb).

    */

    /** @pred nb_queue(- Queue)

    Create a Queue.

    */

    /** @pred nb_queue_close(+ Queue, - Head, ? Tail)

    Unify the queue Queue with a difference list Head- Tail. The queue will now be empty and no further elements can be added.

    */

    /** @pred nb_queue_enqueue(+ Queue, + Element)

    Add Element to the front of the queue Queue.

    */

    /** @pred nb_queue_dequeue(+ Queue, - Element)

    Remove Element from the front of the queue Queue. Fail if the queue is empty.

    */

    /** @pred nb_queue_peek(+ Queue, - Element)

    Element is the front of the queue Queue. Fail if the queue is empty.

    */

    /** @pred nb_queue_size(+ Queue, - Size)

    Unify Size with the number of elements in the queue Queue.

    */

    /** @pred nb_queue_empty(+ Queue)

    Succeeds if Queue is empty.

    */

    /** @pred nb_heap(+ DefaultSize,- Heap)

    Create a Heap with default size DefaultSize. Note that size will expand as needed.

    */

    /** @pred nb_heap_close(+ Heap)

    Close the heap Heap: no further elements can be added.

    */

    /** @pred nb_heap_add(+ Heap, + Key, + Value)

    Add Key- Value to the heap Heap. The key is sorted on Key only.

    */

    /** @pred nb_heap_del(+ Heap, - Key, - Value)

    Remove element Key- Value with smallest Value in heap Heap. Fail if the heap is empty.

    */

    /** @pred nb_heap_peek(+ Heap, - Key, - Value))

    Key- Value is the element with smallest Key in the heap Heap. Fail if the heap is empty.

    */

    /** @pred nb_heap_size(+ Heap, - Size)

    Unify Size with the number of elements in the heap Heap.

    */

    /** @pred nb_heap_empty(+ Heap)

    Succeeds if Heap is empty.

    */

    /** @pred nb_beam(+ DefaultSize,- Beam)

    Create a Beam with default size DefaultSize. Note that size is fixed throughout.

    */

    /** @pred nb_beam_close(+ Beam)

    Close the beam Beam: no further elements can be added.

    */

    /** @pred nb_beam_add(+ Beam, + Key, + Value)

    Add Key- Value to the beam Beam. The key is sorted on Key only.

    */

    /** @pred nb_beam_del(+ Beam, - Key, - Value)

    Remove element Key- Value with smallest Value in beam Beam. Fail if the beam is empty.

    */

    /** @pred nb_beam_peek(+ Beam, - Key, - Value))

    Key- Value is the element with smallest Key in the beam Beam. Fail if the beam is empty.

    */

    /** @pred nb_beam_size(+ Beam, - Size)

    Unify Size with the number of elements in the beam Beam.

    */

    /** @pred nb_beam_empty(+ Beam)

    Succeeds if Beam is empty.

    @} */

    /** @defgroup Ordered_Sets Ordered Sets @ingroup YAPLibrary @{

    The following ordered set manipulation routines are available once included with the use_module(library(ordsets)) command. An ordered set is represented by a list having unique and ordered elements. Output arguments are guaranteed to be ordered sets, if the relevant inputs are. This is a slightly patched version of Richard O'Keefe's original library.

    */

    /** @pred list_to_ord_set(+ List, ? Set)

    Holds when Set is the ordered representation of the set represented by the unordered representation List.

    */

    /** @pred merge(+ List1, + List2, - Merged)

    Holds when Merged is the stable merge of the two given lists.

    Notice that merge/3 will not remove duplicates, so merging ordered sets will not necessarily result in an ordered set. Use ord_union/3 instead.

    */

    /** @pred ord_add_element(+ Set1, + Element, ? Set2)

    Inserting Element in Set1 returns Set2. It should give exactly the same result as merge(Set1, [Element], Set2), but a bit faster, and certainly more clearly. The same as ord_insert/3.

    */

    /** @pred ord_del_element(+ Set1, + Element, ? Set2)

    Removing Element from Set1 returns Set2.

    */

    /** @pred ord_disjoint(+ Set1, + Set2)

    Holds when the two ordered sets have no element in common.

    */

    /** @pred ord_member(+ Element, + Set)

    Holds when Element is a member of Set.

    */

    /** @pred ord_insert(+ Set1, + Element, ? Set2)

    Inserting Element in Set1 returns Set2. It should give exactly the same result as merge(Set1, [Element], Set2), but a bit faster, and certainly more clearly. The same as ord_add_element/3.

    */

    /** @pred ord_intersect(+ Set1, + Set2)

    Holds when the two ordered sets have at least one element in common.

    */

    /** @pred ord_intersection(+ Set1, + Set2, ? Intersection)

    Holds when Intersection is the ordered representation of Set1 and Set2.

    */

    /** @pred ord_intersection(+ Set1, + Set2, ? Intersection, ? Diff)

    Holds when Intersection is the ordered representation of Set1 and Set2. Diff is the difference between Set2 and Set1.

    */

    /** @pred ord_seteq(+ Set1, + Set2)

    Holds when the two arguments represent the same set.

    */

    /** @pred ord_setproduct(+ Set1, + Set2, - Set)

    If Set1 and Set2 are ordered sets, Product will be an ordered set of x1-x2 pairs.

    */

    /** @pred ord_subset(+ Set1, + Set2)

    Holds when every element of the ordered set Set1 appears in the ordered set Set2.

    */

    /** @pred ord_subtract(+ Set1, + Set2, ? Difference)

    Holds when Difference contains all and only the elements of Set1 which are not also in Set2.

    */

    /** @pred ord_symdiff(+ Set1, + Set2, ? Difference)

    Holds when Difference is the symmetric difference of Set1 and Set2.

    */

    /** @pred ord_union(+ Sets, ? Union)

    Holds when Union is the union of the lists Sets.

    */

    /** @pred ord_union(+ Set1, + Set2, ? Union)

    Holds when Union is the union of Set1 and Set2.

    */

    /** @pred ord_union(+ Set1, + Set2, ? Union, ? Diff)

    Holds when Union is the union of Set1 and Set2 and Diff is the difference.

    @} */

    /** @defgroup Pseudo_Random Pseudo Random Number Integer Generator @ingroup YAPLibrary @{

    The following routines produce random non-negative integers in the range 0 .. 2^(w-1) -1, where w is the word size available for integers, e.g. 32 for Intel machines and 64 for Alpha machines. Note that the numbers generated by this random number generator are repeatable. This generator was originally written by Allen Van Gelder and is based on Knuth Vol 2.

    */

    /** @pred rannum(- I)

    Produces a random non-negative integer I whose low bits are not all that random, so it should be scaled to a smaller range in general. The integer I is in the range 0 .. 2^(w-1) - 1. You can use:

    rannum(X) :- yap_flag(max_integer,MI), rannum(R), X is R/MI.
    

    to obtain a floating point number uniformly distributed between 0 and 1.

    */

    /** @pred ranstart

    Initialize the random number generator using a built-in seed. The ranstart/0 built-in is always called by the system when loading the package.

    */

    /** @pred ranstart(+ Seed)

    Initialize the random number generator with user-defined Seed. The same Seed always produces the same sequence of numbers.

    */

    /** @pred ranunif(+ Range,- I)

    ranunif/2 produces a uniformly distributed non-negative random integer I over a caller-specified range R. If range is R, the result is in 0 .. R-1.

    @} */

    /** @defgroup Queues Queues @ingroup YAPLibrary @{

    The following queue manipulation routines are available once included with the use_module(library(queues)) command. Queues are implemented with difference lists.

    @pred make_queue(+ Queue)

    Creates a new empty queue. It should only be used to create a new queue.

    */

    /** @pred join_queue(+ Element, + OldQueue, - NewQueue)

    Adds the new element at the end of the queue.

    */

    /** @pred list_join_queue(+ List, + OldQueue, - NewQueue)

    Ads the new elements at the end of the queue.

    */

    /** @pred jump_queue(+ Element, + OldQueue, - NewQueue)

    Adds the new element at the front of the list.

    */

    /** @pred list_jump_queue(+ List, + OldQueue, + NewQueue)

    Adds all the elements of List at the front of the queue.

    */

    /** @pred head_queue(+ Queue, ? Head)

    Unifies Head with the first element of the queue.

    */

    /** @pred serve_queue(+ OldQueue, + Head, - NewQueue)

    Removes the first element of the queue for service.

    */

    /** @pred empty_queue(+ Queue)

    Tests whether the queue is empty.

    */

    /** @pred length_queue(+ Queue, - Length)

    Counts the number of elements currently in the queue.

    */

    /** @pred list_to_queue(+ List, - Queue)

    Creates a new queue with the same elements as List.

    */

    /** @pred queue_to_list(+ Queue, - List)

    Creates a new list with the same elements as Queue.

    @} */

    /** @defgroup Random Random Number Generator @ingroup YAPLibrary @{

    The following random number operations are included with the use_module(library(random)) command. Since YAP-4.3.19 YAP uses the O'Keefe public-domain algorithm, based on the "Applied Statistics" algorithm AS183.

    @pred getrand(- Key)

    Unify Key with a term of the form rand(X,Y,Z) describing the current state of the random number generator.

    */

    /** @pred random(- Number)

    Unify Number with a floating-point number in the range [0...1).

    */

    /** @pred random(+ LOW, + HIGH, - NUMBER)

    Unify Number with a number in the range [LOW...HIGH). If both LOW and HIGH are integers then NUMBER will also be an integer, otherwise NUMBER will be a floating-point number.

    */

    /** @pred randseq(+ LENGTH, + MAX, - Numbers)

    Unify Numbers with a list of LENGTH unique random integers in the range [1... _MAX_).

    */

    /** @pred randset(+ LENGTH, + MAX, - Numbers)

    Unify Numbers with an ordered list of LENGTH unique random integers in the range [1... _MAX_).

    */

    /** @pred setrand(+ Key)

    Use a term of the form rand(X,Y,Z) to set a new state for the random number generator. The integer X must be in the range [1...30269), the integer Y must be in the range [1...30307), and the integer Z must be in the range [1...30323).

    @} */

    /** @defgroup Read_Utilities Read Utilities @ingroup YAPLibrary @{

    The readutil library contains primitives to read lines, files, multiple terms, etc.

    */

    /** @pred read_line_to_codes(+ Stream, - Codes)

    Read the next line of input from Stream and unify the result with Codes after the line has been read. A line is ended by a newline character or end-of-file. Unlike read_line_to_codes/3, this predicate removes trailing newline character.

    On end-of-file the atom end_of_file is returned. See also at_end_of_stream/[0,1].

    */

    /** @pred read_line_to_codes(+ Stream, - Codes, ? Tail)

    Difference-list version to read an input line to a list of character codes. Reading stops at the newline or end-of-file character, but unlike read_line_to_codes/2, the newline is retained in the output. This predicate is especially useful for reading a block of lines upto some delimiter. The following example reads an HTTP header ended by a blank line:

    read_header_data(Stream, Header) :-
        read_line_to_codes(Stream, Header, Tail),
        read_header_data(Header, Stream, Tail).
    
    read_header_data("\r\n", _, _) :- !.
    read_header_data("\n", _, _) :- !.
    read_header_data("", _, _) :- !.
    read_header_data(_, Stream, Tail) :-
        read_line_to_codes(Stream, Tail, NewTail),
        read_header_data(Tail, Stream, NewTail).
    

    */

    /** @pred read_stream_to_codes(+ Stream, - Codes)

    Read all input until end-of-file and unify the result to Codes.

    */

    /** @pred read_stream_to_codes(+ Stream, - Codes, ? Tail)

    Difference-list version of read_stream_to_codes/2.

    */

    /** @pred read_file_to_codes(+ Spec, - Codes, + Options)

    Read a file to a list of character codes. Currently ignores Options.

    */

    /** @pred read_file_to_terms(+ Spec, - Terms, + Options)

    Read a file to a list of Prolog terms (see read/1). @c Spec is a

    @} */

    /** @defgroup RedhYBlack_Trees Red-Black Trees @ingroup YAPLibrary @{

    Red-Black trees are balanced search binary trees. They are named because nodes can be classified as either red or black. The code we include is based on "Introduction to Algorithms", second edition, by Cormen, Leiserson, Rivest and Stein. The library includes routines to insert, lookup and delete elements in the tree.

    */

    /** @pred rb_new(? T)

    Create a new tree.

    */

    /** @pred rb_empty(? T)

    Succeeds if tree T is empty.

    */

    /** @pred is_rbtree(+ T)

    Check whether T is a valid red-black tree.

    */

    /** @pred rb_insert(+ T0,+ Key,? Value,+ TF)

    Add an element with key Key and Value to the tree T0 creating a new red-black tree TF. Duplicated elements are not allowed.

    Add a new element with key Key and Value to the tree T0 creating a new red-black tree TF. Fails is an element with Key exists in the tree.

    */

    /** @pred rb_lookup(+ Key,- Value,+ T)

    Backtrack through all elements with key Key in the red-black tree T, returning for each the value Value.

    */

    /** @pred rb_lookupall(+ Key,- Value,+ T)

    Lookup all elements with key Key in the red-black tree T, returning the value Value.

    */

    /** @pred rb_delete(+ T,+ Key,- TN)

    Delete element with key Key from the tree T, returning a new tree TN.

    */

    /** @pred rb_delete(+ T,+ Key,- Val,- TN)

    Delete element with key Key from the tree T, returning the value Val associated with the key and a new tree TN.

    */

    /** @pred rb_del_min(+ T,- Key,- Val,- TN)

    Delete the least element from the tree T, returning the key Key, the value Val associated with the key and a new tree TN.

    */

    /** @pred rb_del_max(+ T,- Key,- Val,- TN)

    Delete the largest element from the tree T, returning the key Key, the value Val associated with the key and a new tree TN.

    */

    /** @pred rb_update(+ T,+ Key,+ NewVal,- TN)

    Tree TN is tree T, but with value for Key associated with NewVal. Fails if it cannot find Key in T.

    */

    /** @pred rb_apply(+ T,+ Key,+ G,- TN)

    If the value associated with key Key is Val0 in T, and if call(G,Val0,ValF) holds, then TN differs from T only in that Key is associated with value ValF in tree TN. Fails if it cannot find Key in T, or if call(G,Val0,ValF) is not satisfiable.

    */

    /** @pred rb_visit(+ T,- Pairs)

    Pairs is an infix visit of tree T, where each element of Pairs is of the form K- Val.

    */

    /** @pred rb_size(+ T,- Size)

    Size is the number of elements in T.

    */

    /** @pred rb_keys(+ T,+ Keys)

    Keys is an infix visit with all keys in tree T. Keys will be sorted, but may be duplicate.

    */

    /** @pred rb_map(+ T,+ G,- TN)

    For all nodes Key in the tree T, if the value associated with key Key is Val0 in tree T, and if call(G,Val0,ValF) holds, then the value associated with Key in TN is ValF. Fails if or if call(G,Val0,ValF) is not satisfiable for all Var0.

    */

    /** @pred rb_partial_map(+ T,+ Keys,+ G,- TN)

    For all nodes Key in Keys, if the value associated with key Key is Val0 in tree T, and if call(G,Val0,ValF) holds, then the value associated with Key in TN is ValF. Fails if or if call(G,Val0,ValF) is not satisfiable for all Var0. Assumes keys are not repeated.

    */

    /** @pred rb_fold(+ T,+ G,+ Acc0, - AccF)

    For all nodes Key in the tree T, if the value associated with key Key is V in tree T, if call(G,V,Acc1,Acc2) holds, then if VL is value of the previous node in inorder, call(G,VL,_,Acc0) must hold, and if VR is the value of the next node in inorder, call(G,VR,Acc1,_) must hold.

    */

    /** @pred rb_key_fold(+ T,+ G,+ Acc0, - AccF)

    For all nodes Key in the tree T, if the value associated with key Key is V in tree T, if call(G,Key,V,Acc1,Acc2) holds, then if VL is value of the previous node in inorder, call(G,KeyL,VL,_,Acc0) must hold, and if VR is the value of the next node in inorder, call(G,KeyR,VR,Acc1,_) must hold.

    */

    /** @pred rb_clone(+ T,+ NT,+ Nodes)

    ``Clone'' the red-back tree into a new tree with the same keys as the original but with all values set to unbound values. Nodes is a list containing all new nodes as pairs K-V.

    */

    /** @pred rb_min(+ T,- Key,- Value)

    Key is the minimum key in T, and is associated with Val.

    */

    /** @pred rb_max(+ T,- Key,- Value)

    Key is the maximal key in T, and is associated with Val.

    */

    /** @pred rb_next(+ T, + Key,- Next,- Value)

    Next is the next element after Key in T, and is associated with Val.

    */

    /** @pred rb_previous(+ T, + Key,- Previous,- Value)

    Previous is the previous element after Key in T, and is associated with Val.

    */

    /** @pred ord_list_to_rbtree(+ L, - T)

    T is the red-black tree corresponding to the mapping in ordered list L.

    @} */

    /** @defgroup RegExp Regular Expressions @ingroup YAPLibrary @{

    This library includes routines to determine whether a regular expression matches part or all of a string. The routines can also return which parts parts of the string matched the expression or subexpressions of it. This library relies on Henry Spencer's C-package and is only available in operating systems that support dynamic loading. The C-code has been obtained from the sources of FreeBSD-4.0 and is protected by copyright from Henry Spencer and from the Regents of the University of California (see the file library/regex/COPYRIGHT for further details).

    Much of the description of regular expressions below is copied verbatim from Henry Spencer's manual page.

    A regular expression is zero or more branches, separated by ``|''. It matches anything that matches one of the branches.

    A branch is zero or more pieces, concatenated. It matches a match for the first, followed by a match for the second, etc.

    A piece is an atom possibly followed by \*'', +'', or ?''. An atom followed by *'' matches a sequence of 0 or more matches of the atom. An atom followed by +'' matches a sequence of 1 or more matches of the atom. An atom followed by ?'' matches a match of the atom, or the null string.

    An atom is a regular expression in parentheses (matching a match for the regular expression), a range (see below), .'' (matching any single character), ^'' (matching the null string at the beginning of the input string), $'' (matching the null string at the end of the input string), a \'' followed by a single character (matching that character), or a single character with no other significance (matching that character).

    A range is a sequence of characters enclosed in []''. It normally matches any single character from the sequence. If the sequence begins with ^'', it matches any single character not from the rest of the sequence. If two characters in the sequence are separated by -'', this is shorthand for the full list of ASCII characters between them (e.g. [0-9]'' matches any decimal digit). To include a literal ]'' in the sequence, make it the first character (following a possible ^''). To include a literal ``-'', make it the first or last character.

    @pred regexp(+ RegExp,+ String,+ Opts)

    Match regular expression RegExp to input string String according to options Opts. The options may be:

    + `nocase`: Causes upper-case characters  in   _String_ to
    

    be treated as lower case during the matching process.

    */

    /** @pred regexp(+ RegExp,+ String,+ Opts,? SubMatchVars)

    Match regular expression RegExp to input string String according to options Opts. The variable SubMatchVars should be originally unbound or a list of unbound variables all will contain a sequence of matches, that is, the head of SubMatchVars will contain the characters in String that matched the leftmost parenthesized subexpression within RegExp, the next head of list will contain the characters that matched the next parenthesized subexpression to the right in RegExp, and so on.

    The options may be:

    + `nocase`: Causes upper-case characters  in   _String_ to
    

    be treated as lower case during the matching process. + indices: Changes what is stored in SubMatchVars. Instead of storing the matching characters from String, each variable will contain a term of the form IO-IF giving the indices in String of the first and last characters in the matching range of characters.

    In general there may be more than one way to match a regular expression to an input string. For example, consider the command

      regexp("(a*)b*","aabaaabb", [], [X,Y])
    

    Considering only the rules given so far, X and Y could end up with the values "aabb" and "aa", "aaab" and "aaa", "ab" and "a", or any of several other combinations. To resolve this potential ambiguity regexp chooses among alternatives using the rule ``first then longest''. In other words, it considers the possible matches in order working from left to right across the input string and the pattern, and it attempts to match longer pieces of the input string before shorter ones. More specifically, the following rules apply in decreasing order of priority:

      + If a regular expression could match two different parts of an input string then it will match the one that begins earliest.
      + If a regular expression contains "|"  operators  then the leftmost matching sub-expression is chosen.
      
      + In \*, +, and ? constructs, longer matches are chosen in preference to shorter ones.
      
      + In sequences of expression  components  the  components are considered from left to right.
      

    In the example from above, "(a\*)b\*" matches "aab": the "(a\*)" portion of the pattern is matched first and it consumes the leading "aa"; then the "b\*" portion of the pattern consumes the next "b". Or, consider the following example:

      regexp("(ab|a)(b*)c",  "abc", [], [X,Y,Z])
    

    After this command X will be "abc", Y will be "ab", and Z will be an empty string. Rule 4 specifies that "(ab|a)" gets first shot at the input string and Rule 2 specifies that the "ab" sub-expression is checked before the "a" sub-expression. Thus the "b" has already been claimed before the "(b\*)" component is checked and (b\*) must match an empty string.

    @} */

    /** @defgroup shlib SWI-Prolog's shlib library @ingroup YAPLibrary @{

    This section discusses the functionality of the (autoload) library(shlib), providing an interface to manage shared libraries.

    One of the files provides a global function install_mylib() that initialises the module using calls to PL_register_foreign(). Here is a simple example file mylib.c, which creates a Windows MessageBox:

    #include <windows.h>
    #include <SWI-Prolog.h>
    
    static foreign_t
    pl_say_hello(term_t to)
    { char *a;
    
      if ( PL_get_atom_chars(to, &a) )
      { MessageBox(NULL, a, "DLL test", MB_OK|MB_TASKMODAL);
    
        PL_succeed;
      }
    
      PL_fail;
    }
    
    install_t
    install_mylib()
    { PL_register_foreign("say_hello", 1, pl_say_hello, 0);
    }
    

    Now write a file mylib.pl:

    :- module(mylib, [ say_hello/1 ]).
    :- use_foreign_library(foreign(mylib)).
    

    The file mylib.pl can be loaded as a normal Prolog file and provides the predicate defined in C.

    */

    /** @pred load_foreign_library(: FileSpec) is det

    */

    /** @pred load_foreign_library(: FileSpec, + Entry:atom) is det

    Load a shared object or DLL. After loading the Entry function is called without arguments. The default entry function is composed from install_, followed by the file base-name. E.g., the load-call below calls the function install_mylib(). If the platform prefixes extern functions with _, this prefix is added before calling.

              ...
              load_foreign_library(foreign(mylib)),
              ...
    

    FileSpec is a specification for absolute_file_name/3. If searching the file fails, the plain name is passed to the OS to try the default method of the OS for locating foreign objects. The default definition of file_search_path/2 searches <prolog home>/lib/Yap.

    See also use_foreign_library/1,2 are intended for use in directives.

    */

    /** @pred [det] use_foreign_library(+ FileSpec), use_foreign_library(+ FileSpec, + Entry:atom)

    Load and install a foreign library as load_foreign_library/1 and load_foreign_library/2 and register the installation using initialization/2 with the option now. This is similar to using:

        :- initialization(load_foreign_library(foreign(mylib))).
    

    but using the initialization/1 wrapper causes the library to be loaded after loading of the file in which it appears is completed, while use_foreign_library/1 loads the library immediately. I.e. the difference is only relevant if the remainder of the file uses functionality of the C-library.

    */

    /** @pred [det]unload_foreign_library(+ FileSpec)

    */

    /** @pred [det]unload_foreign_library(+ FileSpec, + Exit:atom)

    Unload a shared object or DLL. After calling the Exit function, the shared object is removed from the process. The default exit function is composed from uninstall_, followed by the file base-name.

    */

    /** @pred current_foreign_library(? File, ? Public)

    Query currently loaded shared libraries.

    @} */

    /** @defgroup Splay_Trees Splay Trees @ingroup YAPLibrary @{

    Splay trees are explained in the paper "Self-adjusting Binary Search Trees", by D.D. Sleator and R.E. Tarjan, JACM, vol. 32, No.3, July 1985, p. 668. They are designed to support fast insertions, deletions and removals in binary search trees without the complexity of traditional balanced trees. The key idea is to allow the tree to become unbalanced. To make up for this, whenever we find a node, we move it up to the top. We use code by Vijay Saraswat originally posted to the Prolog mailing-list.

    @pred splay_access(- Return,+ Key,? Val,+ Tree,- NewTree)

    If item Key is in tree Tree, return its Val and unify Return with true. Otherwise unify Return with null. The variable NewTree unifies with the new tree.

    */

    /** @pred splay_delete(+ Key,? Val,+ Tree,- NewTree)

    Delete item Key from tree Tree, assuming that it is present already. The variable Val unifies with a value for key Key, and the variable NewTree unifies with the new tree. The predicate will fail if Key is not present.

    */

    /** @pred splay_init(- NewTree)

    Initialize a new splay tree.

    */

    /** @pred splay_insert(+ Key,? Val,+ Tree,- NewTree)

    Insert item Key in tree Tree, assuming that it is not there already. The variable Val unifies with a value for key Key, and the variable NewTree unifies with the new tree. In our implementation, Key is not inserted if it is already there: rather it is unified with the item already in the tree.

    */

    /** @pred splay_join(+ LeftTree,+ RighTree,- NewTree)

    Combine trees LeftTree and RighTree into a single tree NewTree containing all items from both trees. This operation assumes that all items in LeftTree are less than all those in RighTree and destroys both LeftTree and RighTree.

    */

    /** @pred splay_split(+ Key,? Val,+ Tree,- LeftTree,- RightTree)

    Construct and return two trees LeftTree and RightTree, where LeftTree contains all items in Tree less than Key, and RightTree contains all items in Tree greater than Key. This operations destroys Tree.

    @} */

    /** @defgroup String_InputOutput Reading From and Writing To Strings @ingroup YAPLibrary @{

    From Version 4.3.2 onwards YAP implements SICStus Prolog compatible String Input/Output. The library allows users to read from and write to a memory buffer as if it was a file. The memory buffer is built from or converted to a string of character codes by the routines in library. Therefore, if one wants to read from a string the string must be fully instantiated before the library built-in opens the string for reading. These commands are available through the use_module(library(charsio)) command.

    @pred format_to_chars(+ Form, + Args, - Result)

    Execute the built-in procedure format/2 with form Form and arguments Args outputting the result to the string of character codes Result.

    */

    /** @pred format_to_chars(+ Form, + Args, - Result, - Result0)

    Execute the built-in procedure format/2 with form Form and arguments Args outputting the result to the difference list of character codes Result-Result0.

    */

    /** @pred write_to_chars(+ Term, - Result)

    Execute the built-in procedure write/1 with argument Term outputting the result to the string of character codes Result.

    */

    /** @pred write_to_chars(+ Term, - Result0, - Result)

    Execute the built-in procedure write/1 with argument Term outputting the result to the difference list of character codes Result-Result0.

    */

    /** @pred atom_to_chars(+ Atom, - Result)

    Convert the atom Atom to the string of character codes Result.

    */

    /** @pred atom_to_chars(+ Atom, - Result0, - Result)

    Convert the atom Atom to the difference list of character codes Result-Result0.

    */

    /** @pred number_to_chars(+ Number, - Result)

    Convert the number Number to the string of character codes Result.

    */

    /** @pred number_to_chars(+ Number, - Result0, - Result)

    Convert the atom Number to the difference list of character codes Result-Result0.

    */

    /** @pred atom_to_term(+ Atom, - Term, - Bindings)

    Use Atom as input to read_term/2 using the option variable_names and return the read term in Term and the variable bindings in Bindings. Bindings is a list of Name = Var couples, thus providing access to the actual variable names. See also read_term/2. If Atom has no valid syntax, a syntax_error exception is raised.

    */

    /** @pred term_to_atom(? Term, ? Atom)

    True if Atom describes a term that unifies with Term. When Atom is instantiated Atom is converted and then unified with Term. If Atom has no valid syntax, a syntax_error exception is raised. Otherwise Term is ``written'' on Atom using write_term/2 with the option quoted(true).

    */

    /** @pred read_from_chars(+ Chars, - Term)

    Parse the list of character codes Chars and return the result in the term Term. The character codes to be read must terminate with a dot character such that either (i) the dot character is followed by blank characters; or (ii) the dot character is the last character in the string.

    */

    /** @pred open_chars_stream(+ Chars, - Stream)

    Open the list of character codes Chars as a stream Stream.

    */

    /** @pred with_output_to_chars(? Goal, - Chars)

    Execute goal Goal such that its standard output will be sent to a memory buffer. After successful execution the contents of the memory buffer will be converted to the list of character codes Chars.

    */

    /** @pred with_output_to_chars(? Goal, ? Chars0, - Chars)

    Execute goal Goal such that its standard output will be sent to a memory buffer. After successful execution the contents of the memory buffer will be converted to the difference list of character codes Chars-Chars0.

    */

    /** @pred with_output_to_chars(? Goal, - Stream, ? Chars0, - Chars)

    Execute goal Goal such that its standard output will be sent to a memory buffer. After successful execution the contents of the memory buffer will be converted to the difference list of character codes Chars-Chars0 and Stream receives the stream corresponding to the memory buffer.

    The implementation of the character IO operations relies on three YAP built-ins:

    @pred charsio:open_mem_read_stream(+ String, - Stream) Store a string in a memory buffer and output a stream that reads from this memory buffer.

    */

    /** @pred charsio:open_mem_write_stream(- Stream) Create a new memory buffer and output a stream that writes to it.

    */

    /** @pred charsio:peek_mem_write_stream(- Stream, L0, L) Convert the memory buffer associated with stream Stream to the difference list of character codes L-L0.

    These built-ins are initialized to belong to the module charsio in init.yap. Novel procedures for manipulating strings by explicitly importing these built-ins.

    YAP does not currently support opening a charsio stream in append mode, or seeking in such a stream.

    @} */

    /** @defgroup System Calling The Operating System from YAP @ingroup YAPLibrary @{

    YAP now provides a library of system utilities compatible with the SICStus Prolog system library. This library extends and to some point replaces the functionality of Operating System access routines. The library includes Unix/Linux and Win32 C code. They are available through the use_module(library(system)) command.

    @pred datime(datime(- Year, - Month, - DayOfTheMonth,

    • Hour, - Minute, - Second)

    The datime/1 procedure returns the current date and time, with information on Year, Month, DayOfTheMonth, Hour, Minute, and Second. The Hour is returned on local time. This function uses the WIN32 GetLocalTime function or the Unix localtime function.

       ?- datime(X).
    
    X = datime(2001,5,28,15,29,46) ? 
    

    */

    /** @pred mktime(datime(+ Year, + Month, + DayOfTheMonth,

    • Hour, + Minute, + Second), - Seconds)

    The mktime/1 procedure returns the number of Seconds elapsed since 00:00:00 on January 1, 1970, Coordinated Universal Time (UTC). The user provides information on Year, Month, DayOfTheMonth, Hour, Minute, and Second. The Hour is given on local time. This function uses the WIN32 GetLocalTime function or the Unix mktime function.

       ?- mktime(datime(2001,5,28,15,29,46),X).
    
    X = 991081786 ? ;
    

    */

    /** @pred delete_file(+ File)

    The delete_file/1 procedure removes file File. If File is a directory, remove the directory and all its subdirectories.

       ?- delete_file(x).
    

    */

    /** @pred delete_file(+ File,+ Opts)

    The delete_file/2 procedure removes file File according to options Opts. These options are directory if one should remove directories, recursive if one should remove directories recursively, and ignore if errors are not to be reported.

    This example is equivalent to using the delete_file/1 predicate:

       ?- delete_file(x, [recursive]).
    

    */

    /** @pred directory_files(+ Dir,+ List)

    Given a directory Dir, directory_files/2 procedures a listing of all files and directories in the directory:

        ?- directory_files('.',L), writeq(L).
    ['Makefile.~1~','sys.so','Makefile','sys.o',x,..,'.']
    

    The predicates uses the dirent family of routines in Unix environments, and findfirst in WIN32.

    */

    /** @pred file_exists(+ File)

    The atom File corresponds to an existing file.

    */

    /** @pred file_exists(+ File,+ Permissions)

    The atom File corresponds to an existing file with permissions compatible with Permissions. YAP currently only accepts for permissions to be described as a number. The actual meaning of this number is Operating System dependent.

    */

    /** @pred file_property(+ File,? Property)

    The atom File corresponds to an existing file, and Property will be unified with a property of this file. The properties are of the form type( _Type_), which gives whether the file is a regular file, a directory, a fifo file, or of unknown type; size( _Size_), with gives the size for a file, and mod_time( _Time_), which gives the last time a file was modified according to some Operating System dependent timestamp; mode( _mode_), gives the permission flags for the file, and linkto( _FileName_), gives the file pointed to by a symbolic link. Properties can be obtained through backtracking:

       ?- file_property('Makefile',P).
    
    P = type(regular) ? ;
    
    P = size(2375) ? ;
    
    P = mod_time(990826911) ? ;
    
    no
    

    */

    /** @pred make_directory(+ Dir)

    Create a directory Dir. The name of the directory must be an atom.

    */

    /** @pred rename_file(+ OldFile,+ NewFile)

    Create file OldFile to NewFile. This predicate uses the C built-in function rename.

    */

    /** @pred environ(? EnvVar,+ EnvValue)

    Unify environment variable EnvVar with its value EnvValue, if there is one. This predicate is backtrackable in Unix systems, but not currently in Win32 configurations.

       ?- environ('HOME',X).
    
    X = 'C:\\cygwin\\home\\administrator' ?
    

    */

    /** @pred host_id(- Id)

    Unify Id with an identifier of the current host. YAP uses the hostid function when available,

    */

    /** @pred host_name(- Name)

    Unify Name with a name for the current host. YAP uses the hostname function in Unix systems when available, and the GetComputerName function in WIN32 systems.

    */

    /** @pred kill( Id,+ SIGNAL)

    Send signal SIGNAL to process Id. In Unix this predicate is a direct interface to kill so one can send signals to groups of processes. In WIN32 the predicate is an interface to TerminateProcess, so it kills Id independently of SIGNAL.

    */

    /** @pred mktemp( Spec,- File)

    Direct interface to mktemp: given a Spec, that is a file name with six X to it, create a file name File. Use tmpnam/1 instead.

    */

    /** @pred pid(- Id)

    Unify Id with the process identifier for the current process. An interface to the getpid function.

    */

    /** @pred tmpnam(- File)

    Interface with tmpnam: obtain a new, unique file name File.

    */

    /** @pred tmp_file(- File)

    Create a name for a temporary file. Base is an user provided identifier for the category of file. The TmpName is guaranteed to be unique. If the system halts, it will automatically remove all created temporary files.

    */

    /** @pred exec(+ Command,[+ InputStream,+ OutputStream,+ ErrorStream],- PID)

    Execute command Command with its streams connected to InputStream, OutputStream, and ErrorStream. The process that executes the command is returned as PID. The command is executed by the default shell bin/sh -c in Unix.

    The following example demonstrates the use of exec/3 to send a command and process its output:

    exec(ls,[std,pipe(S),null],P),repeat, get0(S,C), (C = -1, close(S) ! ; put(C)).
    

    The streams may be one of standard stream, std, null stream, null, or pipe(S), where S is a pipe stream. Note that it is up to the user to close the pipe.

    */

    /** @pred popen(+ Command, + TYPE, - Stream)

    Interface to the popen function. It opens a process by creating a pipe, forking and invoking Command on the current shell. Since a pipe is by definition unidirectional the Type argument may be read or write, not both. The stream should be closed using close/1, there is no need for a special pclose command.

    The following example demonstrates the use of popen/3 to process the output of a command, as exec/3 would do:

       ?- popen(ls,read,X),repeat, get0(X,C), (C = -1, ! ; put(C)).
    
    X = 'C:\\cygwin\\home\\administrator' ?
    

    The WIN32 implementation of popen/3 relies on exec/3.

    */

    /** @pred shell

    Start a new shell and leave YAP in background until the shell completes. YAP uses the shell given by the environment variable SHELL. In WIN32 environment YAP will use COMSPEC if SHELL is undefined.

    */

    /** @pred shell(+ Command)

    Execute command Command under a new shell. YAP will be in background until the command completes. In Unix environments YAP uses the shell given by the environment variable SHELL with the option " -c ". In WIN32 environment YAP will use COMSPEC if SHELL is undefined, in this case with the option " /c ".

    */

    /** @pred shell(+ Command,- Status)

    Execute command Command under a new shell and unify Status with the exit for the command. YAP will be in background until the command completes. In Unix environments YAP uses the shell given by the environment variable SHELL with the option " -c ". In WIN32 environment YAP will use COMSPEC if SHELL is undefined, in this case with the option " /c ".

    */

    /** @pred sleep(+ Time)

    Block the current thread for Time seconds. When YAP is compiled without multi-threading support, this predicate blocks the YAP process. The number of seconds must be a positive number, and it may an integer or a float. The Unix implementation uses usleep if the number of seconds is below one, and sleep if it is over a second. The WIN32 implementation uses Sleep for both cases.

    */

    /** @pred system

    Start a new default shell and leave YAP in background until the shell completes. YAP uses /bin/sh in Unix systems and COMSPEC in WIN32.

    */

    /** @pred system(+ Command,- Res)

    Interface to system: execute command Command and unify Res with the result.

    */

    /** @pred wait(+ PID,- Status)

    Wait until process PID terminates, and return its exits Status.

    @} */

    /** @defgroup Terms Utilities On Terms @ingroup YAPLibrary @{

    The next routines provide a set of commonly used utilities to manipulate terms. Most of these utilities have been implemented in C for efficiency. They are available through the use_module(library(terms)) command.

    @pred cyclic_term(? Term)

    Succeed if the argument Term is not a cyclic term.

    */

    /** @pred term_hash(+ Term, ? Hash)

    If Term is ground unify Hash with a positive integer calculated from the structure of the term. Otherwise the argument Hash is left unbound. The range of the positive integer is from 0 to, but not including, 33554432.

    */

    /** @pred term_hash(+ Term, + Depth, + Range, ? Hash)

    Unify Hash with a positive integer calculated from the structure of the term. The range of the positive integer is from 0 to, but not including, Range. If Depth is -1 the whole term is considered. Otherwise, the term is considered only up to depth 1, where the constants and the principal functor have depth 1, and an argument of a term with depth I has depth I+1.

    */

    /** @pred variables_within_term(+ Variables,? Term, - OutputVariables)

    Unify OutputVariables with the subset of the variables Variables that occurs in Term.

    */

    /** @pred new_variables_in_term(+ Variables,? Term, - OutputVariables)

    Unify OutputVariables with all variables occurring in Term that are not in the list Variables.

    */

    /** @pred variant(? Term1, ? Term2)

    Succeed if Term1 and Term2 are variant terms.

    */

    /** @pred subsumes(? Term1, ? Term2)

    Succeed if Term1 subsumes Term2. Variables in term Term1 are bound so that the two terms become equal.

    */

    /** @pred subsumes_chk(? Term1, ? Term2)

    Succeed if Term1 subsumes Term2 but does not bind any variable in Term1.

    */

    /** @pred variable_in_term(? Term,? Var)

    Succeed if the second argument Var is a variable and occurs in term Term.

    */

    /** @pred unifiable(? Term1, ? Term2, - Bindings)

    Succeed if Term1 and Term2 are unifiable with substitution Bindings.

    @} */

    /** @defgroup Tries Trie DataStructure @ingroup YAPLibrary @{

    The next routines provide a set of utilities to create and manipulate prefix trees of Prolog terms. Tries were originally proposed to implement tabling in Logic Programming, but can be used for other purposes. The tries will be stored in the Prolog database and can seen as alternative to assert and record family of primitives. Most of these utilities have been implemented in C for efficiency. They are available through the use_module(library(tries)) command.

    */

    /** @pred trie_open(- Id)

    Open a new trie with identifier Id.

    */

    /** @pred trie_close(+ Id)

    Close trie with identifier Id.

    */

    /** @pred trie_close_all

    Close all available tries.

    */

    /** @pred trie_mode(? Mode)

    Unify Mode with trie operation mode. Allowed values are either std (default) or rev.

    */

    /** @pred trie_put_entry(+ Trie,+ Term,- Ref)

    Add term Term to trie Trie. The handle Ref gives a reference to the term.

    */

    /** @pred trie_check_entry(+ Trie,+ Term,- Ref)

    Succeeds if a variant of term Term is in trie Trie. An handle Ref gives a reference to the term.

    */

    /** @pred trie_get_entry(+ Ref,- Term)

    Unify Term with the entry for handle Ref.

    */

    /** @pred trie_remove_entry(+ Ref)

    Remove entry for handle Ref.

    */

    /** @pred trie_remove_subtree(+ Ref)

    Remove subtree rooted at handle Ref.

    */

    /** @pred trie_save(+ Trie,+ FileName)

    Dump trie Trie into file FileName.

    */

    /** @pred trie_load(+ Trie,+ FileName)

    Load trie Trie from the contents of file FileName.

    */

    /** @pred trie_stats(- Memory,- Tries,- Entries,- Nodes)

    Give generic statistics on tries, including the amount of memory, Memory, the number of tries, Tries, the number of entries, Entries, and the total number of nodes, Nodes.

    */

    /** @pred trie_max_stats(- Memory,- Tries,- Entries,- Nodes)

    Give maximal statistics on tries, including the amount of memory, Memory, the number of tries, Tries, the number of entries, Entries, and the total number of nodes, Nodes.

    */

    /** @pred trie_usage(+ Trie,- Entries,- Nodes,- VirtualNodes)

    Give statistics on trie Trie, the number of entries, Entries, and the total number of nodes, Nodes, and the number of VirtualNodes.

    */

    /** @pred trie_print(+ Trie)

    Print trie Trie on standard output.

    @} */

    /** @defgroup Cleanup Call Cleanup @ingroup YAPLibrary @{

    call_cleanup/1 and call_cleanup/2 allow predicates to register code for execution after the call is finished. Predicates can be declared to be fragile to ensure that call_cleanup is called for any Goal which needs it. This library is loaded with the use_module(library(cleanup)) command.

    */

    /** @pred :- fragile P,...., Pn

    Declares the predicate P=[module:]name/arity as a fragile predicate, module is optional, default is the current typein_module. Whenever such a fragile predicate is used in a query it will be called through call_cleanup/1.

    :- fragile foo/1,bar:baz/2.
    

    */

    /** @pred call_cleanup(: Goal)

    Execute goal Goal within a cleanup-context. Called predicates might register cleanup Goals which are called right after the end of the call to Goal. Cuts and exceptions inside Goal do not prevent the execution of the cleanup calls. call_cleanup might be nested.

    */

    /** @pred call_cleanup(: Goal, : CleanUpGoal)

    This is similar to call_cleanup/1 with an additional CleanUpGoal which gets called after Goal is finished.

    */

    /** @pred setup_call_cleanup(: Setup,: Goal, : CleanUpGoal)

    Calls (Setup, Goal). For each sucessful execution of Setup, calling Goal, the cleanup handler Cleanup is guaranteed to be called exactly once. This will happen after Goal completes, either through failure, deterministic success, commit, or an exception. Setup will contain the goals that need to be protected from asynchronous interrupts such as the ones received from call_with_time_limit/2 or thread_signal/2. In most uses, Setup will perform temporary side-effects required by Goal that are finally undone by Cleanup.

    Success or failure of Cleanup is ignored and choice-points it created are destroyed (as once/1). If Cleanup throws an exception, this is executed as normal.

    Typically, this predicate is used to cleanup permanent data storage required to execute Goal, close file-descriptors, etc. The example below provides a non-deterministic search for a term in a file, closing the stream as needed.

    term_in_file(Term, File) :-
        setup_call_cleanup(open(File, read, In),
                   term_in_stream(Term, In),
                   close(In) ).
    
    term_in_stream(Term, In) :-
        repeat,
        read(In, T),
        (   T == end_of_file
        ->  !, fail
        ;   T = Term
        ).
    

    Note that it is impossible to implement this predicate in Prolog other than by reading all terms into a list, close the file and call member/2. Without setup_call_cleanup/3 there is no way to gain control if the choice-point left by repeat is removed by a cut or an exception.

    setup_call_cleanup/2 can also be used to test determinism of a goal:

    ?- setup_call_cleanup(true,(X=1;X=2), Det=yes).
    
    X = 1 ;
    
    X = 2,
    Det = yes ;
    

    This predicate is under consideration for inclusion into the ISO standard. For compatibility with other Prolog implementations see call_cleanup/2.

    */

    /** @pred setup_call_catcher_cleanup(: Setup,: Goal, + Catcher,: CleanUpGoal)

    Similar to setup_call_cleanup( _Setup_, _Goal_, _Cleanup_) with additional information on the reason of calling Cleanup. Prior to calling Cleanup, Catcher unifies with the termination code. If this unification fails, Cleanup is not called.

    */

    /** @pred on_cleanup(+ CleanUpGoal)

    Any Predicate might registers a CleanUpGoal. The CleanUpGoal is put onto the current cleanup context. All such CleanUpGoals are executed in reverse order of their registration when the surrounding cleanup-context ends. This call will throw an exception if a predicate tries to register a CleanUpGoal outside of any cleanup-context.

    */

    /** @pred cleanup_all

    Calls all pending CleanUpGoals and resets the cleanup-system to an initial state. Should only be used as one of the last calls in the main program.

    There are some private predicates which could be used in special cases, such as manually setting up cleanup-contexts and registering CleanUpGoals for other than the current cleanup-context. Read the Source Luke.

    @} */

    /** @defgroup Timeout Calls With Timeout @ingroup YAPLibrary @{

    The time_out/3 command relies on the alarm/3 built-in to implement a call with a maximum time of execution. The command is available with the use_module(library(timeout)) command.

    @pred time_out(+ Goal, + Timeout, - Result)

    Execute goal Goal with time limited Timeout, where Timeout is measured in milliseconds. If the goal succeeds, unify Result with success. If the timer expires before the goal terminates, unify Result with time_out.

    This command is implemented by activating an alarm at procedure entry. If the timer expires before the goal completes, the alarm will throw an exception timeout.

    One should note that time_out/3 is not reentrant, that is, a goal called from time_out should never itself call time_out/3. Moreover, time_out/3 will deactivate any previous alarms set by alarm/3 and vice-versa, hence only one of these calls should be used in a program.

    Last, even though the timer is set in milliseconds, the current implementation relies on alarm/3, and therefore can only offer precision on the scale of seconds.

    @} */

    /** @defgroup Trees Updatable Binary Trees @ingroup YAPLibrary @{

    The following queue manipulation routines are available once included with the use_module(library(trees)) command.

    @pred get_label(+ Index, + Tree, ? Label)

    Treats the tree as an array of N elements and returns the Index-th.

    */

    /** @pred list_to_tree(+ List, - Tree)

    Takes a given List of N elements and constructs a binary Tree.

    */

    /** @pred map_tree(+ Pred, + OldTree, - NewTree)

    Holds when OldTree and NewTree are binary trees of the same shape and Pred(Old,New) is true for corresponding elements of the two trees.

    */

    /** @pred put_label(+ Index, + OldTree, + Label, - NewTree)

    constructs a new tree the same shape as the old which moreover has the same elements except that the Index-th one is Label.

    */

    /** @pred tree_size(+ Tree, - Size)

    Calculates the number of elements in the Tree.

    */

    /** @pred tree_to_list(+ Tree, - List)

    Is the converse operation to list_to_tree.

    @} */

    /** @defgroup UGraphs Unweighted Graphs @ingroup YAPLibrary @{

    The following graph manipulation routines are based in code originally written by Richard O'Keefe. The code was then extended to be compatible with the SICStus Prolog ugraphs library. The routines assume directed graphs, undirected graphs may be implemented by using two edges. Graphs are represented in one of two ways:

    + The P-representation of a graph is a list of (from-to) vertex
    

    pairs, where the pairs can be in any old order. This form is convenient for input/output.

    */

    /** @pred The S-representation of a graph is a list of (vertex-neighbors) pairs, where the pairs are in standard order (as produced by keysort) and the neighbors of each vertex are also in standard order (as produced by sort). This form is convenient for many calculations.

    These built-ins are available once included with the use_module(library(ugraphs)) command.

    @pred vertices_edges_to_ugraph(+ Vertices, + Edges, - Graph)

    Given a graph with a set of vertices Vertices and a set of edges Edges, Graph must unify with the corresponding s-representation. Note that the vertices without edges will appear in Vertices but not in Edges. Moreover, it is sufficient for a vertex to appear in Edges.

    ?- vertices_edges_to_ugraph([],[1-3,2-4,4-5,1-5],L).
    
    L = [1-[3,5],2-[4],3-[],4-[5],5-[]] ? 
    
    

    In this case all edges are defined implicitly. The next example shows three unconnected edges:

    ?- vertices_edges_to_ugraph([6,7,8],[1-3,2-4,4-5,1-5],L).
    
    L = [1-[3,5],2-[4],3-[],4-[5],5-[],6-[],7-[],8-[]] ? 
    
    

    */

    /** @pred vertices(+ Graph, - Vertices)

    Unify Vertices with all vertices appearing in graph Graph. In the next example:

    ?- vertices([1-[3,5],2-[4],3-[],4-[5],5-[]], V).
    
    L = [1,2,3,4,5]
    

    */

    /** @pred edges(+ Graph, - Edges)

    Unify Edges with all edges appearing in graph Graph. In the next example:

    ?- vertices([1-[3,5],2-[4],3-[],4-[5],5-[]], V).
    
    L = [1,2,3,4,5]
    

    */

    /** @pred add_vertices(+ Graph, + Vertices, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the list of vertices Vertices to the graph Graph. In the next example:

    ?- add_vertices([1-[3,5],2-[4],3-[],4-[5],
                     5-[],6-[],7-[],8-[]],
                    [0,2,9,10,11],
                       NG).
    
    NG = [0-[],1-[3,5],2-[4],3-[],4-[5],5-[],
          6-[],7-[],8-[],9-[],10-[],11-[]]
    

    */

    /** @pred del_vertices(+ Graph, + Vertices, - NewGraph)

    Unify NewGraph with a new graph obtained by deleting the list of vertices Vertices and all the edges that start from or go to a vertex in Vertices to the graph Graph. In the next example:

    ?- del_vertices([2,1],[1-[3,5],2-[4],3-[],
                     4-[5],5-[],6-[],7-[2,6],8-[]],NL).
    
    NL = [3-[],4-[5],5-[],6-[],7-[6],8-[]]
    

    */

    /** @pred add_edges(+ Graph, + Edges, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the list of edges Edges to the graph Graph. In the next example:

    ?- add_edges([1-[3,5],2-[4],3-[],4-[5],5-[],6-[],
                  7-[],8-[]],[1-6,2-3,3-2,5-7,3-2,4-5],NL).
    
    NL = [1-[3,5,6],2-[3,4],3-[2],4-[5],5-[7],6-[],7-[],8-[]]
    

    */

    /** @pred del_edges(+ Graph, + Edges, - NewGraph)

    Unify NewGraph with a new graph obtained by removing the list of edges Edges from the graph Graph. Notice that no vertices are deleted. In the next example:

    ?- del_edges([1-[3,5],2-[4],3-[],4-[5],5-[],
                  6-[],7-[],8-[]],
                 [1-6,2-3,3-2,5-7,3-2,4-5,1-3],NL).
    
    NL = [1-[5],2-[4],3-[],4-[],5-[],6-[],7-[],8-[]]
    

    */

    /** @pred transpose(+ Graph, - NewGraph)

    Unify NewGraph with a new graph obtained from Graph by replacing all edges of the form V1-V2 by edges of the form V2-V1. The cost is O(|V|^2). In the next example:

    ?- transpose([1-[3,5],2-[4],3-[],
                  4-[5],5-[],6-[],7-[],8-[]], NL).
    
    NL = [1-[],2-[],3-[1],4-[2],5-[1,4],6-[],7-[],8-[]]
    

    Notice that an undirected graph is its own transpose.

    */

    /** @pred neighbors(+ Vertex, + Graph, - Vertices)

    Unify Vertices with the list of neighbors of vertex Vertex in Graph. If the vertice is not in the graph fail. In the next example:

    ?- neighbors(4,[1-[3,5],2-[4],3-[],
                    4-[1,2,7,5],5-[],6-[],7-[],8-[]],
                 NL).
    
    NL = [1,2,7,5]
    

    */

    /** @pred neighbours(+ Vertex, + Graph, - Vertices)

    Unify Vertices with the list of neighbours of vertex Vertex in Graph. In the next example:

    ?- neighbours(4,[1-[3,5],2-[4],3-[],
                     4-[1,2,7,5],5-[],6-[],7-[],8-[]], NL).
    
    NL = [1,2,7,5]
    

    */

    /** @pred complement(+ Graph, - NewGraph)

    Unify NewGraph with the graph complementary to Graph. In the next example:

    ?- complement([1-[3,5],2-[4],3-[],
                   4-[1,2,7,5],5-[],6-[],7-[],8-[]], NL).
    
    NL = [1-[2,4,6,7,8],2-[1,3,5,6,7,8],3-[1,2,4,5,6,7,8],
          4-[3,5,6,8],5-[1,2,3,4,6,7,8],6-[1,2,3,4,5,7,8],
          7-[1,2,3,4,5,6,8],8-[1,2,3,4,5,6,7]]
    

    */

    /** @pred compose(+ LeftGraph, + RightGraph, - NewGraph)

    Compose the graphs LeftGraph and RightGraph to form NewGraph. In the next example:

    ?- compose([1-[2],2-[3]],[2-[4],3-[1,2,4]],L).
    
    L = [1-[4],2-[1,2,4],3-[]]
    

    */

    /** @pred top_sort(+ Graph, - Sort)

    Generate the set of nodes Sort as a topological sorting of graph Graph, if one is possible. In the next example we show how topological sorting works for a linear graph:

    ?- top_sort([_138-[_219],_219-[_139], _139-[]],L).
    
    L = [_138,_219,_139]
    

    */

    /** @pred top_sort(+ Graph, - Sort0, - Sort)

    Generate the difference list Sort- Sort0 as a topological sorting of graph Graph, if one is possible.

    */

    /** @pred transitive_closure(+ Graph, + Closure)

    Generate the graph Closure as the transitive closure of graph Graph. In the next example:

    ?- transitive_closure([1-[2,3],2-[4,5],4-[6]],L).
    
    L = [1-[2,3,4,5,6],2-[4,5,6],4-[6]]
    

    */

    /** @pred reachable(+ Node, + Graph, - Vertices)

    Unify Vertices with the set of all vertices in graph Graph that are reachable from Node. In the next example:

    ?- reachable(1,[1-[3,5],2-[4],3-[],4-[5],5-[]],V).
    
    V = [1,3,5]
    

    @} */

    /** @defgroup DGraphs Directed Graphs @ingroup YAPLibrary @{

    The following graph manipulation routines use the red-black tree library to try to avoid linear-time scans of the graph for all graph operations. Graphs are represented as a red-black tree, where the key is the vertex, and the associated value is a list of vertices reachable from that vertex through an edge (ie, a list of edges).

    @pred dgraph_new(+ Graph)

    Create a new directed graph. This operation must be performed before trying to use the graph.

    */

    /** @pred dgraph_vertices(+ Graph, - Vertices)

    Unify Vertices with all vertices appearing in graph Graph.

    */

    /** @pred dgraph_edge(+ N1, + N2, + Graph)

    Edge N1- N2 is an edge in directed graph Graph.

    */

    /** @pred dgraph_edges(+ Graph, - Edges)

    Unify Edges with all edges appearing in graph Graph.

    */

    /** @pred dgraph_add_vertices(+ Graph, + Vertex, - NewGraph)

    Unify NewGraph with a new graph obtained by adding vertex Vertex to the graph Graph.

    */

    /** @pred dgraph_add_vertices(+ Graph, + Vertices, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the list of vertices Vertices to the graph Graph.

    */

    /** @pred dgraph_del_vertex(+ Graph, + Vertex, - NewGraph)

    Unify NewGraph with a new graph obtained by deleting vertex Vertex and all the edges that start from or go to Vertex to the graph Graph.

    */

    /** @pred dgraph_del_vertices(+ Graph, + Vertices, - NewGraph)

    Unify NewGraph with a new graph obtained by deleting the list of vertices Vertices and all the edges that start from or go to a vertex in Vertices to the graph Graph.

    */

    /** @pred dgraph_add_edge(+ Graph, + N1, + N2, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the edge N1- N2 to the graph Graph.

    */

    /** @pred dgraph_add_edges(+ Graph, + Edges, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the list of edges Edges to the graph Graph.

    */

    /** @pred dgraph_del_edge(+ Graph, + N1, + N2, - NewGraph)

    Succeeds if NewGraph unifies with a new graph obtained by removing the edge N1- N2 from the graph Graph. Notice that no vertices are deleted.

    */

    /** @pred dgraph_del_edges(+ Graph, + Edges, - NewGraph)

    Unify NewGraph with a new graph obtained by removing the list of edges Edges from the graph Graph. Notice that no vertices are deleted.

    */

    /** @pred dgraph_to_ugraph(+ Graph, - UGraph)

    Unify UGraph with the representation used by the ugraphs unweighted graphs library, that is, a list of the form V-Neighbors, where V is a node and Neighbors the nodes children.

    */

    /** @pred ugraph_to_dgraph( + UGraph, - Graph)

    Unify Graph with the directed graph obtain from UGraph, represented in the form used in the ugraphs unweighted graphs library.

    */

    /** @pred dgraph_neighbors(+ Vertex, + Graph, - Vertices)

    Unify Vertices with the list of neighbors of vertex Vertex in Graph. If the vertice is not in the graph fail.

    */

    /** @pred dgraph_neighbours(+ Vertex, + Graph, - Vertices)

    Unify Vertices with the list of neighbours of vertex Vertex in Graph.

    */

    /** @pred dgraph_complement(+ Graph, - NewGraph)

    Unify NewGraph with the graph complementary to Graph.

    */

    /** @pred dgraph_transpose(+ Graph, - Transpose)

    Unify NewGraph with a new graph obtained from Graph by replacing all edges of the form V1-V2 by edges of the form V2-V1.

    */

    /** @pred dgraph_compose(+ Graph1, + Graph2, - ComposedGraph)

    Unify ComposedGraph with a new graph obtained by composing Graph1 and Graph2, ie, ComposedGraph has an edge V1-V2 iff there is a V such that V1-V in Graph1 and V-V2 in Graph2.

    */

    /** @pred dgraph_transitive_closure(+ Graph, - Closure)

    Unify Closure with the transitive closure of graph Graph.

    */

    /** @pred dgraph_symmetric_closure(+ Graph, - Closure)

    Unify Closure with the symmetric closure of graph Graph, that is, if Closure contains an edge U-V it must also contain the edge V-U.

    */

    /** @pred dgraph_top_sort(+ Graph, - Vertices)

    Unify Vertices with the topological sort of graph Graph.

    */

    /** @pred dgraph_top_sort(+ Graph, - Vertices, ? Vertices0)

    Unify the difference list Vertices- Vertices0 with the topological sort of graph Graph.

    */

    /** @pred dgraph_min_path(+ V1, + V1, + Graph, - Path, ? Costt)

    Unify the list Path with the minimal cost path between nodes N1 and N2 in graph Graph. Path Path has cost Cost.

    */

    /** @pred dgraph_max_path(+ V1, + V1, + Graph, - Path, ? Costt)

    Unify the list Path with the maximal cost path between nodes N1 and N2 in graph Graph. Path Path has cost Cost.

    */

    /** @pred dgraph_min_paths(+ V1, + Graph, - Paths)

    Unify the list Paths with the minimal cost paths from node N1 to the nodes in graph Graph.

    */

    /** @pred dgraph_isomorphic(+ Vs, + NewVs, + G0, - GF)

    Unify the list GF with the graph isomorphic to G0 where vertices in Vs map to vertices in NewVs.

    */

    /** @pred dgraph_path(+ Vertex, + Graph, ? Path)

    The path Path is a path starting at vertex Vertex in graph Graph.

    */

    /** @pred dgraph_path(+ Vertex, + Vertex1, + Graph, ? Path)

    The path Path is a path starting at vertex Vertex in graph Graph and ending at path Vertex2.

    */

    /** @pred dgraph_reachable(+ Vertex, + Graph, ? Edges)

    The path Path is a path starting at vertex Vertex in graph Graph.

    */

    /** @pred dgraph_leaves(+ Graph, ? Vertices)

    The vertices Vertices have no outgoing edge in graph Graph.

    @} */

    /** @defgroup UnDGraphs Undirected Graphs @ingroup YAPLibrary @{

    The following graph manipulation routines use the red-black tree graph library to implement undirected graphs. Mostly, this is done by having two directed edges per undirected edge.

    @pred undgraph_new(+ Graph)

    Create a new directed graph. This operation must be performed before trying to use the graph.

    */

    /** @pred undgraph_vertices(+ Graph, - Vertices)

    Unify Vertices with all vertices appearing in graph Graph.

    */

    /** @pred undgraph_edge(+ N1, + N2, + Graph)

    Edge N1- N2 is an edge in undirected graph Graph.

    */

    /** @pred undgraph_edges(+ Graph, - Edges)

    Unify Edges with all edges appearing in graph Graph.

    */

    /** @pred undgraph_add_vertices(+ Graph, + Vertices, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the list of vertices Vertices to the graph Graph.

    */

    /** @pred undgraph_del_vertices(+ Graph, + Vertices, - NewGraph)

    Unify NewGraph with a new graph obtained by deleting the list of vertices Vertices and all the edges that start from or go to a vertex in Vertices to the graph Graph.

    */

    /** @pred undgraph_add_edges(+ Graph, + Edges, - NewGraph)

    Unify NewGraph with a new graph obtained by adding the list of edges Edges to the graph Graph.

    */

    /** @pred undgraph_del_edges(+ Graph, + Edges, - NewGraph)

    Unify NewGraph with a new graph obtained by removing the list of edges Edges from the graph Graph. Notice that no vertices are deleted.

    */

    /** @pred undgraph_neighbors(+ Vertex, + Graph, - Vertices)

    Unify Vertices with the list of neighbors of vertex Vertex in Graph. If the vertice is not in the graph fail.

    */

    /** @pred undgraph_neighbours(+ Vertex, + Graph, - Vertices)

    Unify Vertices with the list of neighbours of vertex Vertex in Graph.

    */

    /** @pred undgraph_complement(+ Graph, - NewGraph)

    Unify NewGraph with the graph complementary to Graph.

    */

    /** @pred dgraph_to_undgraph( + DGraph, - UndGraph)

    Unify UndGraph with the undirected graph obtained from the directed graph DGraph.

    @} */

    /** @defgroup DBUsage Memory Usage in Prolog Data-Base @ingroup YAPLibrary @{

    This library provides a set of utilities for studying memory usage in YAP. The following routines are available once included with the use_module(library(dbusage)) command.

    */

    /** @pred db_usage

    Give general overview of data-base usage in the system.

    */

    /** @pred db_static

    List memory usage for every static predicate.

    */

    /** @pred db_static(+ Threshold)

    List memory usage for every static predicate. Predicate must use more than Threshold bytes.

    */

    /** @pred db_dynamic

    List memory usage for every dynamic predicate.

    */

    /** @pred db_dynamic(+ Threshold)

    List memory usage for every dynamic predicate. Predicate must use more than Threshold bytes.

    @} */

    /** @defgroup Lambda Lambda Expressions @ingroup YAPLibrary @{

    This library, designed and implemented by Ulrich Neumerkel, provides lambda expressions to simplify higher order programming based on call/N.

    Lambda expressions are represented by ordinary Prolog terms. There are two kinds of lambda expressions:

        Free+\X1^X2^ ..^XN^Goal
    
             \X1^X2^ ..^XN^Goal
    

    The second is a shorthand for t+\\X1^X2^..^XN^Goal, where Xi are the parameters.

    Goal is a goal or continuation (Syntax note: Operators within Goal require parentheses due to the low precedence of the ^ operator).

    Free contains variables that are valid outside the scope of the lambda expression. They are thus free variables within.

    All other variables of Goal are considered local variables. They must not appear outside the lambda expression. This restriction is currently not checked. Violations may lead to unexpected bindings.

    In the following example the parentheses around X\>3 are necessary.

    ?- use_module(library(lambda)).
    ?- use_module(library(apply)).
    
    ?- maplist(\X^(X>3),[4,5,9]).
    true.
    

    In the following X is a variable that is shared by both instances of the lambda expression. The second query illustrates the cooperation of continuations and lambdas. The lambda expression is in this case a continuation expecting a further argument.

    ?- Xs = [A,B], maplist(X+\Y^dif(X,Y), Xs).
    Xs = [A, B],
    dif(X, A),
    dif(X, B).
    
    ?- Xs = [A,B], maplist(X+\dif(X), Xs).
    Xs = [A, B],
    dif(X, A),
    dif(X, B).
    
    

    The following queries are all equivalent. To see this, use the fact f(x,y).

    ?- call(f,A1,A2).
    ?- call(\X^f(X),A1,A2).
    ?- call(\X^Y^f(X,Y), A1,A2).                                                                                                            
    ?- call(\X^(X+\Y^f(X,Y)), A1,A2).
    ?- call(call(f, A1),A2).
    ?- call(f(A1),A2).
    ?- f(A1,A2).
    A1 = x,
    A2 = y.
    

    Further discussions at Ulrich Neumerker's page in http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/ISO-Hiord.

    @} */

    /** @defgroup LAM LAM @ingroup YAPPackages @{

    This library provides a set of utilities for interfacing with LAM MPI. The following routines are available once included with the use_module(library(lam_mpi)) command. The yap should be invoked using the LAM mpiexec or mpirun commands (see LAM manual for more details).

    */

    /** @pred mpi_init

    Sets up the mpi environment. This predicate should be called before any other MPI predicate.

    */

    /** @pred mpi_finalize

    Terminates the MPI execution environment. Every process must call this predicate before exiting.

    */

    /** @pred mpi_comm_size(- Size)

    Unifies Size with the number of processes in the MPI environment.

    */

    /** @pred mpi_comm_rank(- Rank)

    Unifies Rank with the rank of the current process in the MPI environment.

    */

    /** @pred mpi_version(- Major,- Minor)

    Unifies Major and Minor with, respectively, the major and minor version of the MPI.

    */

    /** @pred mpi_send(+ Data,+ Dest,+ Tag)

    Blocking communication predicate. The message in Data, with tag Tag, is sent immediately to the processor with rank Dest. The predicate succeeds after the message being sent.

    */

    /** @pred mpi_isend(+ Data,+ Dest,+ Tag,- Handle)

    Non blocking communication predicate. The message in Data, with tag Tag, is sent whenever possible to the processor with rank Dest. An Handle to the message is returned to be used to check for the status of the message, using the mpi_wait or mpi_test predicates. Until mpi_wait is called, the memory allocated for the buffer containing the message is not released.

    */

    /** @pred mpi_recv(? Source,? Tag,- Data)

    Blocking communication predicate. The predicate blocks until a message is received from processor with rank Source and tag Tag. The message is placed in Data.

    */

    /** @pred mpi_irecv(? Source,? Tag,- Handle)

    Non-blocking communication predicate. The predicate returns an Handle for a message that will be received from processor with rank Source and tag Tag. Note that the predicate succeeds immediately, even if no message has been received. The predicate mpi_wait_recv should be used to obtain the data associated to the handle.

    */

    /** @pred mpi_wait_recv(? Handle,- Status,- Data)

    Completes a non-blocking receive operation. The predicate blocks until a message associated with handle Hanlde is buffered. The predicate succeeds unifying Status with the status of the message and Data with the message itself.

    */

    /** @pred mpi_test_recv(? Handle,- Status,- Data)

    Provides information regarding a handle. If the message associated with handle Hanlde is buffered then the predicate succeeds unifying Status with the status of the message and Data with the message itself. Otherwise, the predicate fails.

    */

    /** @pred mpi_wait(? Handle,- Status)

    Completes a non-blocking operation. If the operation was a mpi_send, the predicate blocks until the message is buffered or sent by the runtime system. At this point the send buffer is released. If the operation was a mpi_recv, it waits until the message is copied to the receive buffer. Status is unified with the status of the message.

    */

    /** @pred mpi_test(? Handle,- Status)

    Provides information regarding the handle Handle, ie., if a communication operation has been completed. If the operation associate with Hanlde has been completed the predicate succeeds with the completion status in Status, otherwise it fails.

    */

    /** @pred mpi_barrier

    Collective communication predicate. Performs a barrier synchronization among all processes. Note that a collective communication means that all processes call the same predicate. To be able to use a regular mpi_recv to receive the messages, one should use mpi_bcast2.

    */

    /** @pred mpi_bcast2(+ Root, ? Data)

    Broadcasts the message Data from the process with rank Root to all other processes.

    */

    /** @pred mpi_bcast3(+ Root, + Data, + Tag)

    Broadcasts the message Data with tag Tag from the process with rank Root to all other processes.

    */

    /** @pred mpi_ibcast(+ Root, + Data, + Tag)

    Non-blocking operation. Broadcasts the message Data with tag Tag from the process with rank Root to all other processes.

    */

    /** @pred mpi_default_buffer_size(- OldBufferSize, ? NewBufferSize)

    The OldBufferSize argument unifies with the current size of the MPI communication buffer size and sets the communication buffer size NewBufferSize. The buffer is used for assynchronous waiting and for broadcast receivers. Notice that buffer is local at each MPI process.

    */

    /** @pred mpi_msg_size( Msg, - MsgSize)

    Unify MsgSize with the number of bytes YAP would need to send the message Msg.

    */

    /** @pred mpi_gc

    Attempts to perform garbage collection with all the open handles associated with send and non-blocking broadcasts. For each handle it tests it and the message has been delivered the handle and the buffer are released.

    @} */

    /** @defgroup BDDs Binary Decision Diagrams and Friends @ingroup YAPPackages @{

    This library provides an interface to the BDD package CUDD. It requires CUDD compiled as a dynamic library. In Linux this is available out of box in Fedora, but can easily be ported to other Linux distributions. CUDD is available in the ports OSX package, and in cygwin. To use it, call :-use_module(library(bdd)).

    The following predicates construct a BDD:

    */

    /** @pred bbd_new(? Exp, - BddHandle)

    create a new BDD from the logical expression Exp. The expression may include:

    + Logical Variables:
    

    a leaf-node can be a logical variable. + Constants 0 and 1 a leaf-node can also be one of these two constants. + or( X, Y), X \/ Y, X + Y disjunction + and( X, Y), X /\ Y, X * Y conjunction + nand( X, Y) negated conjunction@ + nor( X, Y) negated disjunction + xor( X, Y) exclusive or + not( X), - X negation

    */

    /** @pred bdd_from_list(? List, - BddHandle)

    Convert a List of logical expressions of the form above into a BDD accessible through BddHandle.

    */

    /** @pred mtbdd_new(? Exp, - BddHandle)

    create a new algebraic decision diagram (ADD) from the logical expression Exp. The expression may include:

    + Logical Variables:
    

    a leaf-node can be a logical variable, or parameter. + Number a leaf-node can also be any number + X * Y product + X + Y sum + X - Y subtraction + or( X, Y), X \/ Y logical or

    */

    /** @pred bdd_tree(+ BDDHandle, Term)

    Convert the BDD or ADD represented by BDDHandle to a Prolog term of the form bdd( _Dir_, _Nodes_, _Vars_) or mtbdd( _Nodes_, _Vars_), respectively. The arguments are:

    + 
    

    Dir direction of the BDD, usually 1 + Nodes list of nodes in the BDD or ADD.

    In a BDD nodes may be pp (both terminals are positive) or pn (right-hand-side is negative), and have four arguments: a logical variable that will be bound to the value of the node, the logical variable corresponding to the node, a logical variable, a 0 or a 1 with the value of the left-hand side, and a logical variable, a 0 or a 1 with the right-hand side.

    + 
    

    Vars are the free variables in the original BDD, or the parameters of the BDD/ADD.

    As an example, the BDD for the expression X+(Y+X)\*(-Z) becomes:

    bdd(1,[pn(N2,X,1,N1),pp(N1,Y,N0,1),pn(N0,Z,1,1)],vs(X,Y,Z))
    

    */

    /** @pred bdd_eval(+ BDDHandle, Val)

    Unify Val with the value of the logical expression compiled in BDDHandle given an assignment to its variables.

    bdd_new(X+(Y+X)*(-Z), BDD), 
    [X,Y,Z] = [0,0,0], 
    bdd_eval(BDD, V), 
    writeln(V).
    

    would write 0 in the standard output stream.

    The Prolog code equivalent to bdd_eval/2 is:

        Tree = bdd(1, T, _Vs),
        reverse(T, RT),
        foldl(eval_bdd, RT, _, V).
    
    eval_bdd(pp(P,X,L,R), _, P) :-
        P is ( X/\L ) \/ ( (1-X) /\ R ).
    eval_bdd(pn(P,X,L,R), _, P) :-
        P is ( X/\L ) \/ ( (1-X) /\ (1-R) ).
    

    First, the nodes are reversed to implement bottom-up evaluation. Then, we use the foldl list manipulation predicate to walk every node, computing the disjunction of the two cases and binding the output variable. The top node gives the full expression value. Notice that (1- _X_) implements negation.

    */

    /** @pred bdd_size(+ BDDHandle, - Size)

    Unify Size with the number of nodes in BDDHandle.

    */

    /** @pred bdd_print(+ BDDHandle, + File)

    Output bdd BDDHandle as a dot file to File.

    */

    /** @pred bdd_to_probability_sum_product(+ BDDHandle, - Prob)

    Each node in a BDD is given a probability Pi. The total probability of a corresponding sum-product network is Prob.

    */

    /** @pred bdd_to_probability_sum_product(+ BDDHandle, - Probs, - Prob) Each node in a BDD is given a probability Pi. The total probability of a corresponding sum-product network is Prob, and the probabilities of the inner nodes are Probs.

    In Prolog, this predicate would correspond to computing the value of a BDD. The input variables will be bound to probabilities, eg [ _X_, _Y_, _Z_] = [0.3.0.7,0.1], and the previous eval_bdd would operate over real numbers:

        Tree = bdd(1, T, _Vs),
        reverse(T, RT),
        foldl(eval_prob, RT, _, V).
    
    eval_prob(pp(P,X,L,R), _, P) :-
        P is  X * L +  (1-X) * R.
    eval_prob(pn(P,X,L,R), _, P) :-
        P is  X * L + (1-X) * (1-R).
    

    */

    /** @pred bdd_close( BDDHandle)

    close the BDD and release any resources it holds.

    @} */

    /** @defgroup Block_Diagram Block Diagram @ingroup YAPLibrary @{

    This library provides a way of visualizing a prolog program using modules with blocks. To use it use: :-use_module(library(block_diagram)).

    */

    /** @pred make_diagram(+inputfilename, +ouputfilename)

    This will crawl the files following the use_module, ensure_loaded directives withing the inputfilename. The result will be a file in dot format. You can make a pdf at the shell by asking dot -Tpdf filename \> output.pdf.

    */

    /** @pred make_diagram(+inputfilename, +ouputfilename, +predicate, +depth, +extension)

    The same as make_diagram/2 but you can define how many of the imported/exporeted predicates will be shown with predicate, and how deep the crawler is allowed to go with depth. The extension is used if the file use module directives do not include a file extension.

    */

    /** @page SWIhYProlog_Emulation SWI-Prolog Emulation

    This library provides a number of SWI-Prolog builtins that are not by default in YAP. This support is loaded with the expects_dialect(swi) command.

    */

    /** @pred append(? List1,? List2,? List3)

    Succeeds when List3 unifies with the concatenation of List1 and List2. The predicate can be used with any instantiation pattern (even three variables).

    */

    /** @pred between(+ Low,+ High,? Value)

    Low and High are integers, High less or equal than Low. If Value is an integer, Low less or equal than Value less or equal than High. When Value is a variable it is successively bound to all integers between Low and High. If High is inf, between/3 is true iff Value less or equal than Low, a feature that is particularly interesting for generating integers from a certain value.

    */

    /** @pred chdir(+ Dir)

    Compatibility predicate. New code should use working_directory/2.

    */

    /** @pred concat_atom(+ List,- Atom)

    List is a list of atoms, integers or floating point numbers. Succeeds if Atom can be unified with the concatenated elements of List. If List has exactly 2 elements it is equivalent to atom_concat/3, allowing for variables in the list.

    */

    /** @pred concat_atom(? List,+ Separator,? Atom)

    Creates an atom just like concat_atom/2, but inserts Separator between each pair of atoms. For example:

    ?- concat_atom([gnu, gnat], ', ', A).
    
    A = 'gnu, gnat'
    

    (Unimplemented) This predicate can also be used to split atoms by instantiating Separator and Atom:

    ?- concat_atom(L, -, 'gnu-gnat').
    
    L = [gnu, gnat]
    

    */

    /** @pred nth1(+ Index,? List,? Elem)

    Succeeds when the Index-th element of List unifies with Elem. Counting starts at 1.

    Set environment variable. Name and Value should be instantiated to atoms or integers. The environment variable will be passed to shell/[0-2] and can be requested using getenv/2. They also influence expand_file_name/2.

    */

    /** @pred setenv(+ Name,+ Value)

    Set environment variable. Name and Value should be instantiated to atoms or integers. The environment variable will be passed to shell/[0-2] and can be requested using getenv/2. They also influence expand_file_name/2.

    */

    /** @pred term_to_atom(? Term,? Atom)

    Succeeds if Atom describes a term that unifies with Term. When Atom is instantiated Atom is converted and then unified with Term. If Atom has no valid syntax, a syntax_error exception is raised. Otherwise Term is ``written'' on Atom using write/1.

    */

    /** @pred working_directory(- Old,+ New)

    Unify Old with an absolute path to the current working directory and change working directory to New. Use the pattern working_directory(CWD, CWD) to get the current directory. See also absolute_file_name/2 and chdir/1.

    */

    /** @pred @ Term1 =@= @ Term2

    True iff Term1 and Term2 are structurally equivalent. I.e. if Term1 and Term2 are variants of each other.

    @} */

    /** @defgroup Invoking_Predicates_on_all_Members_of_a_List Invoking Predicates on all Members of a List @ingroup YAPLibrary @{

    All the predicates in this section call a predicate on all members of a list or until the predicate called fails. The predicate is called via call/[2..], which implies common arguments can be put in front of the arguments obtained from the list(s). For example:

    ?- maplist(plus(1), [0, 1, 2], X).
    
    X = [1, 2, 3]
    

    we will phrase this as `` Predicate is applied on ...''

    @pred maplist(+ Pred,+ List)

    Pred is applied successively on each element of List until the end of the list or Pred fails. In the latter case maplist/2 fails.

    */

    /** @pred maplist(+ Pred,+ List1,+ List2)

    Apply Pred on all successive pairs of elements from List1 and List2. Fails if Pred can not be applied to a pair. See the example above.

    */

    /** @pred maplist(+ Pred,+ List1,+ List2,+ List4)

    Apply Pred on all successive triples of elements from List1, List2 and List3. Fails if Pred can not be applied to a triple. See the example above.

    @} */

    /** @defgroup Forall Forall @ingroup YAPPackages @{

    */

    /** @pred forall(+ Cond,+ Action)

    For all alternative bindings of Cond Action can be proven. The next example verifies that all arithmetic statements in the list L are correct. It does not say which is wrong if one proves wrong.

    ?- forall(member(Result = Formula, [2 = 1 + 1, 4 = 2 * 2]),
                     Result =:= Formula).
    

    */

    /** @page SWIhYProlog_Global_Variables SWI Global variables

    SWI-Prolog global variables are associations between names (atoms) and terms. They differ in various ways from storing information using assert/1 or recorda/3.

    + The value lives on the Prolog (global) stack.  This implies 
    

    that lookup time is independent from the size of the term. This is particulary interesting for large data structures such as parsed XML documents or the CHR global constraint store.

    */

    /** @pred They support both global assignment using nb_setval/2 and backtrackable assignment using b_setval/2.

    + Only one value (which can be an arbitrary complex Prolog
    

    term) can be associated to a variable at a time.

    + Their value cannot be shared among threads.  Each thread
    

    has its own namespace and values for global variables.

    + Currently global variables are scoped globally.  We may
    

    consider module scoping in future versions.

    Both b_setval/2 and nb_setval/2 implicitly create a variable if the referenced name does not already refer to a variable.

    Global variables may be initialised from directives to make them available during the program lifetime, but some considerations are necessary for saved-states and threads. Saved-states to not store global variables, which implies they have to be declared with initialization/1 to recreate them after loading the saved state. Each thread has its own set of global variables, starting with an empty set. Using thread_inititialization/1 to define a global variable it will be defined, restored after reloading a saved state and created in all threads that are created after the registration.

    */

    /** @pred b_setval(+ Name,+ Value)

    Associate the term Value with the atom Name or replaces the currently associated value with Value. If Name does not refer to an existing global variable a variable with initial value [] is created (the empty list). On backtracking the assignment is reversed.

    */

    /** @pred b_getval(+ Name,- Value)

    Get the value associated with the global variable Name and unify it with Value. Note that this unification may further instantiate the value of the global variable. If this is undesirable the normal precautions (double negation or copy_term/2) must be taken. The b_getval/2 predicate generates errors if Name is not an atom or the requested variable does not exist.

    */

    /** @pred nb_setval(+ Name,+ Value)

    Associates a copy of Value created with duplicate_term/2 with the atom Name. Note that this can be used to set an initial value other than [] prior to backtrackable assignment.

    */

    /** @pred nb_getval(+ Name,- Value)

    The nb_getval/2 predicate is a synonym for b_getval/2, introduced for compatibility and symmetry. As most scenarios will use a particular global variable either using non-backtrackable or backtrackable assignment, using nb_getval/2 can be used to document that the variable is used non-backtrackable.

    */

    /** @pred nb_current(? Name,? Value)

    Enumerate all defined variables with their value. The order of enumeration is undefined.

    */

    /** @pred nb_delete(? Name)

    Delete the named global variable.

    @} */

    /** @defgroup Compatibility_of_Global_Variables Compatibility of Global Variables @ingroup YAPPackages @{

    Global variables have been introduced by various Prolog implementations recently. YAP follows their implementation in SWI-Prolog, itself based on hProlog by Bart Demoen. Jan and Bart decided that the semantics if hProlog nb_setval/2, which is equivalent to nb_linkval/2 is not acceptable for normal Prolog users as the behaviour is influenced by how builtin predicates constructing terms (read/1, =../2, etc.) are implemented.

    GNU-Prolog provides a rich set of global variables, including arrays. Arrays can be implemented easily in SWI-Prolog using functor/3 and setarg/3 due to the unrestricted arity of compound terms.

    */

    /** @page Extensions Extensions to Prolog

    YAP includes a number of extensions over the original Prolog language. Next, we discuss support to the most important ones.

    @} */

    /** @defgroup Rational_Trees Rational Trees @ingroup YAPPackages @{

    Prolog unification is not a complete implementation. For efficiency considerations, Prolog systems do not perform occur checks while unifying terms. As an example, X = a(X) will not fail but instead will create an infinite term of the form a(a(a(a(a(...))))), or rational tree.

    Rational trees are now supported by default in YAP. In previous versions, this was not the default and these terms could easily lead to infinite computation. For example, X = a(X), X = X would enter an infinite loop.

    The RATIONAL_TREES flag improves support for these terms. Internal primitives are now aware that these terms can exist, and will not enter infinite loops. Hence, the previous unification will succeed. Another example, X = a(X), ground(X) will succeed instead of looping. Other affected built-ins include the term comparison primitives, numbervars/3, copy_term/2, and the internal data base routines. The support does not extend to Input/Output routines or to assert/1 YAP does not allow directly reading rational trees, and you need to use write_depth/2 to avoid entering an infinite cycle when trying to write an infinite term.

    @} */

    /** @defgroup CohYroutining Co-routining @ingroup YAPPackages @{

    Prolog uses a simple left-to-right flow of control. It is sometimes convenient to change this control so that goals will only be executed when conditions are fulfilled. This may result in a more "data-driven" execution, or may be necessary to correctly implement extensions such as negation by default.

    The COROUTINING flag enables this option. Note that the support for coroutining will in general slow down execution.

    The following declaration is supported:

    + block/1
    

    The argument to block/1 is a condition on a goal or a conjunction of conditions, with each element separated by commas. Each condition is of the form predname( _C1_,..., _CN_), where N is the arity of the goal, and each CI is of the form -, if the argument must suspend until the first such variable is bound, or ?, otherwise.

    + wait/1
    

    The argument to wait/1 is a predicate descriptor or a conjunction of these predicates. These predicates will suspend until their first argument is bound.

    The following primitives are supported:

    */

    /** @pred dif( X, Y)

    Succeed if the two arguments do not unify. A call to dif/2 will suspend if unification may still succeed or fail, and will fail if they always unify.

    */

    /** @pred freeze(? X,: G)

    Delay execution of goal G until the variable X is bound.

    */

    /** @pred frozen( X, G)

    Unify G with a conjunction of goals suspended on variable X, or true if no goal has suspended.

    */

    /** @pred when(+ C,: G)

    Delay execution of goal G until the conditions C are satisfied. The conditions are of the following form:

    + _C1_, _C2_
    

    Delay until both conditions C1 and C2 are satisfied. + C1; C2 Delay until either condition C1 or condition C2 is satisfied. + ?=( V1, C2) Delay until terms V1 and V1 have been unified. + nonvar( V) Delay until variable V is bound. + ground( V) Delay until variable V is ground.

    Note that when/2 will fail if the conditions fail.

    */

    /** @pred call_residue(: G, L)

    Call goal G. If subgoals of G are still blocked, return a list containing these goals and the variables they are blocked in. The goals are then considered as unblocked. The next example shows a case where dif/2 suspends twice, once outside call_residue/2, and the other inside:

    ?- dif(X,Y),
           call_residue((dif(X,Y),(X = f(Z) ; Y = f(Z))), L).
    
    X = f(Z),
    L = [[Y]-dif(f(Z),Y)],
    dif(f(Z),Y) ? ;
    
    Y = f(Z),
    L = [[X]-dif(X,f(Z))],
    dif(X,f(Z)) ? ;
    
    no
    

    The system only reports one invocation of dif/2 as having suspended.

    */

    /** @pred call_residue_vars(: G, L)

    Call goal G and unify L with a list of all constrained variables created during execution of G:

      ?- dif(X,Z), call_residue_vars(dif(X,Y),L).
    dif(X,Z), call_residue_vars(dif(X,Y),L).
    L = [Y],
    dif(X,Z),
    dif(X,Y) ? ;
    
    no
    

    @} */

    /** @defgroup Attributed_Variables Attributed Variables @ingroup YAPPackages @{

    YAP supports attributed variables, originally developed at OFAI by Christian Holzbaur. Attributes are a means of declaring that an arbitrary term is a property for a variable. These properties can be updated during forward execution. Moreover, the unification algorithm is aware of attributed variables and will call user defined handlers when trying to unify these variables.

    Attributed variables provide an elegant abstraction over which one can extend Prolog systems. Their main application so far has been in implementing constraint handlers, such as Holzbaur's CLPQR, Fruewirth and Holzbaur's CHR, and CLP(BN).

    Different Prolog systems implement attributed variables in different ways. Traditionally, YAP has used the interface designed by SICStus Prolog. This interface is still available in the atts library, but from YAP-6.0.3 we recommend using the hProlog, SWI style interface. The main reason to do so is that most packages included in YAP that use attributed variables, such as CHR, CLP(FD), and CLP(QR), rely on the SWI-Prolog interface.

    @} */

    /** @defgroup New_Style_Attribute_Declarations hProlog and SWI-Prolog style Attribute Declarations @ingroup YAPPackages @{

    The following documentation is taken from the SWI-Prolog manual.

    Binding an attributed variable schedules a goal to be executed at the first possible opportunity. In the current implementation the hooks are executed immediately after a successful unification of the clause-head or successful completion of a foreign language (built-in) predicate. Each attribute is associated to a module and the hook attr_unify_hook/2 is executed in this module. The example below realises a very simple and incomplete finite domain reasoner.

    :- module(domain,
          [ domain/2            % Var, ?Domain
          ]).
    :- use_module(library(ordsets)).
    
    domain(X, Dom) :-
        var(Dom), !,
        get_attr(X, domain, Dom).
    domain(X, List) :-
        list_to_ord_set(List, Domain),
        put_attr(Y, domain, Domain),
        X = Y.
    
    %    An attributed variable with attribute value Domain has been
    %    assigned the value Y
    
    attr_unify_hook(Domain, Y) :-
        (   get_attr(Y, domain, Dom2)
        ->  ord_intersection(Domain, Dom2, NewDomain),
            (   NewDomain == []
            ->    fail
            ;    NewDomain = [Value]
            ->    Y = Value
            ;    put_attr(Y, domain, NewDomain)
            )
        ;   var(Y)
        ->  put_attr( Y, domain, Domain )
        ;   ord_memberchk(Y, Domain)
        ).
    
    %    Translate attributes from this module to residual goals
    
    attribute_goals(X) -->
        { get_attr(X, domain, List) },
        [domain(X, List)].
    

    Before explaining the code we give some example queries:

    The predicate domain/2 fetches (first clause) or assigns (second clause) the variable a domain, a set of values it can be unified with. In the second clause first associates the domain with a fresh variable and then unifies X to this variable to deal with the possibility that X already has a domain. The predicate attr_unify_hook/2 is a hook called after a variable with a domain is assigned a value. In the simple case where the variable is bound to a concrete value we simply check whether this value is in the domain. Otherwise we take the intersection of the domains and either fail if the intersection is empty (first example), simply assign the value if there is only one value in the intersection (second example) or assign the intersection as the new domain of the variable (third example). The nonterminal attribute_goals/3 is used to translate remaining attributes to user-readable goals that, when executed, reinstate these attributes.

    @pred put_attr(+ Var,+ Module,+ Value)

    If Var is a variable or attributed variable, set the value for the attribute named Module to Value. If an attribute with this name is already associated with Var, the old value is replaced. Backtracking will restore the old value (i.e., an attribute is a mutable term. See also setarg/3). This predicate raises a representation error if Var is not a variable and a type error if Module is not an atom.

    */

    /** @pred get_attr(+ Var,+ Module,- Value)

    Request the current value for the attribute named Module. If Var is not an attributed variable or the named attribute is not associated to Var this predicate fails silently. If Module is not an atom, a type error is raised.

    */

    /** @pred del_attr(+ Var,+ Module)

    Delete the named attribute. If Var loses its last attribute it is transformed back into a traditional Prolog variable. If Module is not an atom, a type error is raised. In all other cases this predicate succeeds regardless whether or not the named attribute is present.

    */

    /** @pred attr_unify_hook(+ AttValue,+ VarValue)

    Hook that must be defined in the module an attributed variable refers to. Is is called after the attributed variable has been unified with a non-var term, possibly another attributed variable. AttValue is the attribute that was associated to the variable in this module and VarValue is the new value of the variable. Normally this predicate fails to veto binding the variable to VarValue, forcing backtracking to undo the binding. If VarValue is another attributed variable the hook often combines the two attribute and associates the combined attribute with VarValue using put_attr/3.

    */

    /** @pred attr_portray_hook(+ AttValue,+ Var)

    Called by write_term/2 and friends for each attribute if the option attributes(portray) is in effect. If the hook succeeds the attribute is considered printed. Otherwise Module = ... is printed to indicate the existence of a variable.

    */

    /** @pred attribute_goals(+ Var,- Gs,+ GsRest)

    This nonterminal, if it is defined in a module, is used by copy_term/3 to project attributes of that module to residual goals. It is also used by the toplevel to obtain residual goals after executing a query.

    Normal user code should deal with put_attr/3, get_attr/3 and del_attr/2. The routines in this section fetch or set the entire attribute list of a variables. Use of these predicates is anticipated to be restricted to printing and other special purpose operations.

    @pred get_attrs(+ Var,- Attributes)

    Get all attributes of Var. Attributes is a term of the form att( _Module_, _Value_, _MoreAttributes_), where MoreAttributes is [] for the last attribute.

    */

    /** @pred put_attrs(+ Var,+ Attributes)

    Set all attributes of Var. See get_attrs/2 for a description of Attributes.

    */

    /** @pred del_attrs(+ Var)

    If Var is an attributed variable, delete all its attributes. In all other cases, this predicate succeeds without side-effects.

    */

    /** @pred term_attvars(+ Term,- AttVars)

    AttVars is a list of all attributed variables in Term and its attributes. I.e., term_attvars/2 works recursively through attributes. This predicate is Cycle-safe.

    */

    /** @pred copy_term(? TI,- TF,- Goals)

    Term TF is a variant of the original term TI, such that for each variable V in the term TI there is a new variable V' in term TF without any attributes attached. Attributed variables are thus converted to standard variables. Goals is unified with a list that represents the attributes. The goal maplist(call, _Goals_) can be called to recreate the attributes.

    Before the actual copying, copy_term/3 calls attribute_goals/1 in the module where the attribute is defined.

    */

    /** @pred copy_term_nat(? TI,- TF)

    As copy_term/2. Attributes however, are not copied but replaced by fresh variables.

    @} */

    /** @defgroup Old_Style_Attribute_Declarations SICStus Prolog style Attribute Declarations @ingroup YAPLibrary @{

    Old style attribute declarations are activated through loading the library atts . The command

    | ?- use_module(library(atts)).
    

    enables this form of use of attributed variables. The package provides the following functionality:

    + Each attribute must be declared first. Attributes are described by a functor
    

    and are declared per module. Each Prolog module declares its own sets of attributes. Different modules may have different functors with the same module. + The built-in put_atts/2 adds or deletes attributes to a variable. The variable may be unbound or may be an attributed variable. In the latter case, YAP discards previous values for the attributes. + The built-in get_atts/2 can be used to check the values of an attribute associated with a variable. + The unification algorithm calls the user-defined predicate verify_attributes/3 before trying to bind an attributed variable. Unification will resume after this call. + The user-defined predicate attribute_goal/2 converts from an attribute to a goal. + The user-defined predicate project_attributes/2 is used from a set of variables into a set of constraints or goals. One application of project_attributes/2 is in the top-level, where it is used to output the set of floundered constraints at the end of a query.

    @} */

    /** @defgroup Attribute_Declarations Attribute Declarations @ingroup Old_Style_Attribute_Declarations @{

    Attributes are compound terms associated with a variable. Each attribute has a name which is private to the module in which the attribute was defined. Variables may have at most one attribute with a name. Attribute names are defined with the following declaration:

    :- attribute AttributeSpec, ..., AttributeSpec.
    

    where each AttributeSpec has the form ( Name/ Arity). One single such declaration is allowed per module Module.

    Although the YAP module system is predicate based, attributes are local to modules. This is implemented by rewriting all calls to the built-ins that manipulate attributes so that attribute names are preprocessed depending on the module. The user:goal_expansion/3 mechanism is used for this purpose.

    @} */

    /** @defgroup Attribute_Manipulation Attribute Manipulation @ingroup Old_Style_Attribute_Declarations @{

    The attribute manipulation predicates always work as follows:

      + The first argument is the unbound variable associated with attributes, + The second argument is a list of attributes. Each attribute will be a Prolog term or a constant, prefixed with the + and - unary operators. The prefix + may be dropped for convenience.

    The following three procedures are available to the user. Notice that these built-ins are rewritten by the system into internal built-ins, and that the rewriting process depends on the module on which the built-ins have been invoked.

    */

    /** @pred Module:get_atts( -Var, ?ListOfAttributes)

    Unify the list ?ListOfAttributes with the attributes for the unbound variable Var. Each member of the list must be a bound term of the form +( _Attribute_), -( _Attribute_) (the kbd prefix may be dropped). The meaning of + and - is: + +( Attribute) Unifies Attribute with a corresponding attribute associated with Var, fails otherwise.

    + -( _Attribute_)
    

    Succeeds if a corresponding attribute is not associated with Var. The arguments of Attribute are ignored.

    */

    /** @pred Module:put_atts( -Var, ?ListOfAttributes)

    Associate with or remove attributes from a variable Var. The attributes are given in ?ListOfAttributes, and the action depends on how they are prefixed: + +( Attribute) Associate Var with Attribute. A previous value for the attribute is simply replace (like with set_mutable/2).

    + -( _Attribute_)
    

    Remove the attribute with the same name. If no such attribute existed, simply succeed.

    @} */

    /** @defgroup Attributed_Unification Attributed Unification @ingroup Old_Style_Attribute_Declarations @{

    The user-predicate predicate verify_attributes/3 is called when attempting to unify an attributed variable which might have attributes in some Module.

    */

    /** @pred Module:verify_attributes( -Var, +Value, -Goals)

    The predicate is called when trying to unify the attributed variable Var with the Prolog term Value. Note that Value may be itself an attributed variable, or may contain attributed variables. The goal verify_attributes/3 is actually called before Var is unified with Value.

    It is up to the user to define which actions may be performed by verify_attributes/3 but the procedure is expected to return in Goals a list of goals to be called after Var is unified with Value. If verify_attributes/3 fails, the unification will fail.

    Notice that the verify_attributes/3 may be called even if Var< has no attributes in module Module. In this case the routine should simply succeed with Goals unified with the empty list.

    */

    /** @pred attvar( -Var)

    Succeed if Var is an attributed variable.

    @} */

    /** @defgroup Displaying_Attributes Displaying Attributes @ingroup Old_Style_Attribute_Declarations @{

    Attributes are usually presented as goals. The following routines are used by built-in predicates such as call_residue/2 and by the Prolog top-level to display attributes:

    */

    /** @pred Module:attribute_goal( -Var, -Goal) User-defined procedure, called to convert the attributes in Var to a Goal. Should fail when no interpretation is available.

    @} */

    /** @defgroup Projecting_Attributes Projecting Attributes @ingroup Old_Style_Attribute_Declarations @{

    Constraint solvers must be able to project a set of constraints to a set of variables. This is useful when displaying the solution to a goal, but may also be used to manipulate computations. The user-defined project_attributes/2 is responsible for implementing this projection.

    */

    /** @pred Module:project_attributes( +QueryVars, +AttrVars)

    Given a list of variables QueryVars and list of attributed variables AttrVars, project all attributes in AttrVars to QueryVars. Although projection is constraint system dependent, typically this will involve expressing all constraints in terms of QueryVars and considering all remaining variables as existentially quantified.

    Projection interacts with attribute_goal/2 at the Prolog top level. When the query succeeds, the system first calls project_attributes/2. The system then calls attribute_goal/2 to get a user-level representation of the constraints. Typically, attribute_goal/2 will convert from the original constraints into a set of new constraints on the projection, and these constraints are the ones that will have an attribute_goal/2 handler.

    @} */

    /** @defgroup Attribute_Examples Attribute Examples @ingroup Old_Style_Attribute_Declarations @{

    The following two examples example is taken from the SICStus Prolog manual. It sketches the implementation of a simple finite domain ``solver''. Note that an industrial strength solver would have to provide a wider range of functionality and that it quite likely would utilize a more efficient representation for the domains proper. The module exports a single predicate domain( _-Var_, _?Domain_) which associates Domain (a list of terms) with Var. A variable can be queried for its domain by leaving Domain unbound.

    We do not present here a definition for project_attributes/2. Projecting finite domain constraints happens to be difficult.

    :- module(domain, [domain/2]).
    
    :- use_module(library(atts)).
    :- use_module(library(ordsets), [
            ord_intersection/3,
            ord_intersect/2,
            list_to_ord_set/2
       ]).
    
    :- attribute dom/1.
    
    verify_attributes(Var, Other, Goals) :-
            get_atts(Var, dom(Da)), !,          % are we involved?
            (   var(Other) ->                   % must be attributed then
                (   get_atts(Other, dom(Db)) -> %   has a domain?
                    ord_intersection(Da, Db, Dc),
                    Dc = [El|Els],              % at least one element
                    (   Els = [] ->             % exactly one element
                        Goals = [Other=El]      % implied binding
                    ;   Goals = [],
                        put_atts(Other, dom(Dc))% rescue intersection
                    )
                ;   Goals = [],
                    put_atts(Other, dom(Da))    % rescue the domain
                )
            ;   Goals = [],
                ord_intersect([Other], Da)      % value in domain?
            ).
    verify_attributes(_, _, []).                % unification triggered
                                                % because of attributes
                                                % in other modules
    
    attribute_goal(Var, domain(Var,Dom)) :-     % interpretation as goal
            get_atts(Var, dom(Dom)).
    
    domain(X, Dom) :-
            var(Dom), !,
            get_atts(X, dom(Dom)).
    domain(X, List) :-
            list_to_ord_set(List, Set),
            Set = [El|Els],                     % at least one element
            (   Els = [] ->                     % exactly one element
                X = El                          % implied binding
            ;   put_atts(Fresh, dom(Set)),
                X = Fresh                       % may call
                                                % verify_attributes/3
            ).
    

    Note that the ``implied binding'' Other=El was deferred until after the completion of verify_attribute/3. Otherwise, there might be a danger of recursively invoking verify_attribute/3, which might bind Var, which is not allowed inside the scope of verify_attribute/3. Deferring unifications into the third argument of verify_attribute/3 effectively serializes the calls to verify_attribute/3.

    Assuming that the code resides in the file domain.yap, we can use it via:

    | ?- use_module(domain).
    

    Let's test it:

    | ?- domain(X,[5,6,7,1]), domain(Y,[3,4,5,6]), domain(Z,[1,6,7,8]).
    
    domain(X,[1,5,6,7]),
    domain(Y,[3,4,5,6]),
    domain(Z,[1,6,7,8]) ? 
    
    yes
    | ?- domain(X,[5,6,7,1]), domain(Y,[3,4,5,6]), domain(Z,[1,6,7,8]), 
         X=Y.
    
    Y = X,
    domain(X,[5,6]),
    domain(Z,[1,6,7,8]) ? 
    
    yes
    | ?- domain(X,[5,6,7,1]), domain(Y,[3,4,5,6]), domain(Z,[1,6,7,8]),
         X=Y, Y=Z.
    
    X = 6,
    Y = 6,
    Z = 6
    

    To demonstrate the use of the Goals argument of verify_attributes/3, we give an implementation of freeze/2. We have to name it myfreeze/2 in order to avoid a name clash with the built-in predicate of the same name.

    :- module(myfreeze, [myfreeze/2]).
    
    :- use_module(library(atts)).
    
    :- attribute frozen/1.
    
    verify_attributes(Var, Other, Goals) :-
            get_atts(Var, frozen(Fa)), !,       % are we involved?
            (   var(Other) ->                   % must be attributed then
                (   get_atts(Other, frozen(Fb)) % has a pending goal?
                ->  put_atts(Other, frozen((Fa,Fb))) % rescue conjunction
                ;   put_atts(Other, frozen(Fa)) % rescue the pending goal
                ),
                Goals = []
            ;   Goals = [Fa]
            ).
    verify_attributes(_, _, []).
    
    attribute_goal(Var, Goal) :-                % interpretation as goal
            get_atts(Var, frozen(Goal)).
    
    myfreeze(X, Goal) :-
            put_atts(Fresh, frozen(Goal)),
            Fresh = X.
    

    Assuming that this code lives in file myfreeze.yap, we would use it via:

    | ?- use_module(myfreeze).
    | ?- myfreeze(X,print(bound(x,X))), X=2.
    
    bound(x,2)                      % side effect
    X = 2                           % bindings
    

    The two solvers even work together:

    | ?- myfreeze(X,print(bound(x,X))), domain(X,[1,2,3]),
         domain(Y,[2,10]), X=Y.
    
    bound(x,2)                      % side effect
    X = 2,                          % bindings
    Y = 2
    

    The two example solvers interact via bindings to shared attributed variables only. More complicated interactions are likely to be found in more sophisticated solvers. The corresponding verify_attributes/3 predicates would typically refer to the attributes from other known solvers/modules via the module prefix in _Module_:get_atts/2.

    @} */

    /** @defgroup CLPR Constraint Logic Programming over Reals @ingroup YAPPackages @{

    YAP now uses the CLP(R) package developed by Leslie De Koninck, K.U. Leuven as part of a thesis with supervisor Bart Demoen and daily advisor Tom Schrijvers, and distributed with SWI-Prolog.

    This CLP(R) system is a port of the CLP(Q,R) system of Sicstus Prolog and YAP by Christian Holzbaur: Holzbaur C.: OFAI clp(q,r) Manual, Edition 1.3.3, Austrian Research Institute for Artificial Intelligence, Vienna, TR-95-09, 1995, http://www.ai.univie.ac.at/cgi-bin/tr-online?number+95-09 This port only contains the part concerning real arithmetics. This manual is roughly based on the manual of the above mentioned CLP(QR) implementation.

    Please note that the clpr library is not an autoload library and therefore this library must be loaded explicitely before using it:

    :- use_module(library(clpr)).
    

    @} */

    /** @defgroup CLPR_Solver_Predicates Solver Predicates @ingroup CLPR @{

    The following predicates are provided to work with constraints:

    */

    /** @pred {+ Constraints} Adds the constraints given by Constraints to the constraint store.

    */

    /** @pred entailed(+ Constraint) Succeeds if Constraint is necessarily true within the current constraint store. This means that adding the negation of the constraint to the store results in failure.

    */

    /** @pred inf(+ Expression,- Inf) Computes the infimum of Expression within the current state of the constraint store and returns that infimum in Inf. This predicate does not change the constraint store.

    */

    /** @pred inf(+ Expression,- Sup) Computes the supremum of Expression within the current state of the constraint store and returns that supremum in Sup. This predicate does not change the constraint store.

    */

    /** @pred min(+ Expression) Minimizes Expression within the current constraint store. This is the same as computing the infimum and equation the expression to that infimum.

    */

    /** @pred max(+ Expression) Maximizes Expression within the current constraint store. This is the same as computing the supremum and equating the expression to that supremum.

    */

    /** @pred bb_inf(+ Ints,+ Expression,- Inf,- Vertext,+ Eps) Computes the infimum of Expression within the current constraint store, with the additional constraint that in that infimum, all variables in Ints have integral values. Vertex will contain the values of Ints in the infimum. Eps denotes how much a value may differ from an integer to be considered an integer. E.g. when Eps = 0.001, then X = 4.999 will be considered as an integer (5 in this case). Eps should be between 0 and 0.5.

    */

    /** @pred bb_inf(+ Ints,+ Expression,- Inf) The same as bb_inf/5 but without returning the values of the integers and with an eps of 0.001.

    */

    /** @pred dump(+ Target,+ Newvars,- CodedAnswer) Returns the constraints on Target in the list CodedAnswer where all variables of Target have veen replaced by NewVars. This operation does not change the constraint store. E.g. in

    dump([X,Y,Z],[x,y,z],Cons)
    

    Cons will contain the constraints on X, Y and Z where these variables have been replaced by atoms x, y and z.

    @} */

    /** @defgroup CLPR_Syntax Syntax of the predicate arguments @ingroup YAPPackages @{

    The arguments of the predicates defined in the subsection above are defined in the following table. Failing to meet the syntax rules will result in an exception.

    <Constraints> ---> <Constraint>				\\ single constraint \\
    	      | <Constraint> , <Constraints>		\\ conjunction \\
    	      | <Constraint> ; <Constraints>		\\ disjunction \\
    
    <Constraint> ---> <Expression> {<} <Expression>		\\ less than \\
    	     | <Expression> {>} <Expression>		\\ greater than \\
    	     | <Expression> {=<} <Expression>	\\ less or equal \\
    	     | {<=}(<Expression>, <Expression>)	\\ less or equal \\
    	     | <Expression> {>=} <Expression>	\\ greater or equal \\
    	     | <Expression> {=\=} <Expression>	\\ not equal \\
    	     | <Expression> =:= <Expression>		\\ equal \\
    	     | <Expression> = <Expression>		\\ equal \\
    
    <Expression> --->  <Variable>				\\ Prolog variable \\
    	     | <Number>				\\ Prolog number (float, integer) \\
    	     | +<Expression>				\\ unary plus \\
    	     | -<Expression>				\\ unary minus \\
    	     | <Expression> + <Expression>		\\ addition \\
    	     | <Expression> - <Expression>		\\ substraction \\
    	     | <Expression> * <Expression>		\\ multiplication \\
    	     | <Expression> / <Expression>		\\ division \\
    	     | abs(<Expression>)			\\ absolute value \\
    	     | sin(<Expression>)			\\ sine \\
    	     | cos(<Expression>)			\\ cosine \\
    	     | tan(<Expression>)			\\ tangent \\
    	     | exp(<Expression>)			\\ exponent \\
    	     | pow(<Expression>)			\\ exponent \\
    	     | <Expression> {^} <Expression>		\\ exponent \\
    	     | min(<Expression>, <Expression>)	\\ minimum \\
    	     | max(<Expression>, <Expression>)	\\ maximum \\
    

    @} */

    /** @defgroup CLPR_Unification Use of unification @ingroup CLPR @{

    Instead of using the {}/1 predicate, you can also use the standard unification mechanism to store constraints. The following code samples are equivalent:

    + Unification with a variable
    
    {X =:= Y}
    {X = Y}
    X = Y
    
    + Unification with a number
    
    {X =:= 5.0}
    {X = 5.0}
    X = 5.0
    

    @} */

    /** @defgroup CLPR_NonhYlinear_Constraints Non-Linear Constraints @ingroup CLPR @{

    In this version, non-linear constraints do not get solved until certain conditions are satisfied. We call these conditions the isolation axioms. They are given in the following table.

    A = B * C         when B or C is ground	or		 // A = 5 * C or A = B * 4 \\
    	                      A and (B or C) are ground	 // 20 = 5 * C or 20 = B * 4 \\
    
    A = B / C      when C is ground or			// A = B / 3 
    	                      A and B are ground		// 4 = 12 / C 
    
    X = min(Y,Z)     when Y and Z are ground or	// X = min(4,3) 
    X = max(Y,Z)         Y and Z are ground		// X = max(4,3) 
    X = abs(Y)                Y is ground			// X = abs(-7) 
    
    X = pow(Y,Z)   when X and Y are ground or		// 8 = 2 ^ Z 
    X = exp(Y,Z)           X and Z are ground		// 8 = Y ^ 3 
    X = Y ^ Z            Y and Z are ground		// X = 2 ^ 3 
    
    X = sin(Y)	    when X is ground or			// 1 = sin(Y) 
    X = cos(Y)	               Y is ground			// X = sin(1.5707) 
    X = tan(Y)
    

    @section CHR CHR: Constraint Handling Rules @ingroup YAPPackages

    This chapter is written by Tom Schrijvers, K.U. Leuven for the hProlog system. Adjusted by Jan Wielemaker to fit the SWI-Prolog documentation infrastructure and remove hProlog specific references.

    The CHR system of SWI-Prolog is the K.U.Leuven CHR system. The runtime environment is written by Christian Holzbaur and Tom Schrijvers while the compiler is written by Tom Schrijvers. Both are integrated with SWI-Prolog and licenced under compatible conditions with permission from the authors.

    The main reference for SWI-Prolog's CHR system is:

    + T. Schrijvers, and B. Demoen, <em>The K.U.Leuven CHR System: Implementation and Application</em>, First Workshop on Constraint Handling Rules: Selected
    

    Contributions (Fruwirth, T. and Meister, M., eds.), pp. 1--5, 2004.

    @} */

    /** @defgroup CHR_Introduction Introduction @ingroup CHR @{

    Constraint Handling Rules (CHR) is a committed-choice bottom-up language embedded in Prolog. It is designed for writing constraint solvers and is particularily useful for providing application-specific constraints. It has been used in many kinds of applications, like scheduling, model checking, abduction, type checking among many others.

    CHR has previously been implemented in other Prolog systems (SICStus, Eclipse, Yap), Haskell and Java. This CHR system is based on the compilation scheme and runtime environment of CHR in SICStus.

    In this documentation we restrict ourselves to giving a short overview of CHR in general and mainly focus on elements specific to this implementation. For a more thorough review of CHR we refer the reader to [Freuhwirth:98]. More background on CHR can be found at the CHR web site.

    @} */

    /** @defgroup CHR_Syntax_and_Semantics Syntax and Semantics @ingroup YAPPackages @{

    @} */

    /** @defgroup CHR_Syntax CHR Syntax Wingroup CHR @{

    The syntax of CHR rules in hProlog is the following:

    rules --> rule, rules.
    rules --> [].
    
    rule --> name, actual_rule, pragma, [atom('.')].
    
    name --> atom, [atom('@')].
    name --> [].
    
    actual_rule --> simplification_rule.
    actual_rule --> propagation_rule.
    actual_rule --> simpagation_rule.
    
    simplification_rule --> constraints, [atom('<=>')], guard, body.
    propagation_rule --> constraints, [atom('==>')], guard, body.
    simpagation_rule --> constraints, [atom('\')], constraints, [atom('<=>')], 
                         guard, body.
    
    constraints --> constraint, constraint_id.
    constraints --> constraint, [atom(',')], constraints.
    
    constraint --> compound_term.
    
    constraint_id --> [].
    constraint_id --> [atom('#')], variable.
    
    guard --> [].
    guard --> goal, [atom('|')].
    
    body --> goal.
    
    pragma --> [].
    pragma --> [atom('pragma')], actual_pragmas.
    
    actual_pragmas --> actual_pragma.
    actual_pragmas --> actual_pragma, [atom(',')], actual_pragmas.
    
    actual_pragma --> [atom('passive(')], variable, [atom(')')].
    
    

    Additional syntax-related terminology:

    + *head:* the constraints in an `actual_rule` before
    

    the arrow (either \<=\> or ==\>)

    @} */

    /** @defgroup Semantics Semantics @ingroup CHR @{

    In this subsection the operational semantics of CHR in Prolog are presented informally. They do not differ essentially from other CHR systems.

    When a constraint is called, it is considered an active constraint and the system will try to apply the rules to it. Rules are tried and executed sequentially in the order they are written.

    A rule is conceptually tried for an active constraint in the following way. The active constraint is matched with a constraint in the head of the rule. If more constraints appear in the head they are looked for among the suspended constraints, which are called passive constraints in this context. If the necessary passive constraints can be found and all match with the head of the rule and the guard of the rule succeeds, then the rule is committed and the body of the rule executed. If not all the necessary passive constraint can be found, the matching fails or the guard fails, then the body is not executed and the process of trying and executing simply continues with the following rules. If for a rule, there are multiple constraints in the head, the active constraint will try the rule sequentially multiple times, each time trying to match with another constraint.

    This process ends either when the active constraint disappears, i.e. it is removed by some rule, or after the last rule has been processed. In the latter case the active constraint becomes suspended.

    A suspended constraint is eligible as a passive constraint for an active constraint. The other way it may interact again with the rules, is when a variable appearing in the constraint becomes bound to either a nonvariable or another variable involved in one or more constraints. In that case the constraint is triggered, i.e. it becomes an active constraint and all the rules are tried.

    @} */

    /** @defgroup Rule_Types @ingroup CHR @{

    There are three different kinds of rules, each with their specific semantics:

    + simplification
    

    The simplification rule removes the constraints in its head and calls its body.

    + propagation
    

    The propagation rule calls its body exactly once for the constraints in its head.

    + simpagation
    

    The simpagation rule removes the constraints in its head after the \\ and then calls its body. It is an optimization of simplification rules of the form: \[constraints_1, constraints_2 <=> constraints_1, body \] Namely, in the simpagation form:

    constraints1 \ constraints2 <=> body
    

    constraints1 constraints are not called in the body.

    @} */

    /** @defgroup CHR_Rule_Names Rule Names @ingroup CHR @{

    Naming a rule is optional and has no semantical meaning. It only functions as documentation for the programmer.

    @} */

    /** @defgroup CHRPragmas Pragmas @ingroup CHR_Rule_Names @{

    The semantics of the pragmas are:

    + passive(Identifier)
    

    The constraint in the head of a rule Identifier can only act as a passive constraint in that rule.

    Additional pragmas may be released in the future.

    @} */

    /** @defgroup CHR_Options Options @ingroup CHR_Rule_Names @{

    It is possible to specify options that apply to all the CHR rules in the module. Options are specified with the option/2 declaration:

                    option(Option,Value).
    

    Available options are:

    + check_guard_bindings
    

    This option controls whether guards should be checked for illegal variable bindings or not. Possible values for this option are on, to enable the checks, and off, to disable the checks.

    + optimize
    

    This is an experimental option controlling the degree of optimization. Possible values are full, to enable all available optimizations, and off (default), to disable all optimizations.
    The default is derived from the SWI-Prolog flag optimise, where true is mapped to full. Therefore the commandline option -O provides full CHR optimization. If optimization is enabled, debugging should be disabled.

    + debug
    

    This options enables or disables the possibility to debug the CHR code. Possible values are on (default) and off. See debugging for more details on debugging. The default is derived from the prolog flag generate_debug_info, which is true by default. See -nodebug. If debugging is enabled, optimization should be disabled.

    + mode
    

    This option specifies the mode for a particular constraint. The value is a term with functor and arity equal to that of a constraint. The arguments can be one of -, + or ?. The latter is the default. The meaning is the following:

    + -
    

    The corresponding argument of every occurrence of the constraint is always unbound. + + The corresponding argument of every occurrence of the constraint is always ground. + ? The corresponding argument of every occurrence of the constraint can have any instantiation, which may change over time. This is the default value.

    The declaration is used by the compiler for various optimizations. Note that it is up to the user the ensure that the mode declaration is correct with respect to the use of the constraint. This option may occur once for each constraint.

    + type_declaration
    

    This option specifies the argument types for a particular constraint. The value is a term with functor and arity equal to that of a constraint. The arguments can be a user-defined type or one of the built-in types:

    + int
    

    The corresponding argument of every occurrence of the constraint is an integer number. + float ...{} a floating point number. + number ...{} a number. + natural ...{} a positive integer. + any The corresponding argument of every occurrence of the constraint can have any type. This is the default value.

    Currently, type declarations are only used to improve certain optimizations (guard simplification, occurrence subsumption, ...{}).

    + type_definition
    

    This option defines a new user-defined type which can be used in type declarations. The value is a term of the form type( name, list), where name is a term and list is a list of alternatives. Variables can be used to define generic types. Recursive definitions are allowed. Examples are

    type(bool,[true,false]).
    type(complex_number,[float + float * i]).
    type(binary_tree(T),[ leaf(T) | node(binary_tree(T),binary_tree(T)) ]).
    type(list(T),[ [] | [T | list(T)]).
    

    The mode, type_declaration and type_definition options are provided for backward compatibility. The new syntax is described below.

    @} */

    /** @defgroup CHR_in_YAP_Programs CHR in YAP Programs @ingroup CHR @{

    The CHR constraints defined in a particulary chr file are associated with a module. The default module is user. One should never load different chr files with the same CHR module name.

    @} */

    /** @defgroup Constraint_declaration Constraint declaration @ingroup CHR_in_YAP_Programs @{

    Every constraint used in CHR rules has to be declared. There are two ways to do this. The old style is as follows:

    option(type_definition,type(list(T),[ [] , [T|list(T)] ]).
    option(mode,foo(+,?)).
    option(type_declaration,foo(list(int),float)).
    :- constraints foo/2, bar/0.
    

    The new style is as follows:

    :- chr_type list(T) ---> [] ; [T|list(T)].
    :- constraints foo(+list(int),?float), bar.
    

    @} */

    /** @defgroup Compilation Compilation

    The@{ SWI-Prolog CHR compiler exploits term_expansion/2 rules to translate the constraint handling rules to plain Prolog. These rules are loaded from the library chr. They are activated if the compiled file has the chr extension or after finding a declaration of the format below.

    :- constraints ...
    

    It is adviced to define CHR rules in a module file, where the module declaration is immediately followed by including the chr library as examplified below:

    :- module(zebra, [ zebra/0 ]).
    :- use_module(library(chr)).
    
    :- constraints ...
    

    Using this style CHR rules can be defined in ordinary Prolog pl files and the operator definitions required by CHR do not leak into modules where they might cause conflicts.

    @} */

    /** @defgroup CHR_Debugging Debugging @ingroup CHR @{

    The CHR debugging facilities are currently rather limited. Only tracing is currently available. To use the CHR debugging facilities for a CHR file it must be compiled for debugging. Generating debug info is controlled by the CHR option debug, whose default is derived from the SWI-Prolog flag generate_debug_info. Therefore debug info is provided unless the -nodebug is used.

    @} */

    /** @defgroup Ports Ports @ingroup CHR @{

    For CHR constraints the four standard ports are defined:

    + call
    

    A new constraint is called and becomes active. + exit An active constraint exits: it has either been inserted in the store after trying all rules or has been removed from the constraint store. + fail An active constraint fails. + redo An active constraint starts looking for an alternative solution.

    In addition to the above ports, CHR constraints have five additional ports:

    + wake
    

    A suspended constraint is woken and becomes active. + insert An active constraint has tried all rules and is suspended in the constraint store. + remove An active or passive constraint is removed from the constraint store, if it had been inserted. + try An active constraints tries a rule with possibly some passive constraints. The try port is entered just before committing to the rule. + apply An active constraints commits to a rule with possibly some passive constraints. The apply port is entered just after committing to the rule.

    @} */

    /** @defgroup Tracing Tracing @ingroup CHR @{

    Tracing is enabled with the chr_trace/0 predicate and disabled with the chr_notrace/0 predicate.

    When enabled the tracer will step through the call, exit, fail, wake and apply ports, accepting debug commands, and simply write out the other ports.

    The following debug commans are currently supported:

            CHR debug options:
    
                    <cr>    creep           c       creep
    		s	skip
    		g	ancestors
                    n       nodebug
    		b	break
                    a       abort
                    f       fail
                    ?       help            h       help
    

    Their meaning is:

    + creep
    

    Step to the next port. + skip Skip to exit port of this call or wake port. + ancestors Print list of ancestor call and wake ports. + nodebug Disable the tracer. + break Enter a recursive Prolog toplevel. See break/0. + abort Exit to the toplevel. See abort/0. + fail Insert failure in execution. + help Print the above available debug options.

    @} */

    /** @defgroup CHR_Debugging_Predicates CHR Debugging Predicates @ingroup CHR @{

    The chr module contains several predicates that allow inspecting and printing the content of the constraint store.

    + chr_trace/0
    

    Activate the CHR tracer. By default the CHR tracer is activated and deactivated automatically by the Prolog predicates trace/0 and notrace/0.

    */

    /** @pred chr_notrace/0 De-activate the CHR tracer. By default the CHR tracer is activated and deactivated automatically by the Prolog predicates trace/0 and notrace/0.

    + chr_leash/0 
    

    Define the set of CHR ports on which the CHR tracer asks for user intervention (i.e. stops). Spec is either a list of ports or a predefined alias'. Defined aliases are: fullto stop at all ports,noneoroffto never stop, anddefaultto stop at thecall, exit, fail, wakeandapply` ports. See also leash/1.

    */

    /** @pred chr_show_store(+ Mod) Prints all suspended constraints of module Mod to the standard output. This predicate is automatically called by the SWI-Prolog toplevel at the end of each query for every CHR module currently loaded. The prolog-flag chr_toplevel_show_store controls whether the toplevel shows the constraint stores. The value true enables it. Any other value disables it.

    @} */

    /** @defgroup CHR_Examples Examples @ingroup CHR @{

    Here are two example constraint solvers written in CHR.

    + 
    

    The program below defines a solver with one constraint, leq/2, which is a less-than-or-equal constraint.

    :- module(leq,[cycle/3, leq/2]).
    :- use_module(library(chr)).
    
    :- constraints leq/2.
    reflexivity  @ leq(X,X) <=> true.
    antisymmetry @ leq(X,Y), leq(Y,X) <=> X = Y.
    idempotence  @ leq(X,Y) \ leq(X,Y) <=> true.
    transitivity @ leq(X,Y), leq(Y,Z) ==> leq(X,Z).
    
    cycle(X,Y,Z):-
            leq(X,Y),
            leq(Y,Z),
            leq(Z,X).
    
    + 
    

    The program below implements a simple finite domain constraint solver.

    :- module(dom,[dom/2]).
    :- use_module(library(chr)).
    
    :- constraints dom/2. 
    
    dom(X,[]) <=> fail.
    dom(X,[Y]) <=> X = Y.
    dom(X,L1), dom(X,L2) <=> intersection(L1,L2,L3), dom(X,L3).
    
    intersection([],_,[]).
    intersection([H|T],L2,[H|L3]) :-
            member(H,L2), !,
            intersection(T,L2,L3).
    intersection([_|T],L2,L3) :-
            intersection(T,L2,L3).
    

    @} */

    /** @defgroup CHR_Compatibility Compatibility with SICStus CHR @ingroup YAPPackages @{

    There are small differences between CHR in SWI-Prolog and newer YAPs and SICStus and older versions of YAP. Besides differences in available options and pragmas, the following differences should be noted:

    + [The handler/1 declaration]
    

    In SICStus every CHR module requires a handler/1 declaration declaring a unique handler name. This declaration is valid syntax in SWI-Prolog, but will have no effect. A warning will be given during compilation.

    + [The rules/1 declaration]
    

    In SICStus, for every CHR module it is possible to only enable a subset of the available rules through the rules/1 declaration. The declaration is valid syntax in SWI-Prolog, but has no effect. A warning is given during compilation.

    + [Sourcefile naming]
    

    SICStus uses a two-step compiler, where chr files are first translated into pl files. For SWI-Prolog CHR rules may be defined in a file with any extension.

    @} */

    /** @defgroup CHR_Guidelines Guidelines @ingroup YAPPackages @{

    In this section we cover several guidelines on how to use CHR to write constraint solvers and how to do so efficiently.

    + [Set semantics]
    

    The CHR system allows the presence of identical constraints, i.e. multiple constraints with the same functor, arity and arguments. For most constraint solvers, this is not desirable: it affects efficiency and possibly termination. Hence appropriate simpagation rules should be added of the form:

    {constraint \ constraint <=> true}.
    
    + [Multi-headed rules]
    

    Multi-headed rules are executed more efficiently when the constraints share one or more variables.

    + [Mode and type declarations]
    

    Provide mode and type declarations to get more efficient program execution. Make sure to disable debug (-nodebug) and enable optimization (-O).

    @} */

    /** @defgroup Logtalk Logtalk @ingroup YAPPackages @{

    The Logtalk object-oriented extension is available after running its standalone installer by using the yaplgt command in POSIX systems or by using the Logtalk - YAP shortcut in the Logtalk program group in the Start Menu on Windows systems. For more information please see the URL http://logtalk.org/.

    \copydoc real

    @} */

    /** @defgroup Threads Threads @ingroup YAPBuiltins @{

    YAP implements a SWI-Prolog compatible multithreading library. Like in SWI-Prolog, Prolog threads have their own stacks and only share the Prolog heap: predicates, records, flags and other global non-backtrackable data. The package is based on the POSIX thread standard (Butenhof:1997:PPT) used on most popular systems except for MS-Windows.

    @} */

    /** @defgroup Creating_and_Destroying_Prolog_Threads Creating and Destroying Prolog Threads @ingroup Threads @{

    @pred thread_create(: Goal, - Id, + Options)

    Create a new Prolog thread (and underlying C-thread) and start it by executing Goal. If the thread is created successfully, the thread-identifier of the created thread is unified to Id. Options is a list of options. Currently defined options are:

    + stack
    

    Set the limit in K-Bytes to which the Prolog stacks of this thread may grow. If omitted, the limit of the calling thread is used. See also the commandline -S option.

    + trail
    

    Set the limit in K-Bytes to which the trail stack of this thread may grow. If omitted, the limit of the calling thread is used. See also the commandline option -T.

    + alias
    

    Associate an alias-name with the thread. This named may be used to refer to the thread and remains valid until the thread is joined (see thread_join/2).

    + at_exit
    

    Define an exit hook for the thread. This hook is called when the thread terminates, no matter its exit status.

    + detached
    

    If false (default), the thread can be waited for using thread_join/2. thread_join/2 must be called on this thread to reclaim the all resources associated to the thread. If true, the system will reclaim all associated resources automatically after the thread finishes. Please note that thread identifiers are freed for reuse after a detached thread finishes or a normal thread has been joined. See also thread_join/2 and thread_detach/1.

    The Goal argument is copied to the new Prolog engine. This implies further instantiation of this term in either thread does not have consequences for the other thread: Prolog threads do not share data from their stacks.

    */

    /** @pred thread_create(: Goal, - Id)

    Create a new Prolog thread using default options. See thread_create/3.

    */

    /** @pred thread_create(: Goal)

    Create a new Prolog detached thread using default options. See thread_create/3.

    */

    /** @pred thread_self(- Id)

    Get the Prolog thread identifier of the running thread. If the thread has an alias, the alias-name is returned.

    */

    /** @pred thread_join(+ Id, - Status)

    Wait for the termination of thread with given Id. Then unify the result-status of the thread with Status. After this call, Id becomes invalid and all resources associated with the thread are reclaimed. Note that threads with the attribute detached true cannot be joined. See also current_thread/2.

    A thread that has been completed without thread_join/2 being called on it is partly reclaimed: the Prolog stacks are released and the C-thread is destroyed. A small data-structure representing the exit-status of the thread is retained until thread_join/2 is called on the thread. Defined values for Status are:

    + true
    

    The goal has been proven successfully.

    + false
    

    The goal has failed.

    + exception( _Term_)
    

    The thread is terminated on an exception. See print_message/2 to turn system exceptions into readable messages.

    + exited( _Term_)
    

    The thread is terminated on thread_exit/1 using the argument Term.

    + thread_detach(+ _Id_) 
    

    Switch thread into detached-state (see detached option at thread_create/3 at runtime. Id is the identifier of the thread placed in detached state.

    One of the possible applications is to simplify debugging. Threads that are created as detached leave no traces if they crash. For not-detached threads the status can be inspected using current_thread/2. Threads nobody is waiting for may be created normally and detach themselves just before completion. This way they leave no traces on normal completion and their reason for failure can be inspected.

    */

    /** @pred thread_yield

    Voluntarily relinquish the processor.

    */

    /** @pred thread_exit(+ Term)

    Terminates the thread immediately, leaving exited( _Term_) as result-state for thread_join/2. If the thread has the attribute detached true it terminates, but its exit status cannot be retrieved using thread_join/2 making the value of Term irrelevant. The Prolog stacks and C-thread are reclaimed.

    */

    /** @pred thread_at_exit(: Term)

    Run Goal just before releasing the thread resources. This is to be compared to at_halt/1, but only for the current thread. These hooks are ran regardless of why the execution of the thread has been completed. As these hooks are run, the return-code is already available through thread_property/2 using the result of thread_self/1 as thread-identifier. If you want to guarantee the execution of an exit hook no matter how the thread terminates (the thread can be aborted before reaching the thread_at_exit/1 call), consider using instead the at_exit/1 option of thread_create/3.

    */

    /** @pred thread_setconcurrency(+ Old, - New)

    Determine the concurrency of the process, which is defined as the maximum number of concurrently active threads. Active' here means they are using CPU time. This option is provided if the thread-implementation provides pthread_setconcurrency()`. Solaris is a typical example of this family. On other systems this predicate unifies Old to 0 (zero) and succeeds silently.

    */

    /** @pred thread_sleep(+ Time)

    Make current thread sleep for Time seconds. Time may be an integer or a floating point number. When time is zero or a negative value the call succeeds and returns immediately. This call should not be used if alarms are also being used.

    @} */

    /** @defgroup Monitoring_Threads Monitoring Threads @ingroup Threads @{

    Normal multi-threaded applications should not need these the predicates from this section because almost any usage of these predicates is unsafe. For example checking the existence of a thread before signalling it is of no use as it may vanish between the two calls. Catching exceptions using catch/3 is the only safe way to deal with thread-existence errors.

    These predicates are provided for diagnosis and monitoring tasks.

    */

    /** @pred thread_property(? Id, ? Property)

    Enumerates the properties of the specified thread. Calling thread_property/2 does not influence any thread. See also thread_join/2. For threads that have an alias-name, this name can be used in Id instead of the numerical thread identifier. Property is one of:

    + status( _Status_)
    

    The thread status of a thread (see below).

    + alias( _Alias_)
    

    The thread alias, if it exists.

    + at_exit( _AtExit_)
    

    The thread exit hook, if defined (not available if the thread is already terminated).

    + detached( _Boolean_)
    

    The detached state of the thread.

    + stack( _Size_)
    

    The thread stack data-area size.

    + trail( _Size_)
    

    The thread trail data-area size.

    + system( _Size_)
    

    The thread system data-area size.

    */

    /** @pred current_thread(+ Id, - Status)

    Enumerates identifiers and status of all currently known threads. Calling current_thread/2 does not influence any thread. See also thread_join/2. For threads that have an alias-name, this name is returned in Id instead of the numerical thread identifier. Status is one of:

    + running
    

    The thread is running. This is the initial status of a thread. Please note that threads waiting for something are considered running too.

    + false
    

    The Goal of the thread has been completed and failed.

    + true
    

    The Goal of the thread has been completed and succeeded.

    + exited( _Term_)
    

    The Goal of the thread has been terminated using thread_exit/1 with Term as argument. If the underlying native thread has exited (using pthread_exit()) Term is unbound.

    + exception( _Term_)
    

    The Goal of the thread has been terminated due to an uncaught exception (see throw/1 and catch/3).

    */

    /** @pred thread_statistics(+ Id, + Key, - Value)

    Obtains statistical information on thread Id as statistics/2 does in single-threaded applications. This call returns all keys of statistics/2, although only information statistics about the stacks and CPU time yield different values for each thread.

    + mutex_statistics 
    

    Print usage statistics on internal mutexes and mutexes associated with dynamic predicates. For each mutex two numbers are printed: the number of times the mutex was acquired and the number of collisions: the number times the calling thread has to wait for the mutex. The collision-count is not available on Windows as this would break portability to Windows-95/98/ME or significantly harm performance. Generally collision count is close to zero on single-CPU hardware.

    + threads 
    

    Prints a table of current threads and their status.

    @} */

    /** @defgroup Thread_Communication Thread communication @ingroup Threads @{

    Prolog threads can exchange data using dynamic predicates, database records, and other globally shared data. These provide no suitable means to wait for data or a condition as they can only be checked in an expensive polling loop. Message queues provide a means for threads to wait for data or conditions without using the CPU.

    Each thread has a message-queue attached to it that is identified by the thread. Additional queues are created using message_queue_create/2.

    @pred thread_send_message(+ Term)

    Places Term in the message-queue of the thread running the goal. Any term can be placed in a message queue, but note that the term is copied to the receiving thread and variable-bindings are thus lost. This call returns immediately.

    */

    /** @pred thread_send_message(+ QueueOrThreadId, + Term)

    Place Term in the given queue or default queue of the indicated thread (which can even be the message queue of itself (see thread_self/1). Any term can be placed in a message queue, but note that the term is copied to the receiving thread and variable-bindings are thus lost. This call returns immediately.

    If more than one thread is waiting for messages on the given queue and at least one of these is waiting with a partially instantiated Term, the waiting threads are all sent a wakeup signal, starting a rush for the available messages in the queue. This behaviour can seriously harm performance with many threads waiting on the same queue as all-but-the-winner perform a useless scan of the queue. If there is only one waiting thread or all waiting threads wait with an unbound variable an arbitrary thread is restarted to scan the queue.

    */

    /** @pred thread_get_message(? Term)

    Examines the thread message-queue and if necessary blocks execution until a term that unifies to Term arrives in the queue. After a term from the queue has been unified unified to Term, the term is deleted from the queue and this predicate returns.

    Please note that not-unifying messages remain in the queue. After the following has been executed, thread 1 has the term gnu in its queue and continues execution using A is gnat.

       <thread 1>
       thread_get_message(a(A)),
    
       <thread 2>
       thread_send_message(b(gnu)),
       thread_send_message(a(gnat)),
    

    See also thread_peek_message/1.

    */

    /** @pred message_queue_create(? Queue)

    If Queue is an atom, create a named queue. To avoid ambiguity on thread_send_message/2, the name of a queue may not be in use as a thread-name. If Queue is unbound an anonymous queue is created and Queue is unified to its identifier.

    */

    /** @pred message_queue_destroy(+ Queue)

    Destroy a message queue created with message_queue_create/1. It is not allows to destroy the queue of a thread. Neither is it allowed to destroy a queue other threads are waiting for or, for anonymous message queues, may try to wait for later.

    */

    /** @pred thread_get_message(+ Queue, ? Term)

    As thread_get_message/1, operating on a given queue. It is allowed to peek into another thread's message queue, an operation that can be used to check whether a thread has swallowed a message sent to it.

    */

    /** @pred thread_peek_message(? Term)

    Examines the thread message-queue and compares the queued terms with Term until one unifies or the end of the queue has been reached. In the first case the call succeeds (possibly instantiating Term. If no term from the queue unifies this call fails.

    */

    /** @pred thread_peek_message(+ Queue, ? Term)

    As thread_peek_message/1, operating on a given queue. It is allowed to peek into another thread's message queue, an operation that can be used to check whether a thread has swallowed a message sent to it.

    Explicit message queues are designed with the worker-pool model in mind, where multiple threads wait on a single queue and pick up the first goal to execute. Below is a simple implementation where the workers execute arbitrary Prolog goals. Note that this example provides no means to tell when all work is done. This must be realised using additional synchronisation.

    %    create_workers(+Id, +N)
    %    
    %    Create a pool with given Id and number of workers.
    
    create_workers(Id, N) :-
        message_queue_create(Id),
        forall(between(1, N, _),
               thread_create(do_work(Id), _, [])).
    
    do_work(Id) :-
        repeat,
          thread_get_message(Id, Goal),
          (   catch(Goal, E, print_message(error, E))
          ->  true
          ;   print_message(error, goal_failed(Goal, worker(Id)))
          ),
        fail.
    
    %    work(+Id, +Goal)
    %    
    %    Post work to be done by the pool
    
    work(Id, Goal) :-
        thread_send_message(Id, Goal).
    

    @} */

    /** @defgroup Signalling_Threads Signalling Threads @ingroup Threadas @{

    These predicates provide a mechanism to make another thread execute some goal as an interrupt. Signalling threads is safe as these interrupts are only checked at safe points in the virtual machine. Nevertheless, signalling in multi-threaded environments should be handled with care as the receiving thread may hold a mutex (see with_mutex/2). Signalling probably only makes sense to start debugging threads and to cancel no-longer-needed threads with throw/1, where the receiving thread should be designed carefully do handle exceptions at any point.

    */

    /** @pred thread_signal(+ ThreadId, : Goal)

    Make thread ThreadId execute Goal at the first opportunity. In the current implementation, this implies at the first pass through the Call-port. The predicate thread_signal/2 itself places Goal into the signalled-thread's signal queue and returns immediately.

    Signals (interrupts) do not cooperate well with the world of multi-threading, mainly because the status of mutexes cannot be guaranteed easily. At the call-port, the Prolog virtual machine holds no locks and therefore the asynchronous execution is safe.

    Goal can be any valid Prolog goal, including throw/1 to make the receiving thread generate an exception and trace/0 to start tracing the receiving thread.

    @} */

    /** @defgroup Threads_and_Dynamic_Predicates Threads and Dynamic Predicates @ingroup Threads @{

    Besides queues threads can share and exchange data using dynamic predicates. The multi-threaded version knows about two types of dynamic predicates. By default, a predicate declared dynamic (see dynamic/1) is shared by all threads. Each thread may assert, retract and run the dynamic predicate. Synchronisation inside Prolog guarantees the consistency of the predicate. Updates are logical: visible clauses are not affected by assert/retract after a query started on the predicate. In many cases primitive from thread synchronisation should be used to ensure application invariants on the predicate are maintained.

    Besides shared predicates, dynamic predicates can be declared with the thread_local/1 directive. Such predicates share their attributes, but the clause-list is different in each thread.

    */

    /** @pred thread_local( +Functor/Arity)

    related to the dynamic/1 directive. It tells the system that the predicate may be modified using assert/1, retract/1, etc, during execution of the program. Unlike normal shared dynamic data however each thread has its own clause-list for the predicate. As a thread starts, this clause list is empty. If there are still clauses as the thread terminates these are automatically reclaimed by the system. The thread_local property implies the property dynamic.

    Thread-local dynamic predicates are intended for maintaining thread-specific state or intermediate results of a computation.

    It is not recommended to put clauses for a thread-local predicate into a file as in the example below as the clause is only visible from the thread that loaded the source-file. All other threads start with an empty clause-list.

    :- thread_local
        foo/1.
    
    foo(gnat).
    

    @} */

    /** @defgroup Thread_Synchronisation Thread Synchronisation

    All@{ internal Prolog operations are thread-safe. This implies two Prolog threads can operate on the same dynamic predicate without corrupting the consistency of the predicate. This section deals with user-level mutexes (called monitors in ADA or critical-sections by Microsoft). A mutex is a MUTual EXclusive device, which implies at most one thread can hold a mutex.

    Mutexes are used to realise related updates to the Prolog database. With related', we refer to the situation where a transaction' implies two or more changes to the Prolog database. For example, we have a predicate address/2, representing the address of a person and we want to change the address by retracting the old and asserting the new address. Between these two operations the database is invalid: this person has either no address or two addresses, depending on the assert/retract order.

    Here is how to realise a correct update:

    :- initialization
        mutex_create(addressbook).
    
    change_address(Id, Address) :-
        mutex_lock(addressbook),
        retractall(address(Id, _)),
        asserta(address(Id, Address)),
        mutex_unlock(addressbook).
    

    */

    /** @pred mutex_create(? MutexId)

    Create a mutex. if MutexId is an atom, a named mutex is created. If it is a variable, an anonymous mutex reference is returned. There is no limit to the number of mutexes that can be created.

    */

    /** @pred mutex_destroy(+ MutexId)

    Destroy a mutex. After this call, MutexId becomes invalid and further references yield an existence_error exception.

    */

    /** @pred with_mutex(+ MutexId, : Goal)

    Execute Goal while holding MutexId. If Goal leaves choicepoints, these are destroyed (as in once/1). The mutex is unlocked regardless of whether Goal succeeds, fails or raises an exception. An exception thrown by Goal is re-thrown after the mutex has been successfully unlocked. See also mutex_create/2.

    Although described in the thread-section, this predicate is also available in the single-threaded version, where it behaves simply as once/1.

    */

    /** @pred mutex_lock(+ MutexId)

    Lock the mutex. Prolog mutexes are recursive mutexes: they can be locked multiple times by the same thread. Only after unlocking it as many times as it is locked, the mutex becomes available for locking by other threads. If another thread has locked the mutex the calling thread is suspended until to mutex is unlocked.

    If MutexId is an atom, and there is no current mutex with that name, the mutex is created automatically using mutex_create/1. This implies named mutexes need not be declared explicitly.

    Please note that locking and unlocking mutexes should be paired carefully. Especially make sure to unlock mutexes even if the protected code fails or raises an exception. For most common cases use with_mutex/2, which provides a safer way for handling Prolog-level mutexes.

    */

    /** @pred mutex_trylock(+ MutexId)

    As mutex_lock/1, but if the mutex is held by another thread, this predicates fails immediately.

    */

    /** @pred mutex_unlock(+ MutexId)

    Unlock the mutex. This can only be called if the mutex is held by the calling thread. If this is not the case, a permission_error exception is raised.

    */

    /** @pred mutex_unlock_all

    Unlock all mutexes held by the current thread. This call is especially useful to handle thread-termination using abort/0 or exceptions. See also thread_signal/2.

    */

    /** @pred current_mutex(? MutexId, ? ThreadId, ? Count)

    Enumerates all existing mutexes. If the mutex is held by some thread, ThreadId is unified with the identifier of the holding thread and Count with the recursive count of the mutex. Otherwise, ThreadId is [] and Count is 0.

    @} */

    /** @defgroup Parallelism Parallelism @ingroup YAPPackages @{

    There has been a sizeable amount of work on an or-parallel implementation for YAP, called YAPOr. Most of this work has been performed by Ricardo Rocha. In this system parallelism is exploited implicitly by running several alternatives in or-parallel. This option can be enabled from the configure script or by checking the system's Makefile.

    YAPOr is still a very experimental system, going through rapid development. The following restrictions are of note:

    + *YAPOr* currently only supports the Linux/X86 and SPARC/Solaris
    

    platforms. Porting to other Unix-like platforms should be straightforward.

    + *YAPOr* does not support parallel updates to the
    

    data-base.

    + *YAPOr* does not support opening or closing of streams during
    

    parallel execution.

    + Garbage collection and stack shifting are not supported in
    

    YAPOr.

    + Built-ins that cause side-effects can only be executed when
    

    left-most in the search-tree. There are no primitives to provide asynchronous or cavalier execution of these built-ins, as in Aurora or Muse.

    + YAP does not support voluntary suspension of work.
    

    We expect that some of these restrictions will be removed in future releases.

    @} */

    /** @defgroup Tabling Tabling @ingroup YAPBuiltins @{

    YAPTab is the tabling engine that extends YAP's execution model to support tabled evaluation for definite programs. YAPTab was implemented by Ricardo Rocha and its implementation is largely based on the ground-breaking design of the XSB Prolog system, which implements the SLG-WAM. Tables are implemented using tries and YAPTab supports the dynamic intermixing of batched scheduling and local scheduling at the subgoal level. Currently, the following restrictions are of note:

    + YAPTab does not handle tabled predicates with loops through negation (undefined behaviour).
    + YAPTab does not handle tabled predicates with cuts (undefined behaviour).
    + YAPTab does not support coroutining (configure error).
    + YAPTab does not support tabling dynamic predicates (permission error).
    

    To experiment with YAPTab use --enable-tabling in the configure script or add -DTABLING to YAP_EXTRAS in the system's Makefile. We next describe the set of built-ins predicates designed to interact with YAPTab and control tabled execution:

    */

    /** @pred table + P

    Declares predicate P (or a list of predicates P1,..., Pn or [ P1,..., Pn]) as a tabled predicate. P must be written in the form name/arity. Examples:

    :- table son/3.
    :- table father/2.
    :- table mother/2.
    

    or

    :- table son/3, father/2, mother/2.
    

    or

    :- table [son/3, father/2, mother/2].
    

    */

    /** @pred is_tabled(+ P)

    Succeeds if the predicate P (or a list of predicates P1,..., Pn or [ P1,..., Pn]), of the form name/arity, is a tabled predicate.

    */

    /** @pred tabling_mode(+ P,? Mode)

    Sets or reads the default tabling mode for a tabled predicate P (or a list of predicates P1,..., Pn or [ P1,..., Pn]). The list of Mode options includes:

    + batched
    

    Defines that, by default, batched scheduling is the scheduling strategy to be used to evaluated calls to predicate P. + local Defines that, by default, local scheduling is the scheduling strategy to be used to evaluated calls to predicate P. + exec_answers Defines that, by default, when a call to predicate P is already evaluated (completed), answers are obtained by executing compiled WAM-like code directly from the trie data structure. This reduces the loading time when backtracking, but the order in which answers are obtained is undefined. + load_answers Defines that, by default, when a call to predicate P is already evaluated (completed), answers are obtained (as a consumer) by loading them from the trie data structure. This guarantees that answers are obtained in the same order as they were found. Somewhat less efficient but creates less choice-points.

    The default tabling mode for a new tabled predicate is batched and exec_answers. To set the tabling mode for all predicates at once you can use the yap_flag/2 predicate as described next.

    */

    /** @pred yap_flag(tabling_mode,? Mode) Sets or reads the tabling mode for all tabled predicates. The list of Mode options includes:

    + default
    

    Defines that (i) all calls to tabled predicates are evaluated using the predicate default mode, and that (ii) answers for all completed calls are obtained by using the predicate default mode. + batched Defines that all calls to tabled predicates are evaluated using batched scheduling. This option ignores the default tabling mode of each predicate. + local Defines that all calls to tabled predicates are evaluated using local scheduling. This option ignores the default tabling mode of each predicate. + exec_answers Defines that answers for all completed calls are obtained by executing compiled WAM-like code directly from the trie data structure. This option ignores the default tabling mode of each predicate. + load_answers Defines that answers for all completed calls are obtained by loading them from the trie data structure. This option ignores the default tabling mode of each predicate.

    */

    /** @pred abolish_table(+ P)

    Removes all the entries from the table space for predicate P (or a list of predicates P1,..., Pn or [ P1,..., Pn]). The predicate remains as a tabled predicate.

    */

    /** @pred abolish_all_tables/0

    Removes all the entries from the table space for all tabled predicates. The predicates remain as tabled predicates.

    */

    /** @pred show_table(+ P)

    Prints table contents (subgoals and answers) for predicate P (or a list of predicates P1,..., Pn or [ P1,..., Pn]).

    */

    /** @pred table_statistics(+ P)

    Prints table statistics (subgoals and answers) for predicate P (or a list of predicates P1,..., Pn or [ P1,..., Pn]).

    */

    /** @pred tabling_statistics/0

    Prints statistics on space used by all tables.

    @} */

    /** @defgroup Low_Level_Tracing Tracing at Low Level @ingroup YAPBuiltins @{

    It is possible to follow the flow at abstract machine level if YAP is compiled with the flag LOW_LEVEL_TRACER. Note that this option is of most interest to implementers, as it quickly generates an huge amount of information.

    Low level tracing can be toggled from an interrupt handler by using the option T. There are also two built-ins that activate and deactivate low level tracing:

    */

    /** @pred start_low_level_trace

    Begin display of messages at procedure entry and retry.

    + stop_low_level_trace 
    

    Stop display of messages at procedure entry and retry.

    Note that this compile-time option will slow down execution.

    @} */

    /** @defgroup Low_Level_Profiling Profiling the Abstract Machine

    Imp@{ lementors may be interested in detecting on which abstract machine instructions are executed by a program. The ANALYST flag can give WAM level information. Note that this option slows down execution very substantially, and is only of interest to developers of the system internals, or to system debuggers.

    */

    /** @pred reset_op_counters

    Reinitialize all counters.

    */

    /** @pred show_op_counters(+ A)

    Display the current value for the counters, using label A. The label must be an atom.

    */

    /** @pred show_ops_by_group(+ A)

    Display the current value for the counters, organized by groups, using label A. The label must be an atom.

    @} */

    /** @defgroup Debugging Debugging @ingroup YAPBuiltins @{

    @} */

    /** @defgroup Deb_Preds Debugging Predicates

    The@{ following predicates are available to control the debugging of programs:

    + debug
    

    Switches the debugger on.

    + debugging 
    

    Outputs status information about the debugger which includes the leash mode and the existing spy-points, when the debugger is on.

    + nodebug 
    

    Switches the debugger off.

    */

    /** @pred spy + P

    Sets spy-points on all the predicates represented by P. P can either be a single specification or a list of specifications. Each one must be of the form Name/Arity or Name. In the last case all predicates with the name Name will be spied. As in C-Prolog, system predicates and predicates written in C, cannot be spied.

    */

    /** @pred nospy + P

    Removes spy-points from all predicates specified by P. The possible forms for P are the same as in spy P.

    */

    /** @pred nospyall

    Removes all existing spy-points.

    */

    /** @pred leash(+ M)

    Sets leashing mode to M. The mode can be specified as:

    + full
    

    prompt on Call, Exit, Redo and Fail + tight prompt on Call, Redo and Fail + half prompt on Call and Redo + loose prompt on Call + off never prompt + none never prompt, same as off

    The initial leashing mode is full.

    The user may also specify directly the debugger ports where he wants to be prompted. If the argument for leash is a number N, each of lower four bits of the number is used to control prompting at one the ports of the box model. The debugger will prompt according to the following conditions:

    + 
    

    if N/\\ 1 =\\= 0 prompt on fail + if N/\\ 2 =\\= 0 prompt on redo + if N/\\ 4 =\\= 0 prompt on exit + if N/\\ 8 =\\= 0 prompt on call

    Therefore, leash(15) is equivalent to leash(full) and leash(0) is equivalent to leash(off).

    Another way of using leash is to give it a list with the names of the ports where the debugger should stop. For example, leash([call,exit,redo,fail]) is the same as leash(full) or leash(15) and leash([fail]) might be used instead of leash(1).

    */

    /** @pred spy_write(+ Stream,Term)

    If defined by the user, this predicate will be used to print goals by the debugger instead of write/2.

    */

    /** @pred trace

    Switches on the debugger and starts tracing.

    */

    /** @pred notrace

    Ends tracing and exits the debugger. This is the same as nodebug/0.

    @} */

    /** @defgroup Deb_Interaction Interacting with the debugger

    Deb@{ ugging with YAP is similar to debugging with C-Prolog. Both systems include a procedural debugger, based on Byrd's four port model. In this model, execution is seen at the procedure level: each activation of a procedure is seen as a box with control flowing into and out of that box.

    In the four port model control is caught at four key points: before entering the procedure, after exiting the procedure (meaning successful evaluation of all queries activated by the procedure), after backtracking but before trying new alternative to the procedure and after failing the procedure. Each one of these points is named a port:

    @group
               *--------------------------------------*
       Call    |                                      |    Exit
    ---------> +  descendant(X,Y) :- offspring(X,Y).  + --------->
               |                                      |
               |  descendant(X,Z) :-                  |
    <--------- +     offspring(X,Y), descendant(Y,Z). + <---------
       Fail    |                                      |    Redo
               *--------------------------------------*
    
    + Call
    

    The call port is activated before initial invocation of procedure. Afterwards, execution will try to match the goal with the head of existing clauses for the procedure. + Exit This port is activated if the procedure succeeds. Control will now leave the procedure and return to its ancestor. + Redo if the goal, or goals, activated after the call port fail then backtracking will eventually return control to this procedure through the redo port. + Fail If all clauses for this predicate fail, then the invocation fails, and control will try to redo the ancestor of this invocation.

    To start debugging, the user will either call trace or spy the relevant procedures, entering debug mode, and start execution of the program. When finding the first spy-point, YAP's debugger will take control and show a message of the form:

    * (1)  call:  quicksort([1,2,3],_38) ?
    

    The debugger message will be shown while creeping, or at spy-points, and it includes four or five fields:

    + 
    

    The first three characters are used to point out special states of the debugger. If the port is exit and the first character is '?', the current call is non-deterministic, that is, it still has alternatives to be tried. If the second character is a \*, execution is at a spy-point. If the third character is a \>, execution has returned either from a skip, a fail or a redo command. + The second field is the activation number, and uniquely identifies the activation. The number will start from 1 and will be incremented for each activation found by the debugger. + In the third field, the debugger shows the active port. + The fourth field is the goal. The goal is written by write_term/3 on the standard error stream, using the options given by debugger_print_options.

    If the active port is leashed, the debugger will prompt the user with a ?, and wait for a command. A debugger command is just a character, followed by a return. By default, only the call and redo entries are leashed, but the leash/1 predicate can be used in order to make the debugger stop where needed.

    There are several commands available, but the user only needs to remember the help command, which is h. This command shows all the available options, which are:

    + c - creep
    

    this command makes YAP continue execution and stop at the next leashed port. + return - creep the same as c + l - leap YAP will execute until it meets a port for a spied predicate; this mode keeps all computation history for debugging purposes, so it is more expensive than standard execution. Use k or z for fast execution. + k - quasi-leap similar to leap but faster since the computation history is not kept; useful when leap becomes too slow. + z - zip same as k + s - skip YAP will continue execution without showing any messages until returning to the current activation. Spy-points will be ignored in this mode. Note that this command keeps all debugging history, use t for fast execution. This command is meaningless, and therefore illegal, in the fail and exit ports. + t - fast-skip similar to skip but faster since computation history is not kept; useful if skip becomes slow. + f [ GoalId] - fail If given no argument, forces YAP to fail the goal, skipping the fail port and backtracking to the parent. If f receives a goal number as the argument, the command fails all the way to the goal. If goal GoalId has completed execution, YAP fails until meeting the first active ancestor. + r [ GoalId] - retry This command forces YAP to jump back call to the port. Note that any side effects of the goal cannot be undone. This command is not available at the call port. If f receives a goal number as the argument, the command retries goal GoalId instead. If goal GoalId has completed execution, YAP fails until meeting the first active ancestor.

    + a - abort
    

    execution will be aborted, and the interpreter will return to the top-level. YAP disactivates debug mode, but spypoints are not removed. + n - nodebug stop debugging and continue execution. The command will not clear active spy-points. + e - exit leave YAP. + h - help show the debugger commands. + ! Query execute a query. YAP will not show the result of the query. + b - break break active execution and launch a break level. This is the same as !break. + + - spy this goal start spying the active goal. The same as ! spy G where G is the active goal. + - - nospy this goal stop spying the active goal. The same as ! nospy G where G is the active goal. + p - print shows the active goal using print/1 + d - display shows the active goal using display/1 + <Depth - debugger write depth sets the maximum write depth, both for composite terms and lists, that will be used by the debugger. For more information about write_depth/2 ( (see Input/Output Control)). + < - full term resets to the default of ten the debugger's maximum write depth. For more information about write_depth/2 ( (see Input/Output Control)). + A - alternatives show the list of backtrack points in the current execution. + g [ N] show the list of ancestors in the current debugging environment. If it receives N, show the first N ancestors.

    The debugging information, when fast-skip quasi-leap is used, will be lost.

    */

    /** @page Efficiency Efficiency Considerations

    We next discuss several issues on trying to make Prolog programs run fast in YAP. We assume two different programming styles:

    + Execution of <em>deterministic</em> programs often
    

    boils down to a recursive loop of the form:

    loop(Env) :-
            do_something(Env,NewEnv),
            loop(NewEnv).
    

    @} */

    /** @defgroup Indexing Indexing

    The@{ indexation mechanism restricts the set of clauses to be tried in a procedure by using information about the status of the instantiated arguments of the goal. These arguments are then used as a key, selecting a restricted set of a clauses from all the clauses forming the procedure.

    As an example, the two clauses for concatenate:

    concatenate([],L,L).
    concatenate([H|T],A,[H|NT]) :- concatenate(T,A,NT).
    

    If the first argument for the goal is a list, then only the second clause is of interest. If the first argument is the nil atom, the system needs to look only for the first clause. The indexation generates instructions that test the value of the first argument, and then proceed to a selected clause, or group of clauses.

    Note that if the first argument was a free variable, then both clauses should be tried. In general, indexation will not be useful if the first argument is a free variable.

    When activating a predicate, a Prolog system needs to store state information. This information, stored in a structure known as choice point or fail point, is necessary when backtracking to other clauses for the predicate. The operations of creating and using a choice point are very expensive, both in the terms of space used and time spent. Creating a choice point is not necessary if there is only a clause for the predicate as there are no clauses to backtrack to. With indexation, this situation is extended: in the example, if the first argument was the atom nil, then only one clause would really be of interest, and it is pointless to create a choice point. This feature is even more useful if the first argument is a list: without indexation, execution would try the first clause, creating a choice point. The clause would fail, the choice point would then be used to restore the previous state of the computation and the second clause would be tried. The code generated by the indexation mechanism would behave much more efficiently: it would test the first argument and see whether it is a list, and then proceed directly to the second clause.

    An important side effect concerns the use of "cut". In the above example, some programmers would use a "cut" in the first clause just to inform the system that the predicate is not backtrackable and force the removal the choice point just created. As a result, less space is needed but with a great loss in expressive power: the "cut" would prevent some uses of the procedure, like generating lists through backtracking. Of course, with indexation the "cut" becomes useless: the choice point is not even created.

    Indexation is also very important for predicates with a large number of clauses that are used like tables:

    logician(aristoteles,greek).
    logician(frege,german).
    logician(russel,english).
    logician(godel,german).
    logician(whitehead,english).
    

    An interpreter like C-Prolog, trying to answer the query:

    ?- logician(godel,X).
    

    would blindly follow the standard Prolog strategy, trying first the first clause, then the second, the third and finally finding the relevant clause. Also, as there are some more clauses after the important one, a choice point has to be created, even if we know the next clauses will certainly fail. A "cut" would be needed to prevent some possible uses for the procedure, like generating all logicians. In this situation, the indexing mechanism generates instructions that implement a search table. In this table, the value of the first argument would be used as a key for fast search of possibly matching clauses. For the query of the last example, the result of the search would be just the fourth clause, and again there would be no need for a choice point.

    If the first argument is a complex term, indexation will select clauses just by testing its main functor. However, there is an important exception: if the first argument of a clause is a list, the algorithm also uses the list's head if not a variable. For instance, with the following clauses,

    rules([],B,B).
    rules([n(N)|T],I,O) :- rules_for_noun(N,I,N), rules(T,N,O).
    rules([v(V)|T],I,O) :- rules_for_verb(V,I,N), rules(T,N,O).
    rules([q(Q)|T],I,O) :- rules_for_qualifier(Q,I,N), rules(T,N,O).
    

    if the first argument of the goal is a list, its head will be tested, and only the clauses matching it will be tried during execution.

    Some advice on how to take a good advantage of this mechanism:

    + 
    

    Try to make the first argument an input argument.

    + 
    

    Try to keep together all clauses whose first argument is not a variable, that will decrease the number of tests since the other clauses are always tried.

    + 
    

    Try to avoid predicates having a lot of clauses with the same key. For instance, the procedure:

    type(n(mary),person).
    type(n(john), person).
    type(n(chair),object).
    type(v(eat),active).
    type(v(rest),passive).
    

    becomes more efficient with:

    type(n(N),T) :- type_of_noun(N,T).
    type(v(V),T) :- type_of_verb(V,T).
    
    type_of_noun(mary,person).
    type_of_noun(john,person).
    type_of_noun(chair,object).
    
    type_of_verb(eat,active).
    type_of_verb(rest,passive).
    

    */

    /** @page ChYInterface C Language interface to YAP

    YAP provides the user with three facilities for writing predicates in a language other than Prolog. Under Unix systems, most language implementations were linkable to C, and the first interface exported the YAP machinery to the C language. YAP also implements most of the SWI-Prolog foreign language interface. This gives portability with a number of SWI-Prolog packages. Last, a new C++ based interface is being designed to work with the swig (@url(www.swig.org}) interface compiler.

    + The @ref c-interface  YAP C-interface exports the YAP engine.
    + The @ref swi-c-interface emulates Jan Wielemaker's SWI foreign language interface.
    + The @ref  yap-cplus-interface is desiged to interface with Object-Oriented systems.
    

    @} */

    /** @defgroup Loading_Objects Loading Object Files

    The@{ primitive predicate

    */

    /** @pred load_foreign_files( Files, Libs, InitRoutine)

    should be used, from inside YAP, to load object files produced by the C compiler. The argument ObjectFiles should be a list of atoms specifying the object files to load, Libs is a list (possibly empty) of libraries to be passed to the unix loader (ld) and InitRoutine is the name of the C routine (to be called after the files are loaded) to perform the necessary declarations to YAP of the predicates defined in the files.

    YAP will search for ObjectFiles in the current directory first. If it cannot find them it will search for the files using the environment variable:

    + YAPLIBDIR
    

    if defined, or in the default library.

    YAP also supports the SWI-Prolog interface to loading foreign code:

    */

    /** @pred open_shared_object(+ File, - Handle)

    File is the name of a shared object file (called dynamic load library in MS-Windows). This file is attached to the current process and Handle is unified with a handle to the library. Equivalent to open_shared_object(File, [], Handle). See also load_foreign_library/1 and load_foreign_library/2.

    On errors, an exception shared_object( Action, Message) is raised. Message is the return value from dlerror().

    */

    /** @pred open_shared_object(+ File, - Handle, + Options)

    As open_shared_object/2, but allows for additional flags to be passed. Options is a list of atoms. now implies the symbols are resolved immediately rather than lazily (default). global implies symbols of the loaded object are visible while loading other shared objects (by default they are local). Note that these flags may not be supported by your operating system. Check the documentation of dlopen() or equivalent on your operating system. Unsupported flags are silently ignored.

    */

    /** @pred close_shared_object(+ Handle)

    Detach the shared object identified by Handle.

    */

    /** @pred call_shared_object_function(+ Handle, + Function)

    Call the named function in the loaded shared library. The function is called without arguments and the return-value is ignored. In SWI-Prolog, normally this function installs foreign language predicates using calls to PL_register_foreign().

    @} */

    /** @defgroup SavebQeERest Saving and Restoring

    YAP@{ 4 currently does not support save and restore for object code loaded with load_foreign_files/3. We plan to support save and restore in future releases of YAP.

    */