@chapter SWI-Prolog Emulation This library provides a number of SWI-Prolog builtins that are not by default in YAP. This library is loaded with the @code{use_module(library(swi))} command. @table @code @item append(?@var{List1},?@var{List2},?@var{List3}) @findex append/3 @snindex append/3 @cnindex append/3 Succeeds when @var{List3} unifies with the concatenation of @var{List1} and @var{List2}. The predicate can be used with any instantiation pattern (even three variables). @item between(+@var{Low},+@var{High},?@var{Value}) @findex between/3 @snindex between/3 @cnindex between/3 @var{Low} and @var{High} are integers, @var{High} less or equal than @var{Low}. If @var{Value} is an integer, @var{Low} less or equal than @var{Value} less or equal than @var{High}. When @var{Value} is a variable it is successively bound to all integers between @var{Low} and @var{High}. If @var{High} is @code{inf}, @code{between/3} is true iff @var{Value} less or equal than @var{Low}, a feature that is particularly interesting for generating integers from a certain value. @item chdir(+@var{Dir}) @findex chdir/1 @snindex chdir/1 @cnindex chdir/1 Compatibility predicate. New code should use @code{working_directory/2}. @item concat_atom(+@var{List},-@var{Atom}) @findex concat_atom/2 @snindex concat_atom/2 @cnindex concat_atom/2 @var{List} is a list of atoms, integers or floating point numbers. Succeeds if @var{Atom} can be unified with the concatenated elements of @var{List}. If @var{List} has exactly 2 elements it is equivalent to @code{atom_concat/3}, allowing for variables in the list. @item concat_atom(?@var{List},+@var{Separator},?@var{Atom}) @findex concat_atom/3 @snindex concat_atom/3 @cnindex concat_atom/3 Creates an atom just like concat_atom/2, but inserts @var{Separator} between each pair of atoms. For example: \@example ?- concat_atom([gnu, gnat], ', ', A). A = 'gnu, gnat' @end example (Unimplemented) This predicate can also be used to split atoms by instantiating @var{Separator} and @var{Atom}: @example ?- concat_atom(L, -, 'gnu-gnat'). L = [gnu, gnat] @end example @item nth1(+@var{Index},?@var{List},?@var{Elem}) @findex nth1/3 @snindex nth1/3 @cnindex nth1/3 Succeeds when the @var{Index}-th element of @var{List} unifies with @var{Elem}. Counting starts at 1. Set environment variable. @var{Name} and @var{Value} should be instantiated to atoms or integers. The environment variable will be passed to @code{shell/[0-2]} and can be requested using @code{getenv/2}. They also influence @code{expand_file_name/2}. @item setenv(+@var{Name},+@var{Value}) @findex setenv/2 @snindex setenv/2 @cnindex setenv/2 Set environment variable. @var{Name} and @var{Value} should be instantiated to atoms or integers. The environment variable will be passed to @code{shell/[0-2]} and can be requested using @code{getenv/2}. They also influence @code{expand_file_name/2}. @item term_to_atom(?@var{Term},?@var{Atom}) @findex term_to_atom/2 @snindex term_to_atom/2 @cnindex term_to_atom/2 Succeeds if @var{Atom} describes a term that unifies with @var{Term}. When @var{Atom} is instantiated @var{Atom} is converted and then unified with @var{Term}. If @var{Atom} has no valid syntax, a @code{syntax_error} exception is raised. Otherwise @var{Term} is ``written'' on @var{Atom} using @code{write/1}. @item working_directory(-@var{Old},+@var{New}) @findex working_directory/2 @snindex working_directory/2 @cnindex working_directory/2 Unify @var{Old} with an absolute path to the current working directory and change working directory to @var{New}. Use the pattern @code{working_directory(CWD, CWD)} to get the current directory. See also @code{absolute_file_name/2} and @code{chdir/1}. @item @@@var{Term1} =@@= @@@var{Term2} @findex =@@=/2 @snindex =@@=/2 @cnindex =@@=/2 True iff @var{Term1} and @var{Term2} are structurally equivalent. I.e. if @var{Term1} and @var{Term2} are variants of each other. @end table @node Invoking Predicates on all Members of a List,Forall, , SWI-Prolog @section Invoking Predicates on all Members of a List @c \label{sec:applylist} 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 @code{call/[2..]}, which implies common arguments can be put in front of the arguments obtained from the list(s). For example: @example ?- maplist(plus(1), [0, 1, 2], X). X = [1, 2, 3] @end example we will phrase this as ``@var{Predicate} is applied on ...'' @table @code @item maplist(+@var{Pred},+@var{List}) @findex maplist/2 @snindex maplist/2 @cnindex maplist/2 @var{Pred} is applied successively on each element of @var{List} until the end of the list or @var{Pred} fails. In the latter case @code{maplist/2} fails. @item maplist(+@var{Pred},+@var{List1},+@var{List2}) @findex maplist/3 @snindex maplist/3 @cnindex maplist/3 Apply @var{Pred} on all successive pairs of elements from @var{List1} and @var{List2}. Fails if @var{Pred} can not be applied to a pair. See the example above. @item maplist(+@var{Pred},+@var{List1},+@var{List2},+@var{List4}) @findex maplist/4 @snindex maplist/4 @cnindex maplist/4 Apply @var{Pred} on all successive triples of elements from @var{List1}, @var{List2} and @var{List3}. Fails if @var{Pred} can not be applied to a triple. See the example above. @c @item findlist(+@var{Pred},+@var{List1},?@var{List2}) @c @findex findlist/3 @c @snindex findlist/3 @c @cnindex findlist/3 @c Unify @var{List2} with a list of all elements of @var{List1} to which @c @var{Pred} applies. @end table @node Forall,hProlog and SWI-Prolog Attributed Variables,Invoking Predicates on all Members of a List, SWI-Prolog @section Forall @c \label{sec:forall2} @table @code @item forall(+@var{Cond},+@var{Action}) @findex forall/2 @snindex forall/2 @cnindex forall/2 For all alternative bindings of @var{Cond} @var{Action} can be proven. The next example verifies that all arithmetic statements in the list @var{L} are correct. It does not say which is wrong if one proves wrong. @example ?- forall(member(Result = Formula, [2 = 1 + 1, 4 = 2 * 2]), Result =:= Formula). @end example @end table @node hProlog and SWI-Prolog Attributed Variables, SWI-Prolog Global Variables, Forall,SWI-Prolog @section hProlog and SWI-Prolog Attributed Variables @cindex hProlog Attributed Variables Attributed variables @c @ref{Attributed variables} provide a technique for extending the Prolog unification algorithm by hooking the binding of attributed variables. There is little consensus in the Prolog community on the exact definition and interface to attributed variables. Yap Prolog traditionally implements a SICStus-like interface, but to enable SWI-compatibility we have implemented the SWI-Prolog interface, identical to the one realised by Bart Demoen for hProlog. 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 (builtin) 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. @example :- module(domain, [ domain/2 % Var, ?Domain ]). :- use_module(library(oset)). domain(X, Dom) :- var(Dom), !, get_attr(X, domain, Dom). domain(X, List) :- sort(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) -> oset_int(Domain, Dom2, NewDomain), ( NewDomain == [] -> fail ; NewDomain = [Value] -> Y = Value ; put_attr(Y, domain, NewDomain) ) ; var(Y) -> put_attr( Y, domain, Domain ) ; memberchk(Y, Domain) ). @end example Before explaining the code we give some example queries: @table @code @item ?- domain(X, [a,b]), X = c no @item ?- domain(X, [a,b]), domain(X, [a,c]). X = a @item ?- domain(X, [a,b,c]), domain(X, [a,c]). X = _D0 @end table The predicate @code{domain/2} fetches (first clause) or assigns (second clause) the variable a @emph{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 @code{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). @table @code @item put_attr(+@var{Var},+@var{Module},+@var{Value}) @findex put_attr/3 @snindex put_attr/3 @cnindex put_attr/3 If @var{Var} is a variable or attributed variable, set the value for the attribute named @var{Module} to @var{Value}. If an attribute with this name is already associated with @var{Var}, the old value is replaced. Backtracking will restore the old value (i.e. an attribute is a mutable term. See also @code{setarg/3}). This predicate raises a type error if @var{Var} is not a variable or @var{Module} is not an atom. @item get_attr(+@var{Var},+@var{Module},+@var{Value}) @findex get_attr/3 @snindex get_attr/3 @cnindex get_attr/3 Request the current @var{value} for the attribute named @var{Module}. If @var{Var} is not an attributed variable or the named attribute is not associated to @var{Var} this predicate fails silently. If @var{Module} is not an atom, a type error is raised. @item del_attr(+@var{Var},+@var{Module}) @findex del_attr/2 @snindex del_attr/2 @cnindex del_attr/2 Delete the named attribute. If @var{Var} loses its last attribute it is transformed back into a traditional Prolog variable. If @var{Module} is not an atom, a type error is raised. In all other cases this predicate succeeds regardless of whether or not the named attribute is present. @item attr_unify_hook(+@var{AttValue},+@var{VarValue}) @findex attr_unify_hook/2 @snindex attr_unify_hook/2 @cnindex attr_unify_hook/2 Hook that must be defined in the module an attributed variable refers to. Is is called @emph{after} the attributed variable has been unified with a non-var term, possibly another attributed variable. @var{AttValue} is the attribute that was associated to the variable in this module and @var{VarValue} is the new value of the variable. Normally this predicate fails to veto binding the variable to @var{VarValue}, forcing backtracking to undo the binding. If @var{VarValue} is another attributed variable the hook often combines the two attribute and associates the combined attribute with @var{VarValue} using @code{put_attr/3}. @c \predicate{attr_portray_hook}{2}{+AttValue, +Var} @c Called by write_term/2 and friends for each attribute if the option @c \term{attributes}{portray} is in effect. If the hook succeeds the @c attribute is considered printed. Otherwise \exam{Module = ...} is @c printed to indicate the existence of a variable. @end table @subsection Special Purpose SWI Predicates for Attributes Normal user code should deal with @code{put_attr/3}, @code{get_attr/3} and @code{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. @table @code @item get_attrs(+@var{Var},-@var{Attributes}) @findex get_attrs/2 @snindex get_attrs/2 @cnindex get_attrs/2 Get all attributes of @var{Var}. @var{Attributes} is a term of the form @code{att(Module, Value, MoreAttributes)}, where @var{MoreAttributes} is @code{[]} for the last attribute. @item put_attrs(+@var{Var},+@var{Attributes}) @findex put_attrs/2 @snindex put_attrs/2 @cnindex put_attrs/2 Set all attributes of @var{Var}. See get_attrs/2 for a description of @var{Attributes}. @item copy_term_nat(?@var{TI},-@var{TF}) @findex copy_term_nat/2 @snindex copy_term_nat/2 @cnindex copy_term_nat/2 As @code{copy_term/2}. Attributes however, are @emph{not} copied but replaced by fresh variables. @end table @node SWI-Prolog Global Variables, ,hProlog and SWI-Prolog Attributed Variables,SWI-Prolog @section SWI Global variables @c \label{sec:gvar} SWI-Prolog global variables are associations between names (atoms) and terms. They differ in various ways from storing information using @code{assert/1} or @code{recorda/3}. @itemize @bullet @item 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. @item They support both global assignment using @code{nb_setval/2} and backtrackable assignment using @code{b_setval/2}. @item Only one value (which can be an arbitrary complex Prolog term) can be associated to a variable at a time. @item Their value cannot be shared among threads. Each thread has its own namespace and values for global variables. @item Currently global variables are scoped globally. We may consider module scoping in future versions. @end itemize Both @code{b_setval/2} and @code{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 @code{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 @code{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 @emph{after} the registration. @table @code @item b_setval(+@var{Name},+@var{Value}) @findex b_setval/2 @snindex b_setval/2 @cnindex b_setval/2 Associate the term @var{Value} with the atom @var{Name} or replaces the currently associated value with @var{Value}. If @var{Name} does not refer to an existing global variable a variable with initial value @code{[]} is created (the empty list). On backtracking the assignment is reversed. @item b_getval(+@var{Name},-@var{Value}) @findex b_getval/2 @snindex b_getval/2 @cnindex b_getval/2 Get the value associated with the global variable @var{Name} and unify it with @var{Value}. Note that this unification may further instantiate the value of the global variable. If this is undesirable the normal precautions (double negation or @code{copy_term/2}) must be taken. The @code{b_getval/2} predicate generates errors if @var{Name} is not an atom or the requested variable does not exist. @end table @table @code @item nb_setval(+@var{Name},+@var{Value}) @findex nb_setval/2 @snindex nb_setval/2 @cnindex nb_setval/2 Associates a copy of @var{Value} created with @code{duplicate_term/2} with the atom @var{Name}. Note that this can be used to set an initial value other than @code{[]} prior to backtrackable assignment. @item nb_getval(+@var{Name},-@var{Value}) @findex nb_getval/2 @snindex nb_getval/2 @cnindex nb_getval/2 The @code{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 @code{nb_getval/2} can be used to document that the variable is used non-backtrackable. @c \predicate{nb_linkval}{2}{+Name, +Value} @c Associates the term @var{Value} with the atom @var{Name} without copying @c it. This is a fast special-purpose variation of nb_setval/2 intended for @c expert users only because the semantics on backtracking to a point @c before creating the link are poorly defined for compound terms. The @c principal term is always left untouched, but backtracking behaviour on @c arguments is undone if the original assignment was \jargon{trailed} and @c left alone otherwise, which implies that the history that created the @c term affects the behaviour on backtracking. Please consider the @c following example: @c \begin{code} @c demo_nb_linkval :- @c T = nice(N), @c ( N = world, @c nb_linkval(myvar, T), @c fail @c ; nb_getval(myvar, V), @c writeln(V) @c ). @c \end{code} @item nb_current(?@var{Name},?@var{Value}) @findex nb_current/2 @snindex nb_current/2 @cnindex nb_current/2 Enumerate all defined variables with their value. The order of enumeration is undefined. @item nb_delete(?@var{Name}) @findex nb_delete/1 @snindex nb_delete/1 @cnindex nb_delete/1 Delete the named global variable. @end table @subsection Compatibility of SWI-Prolog Global Variables Global variables have been introduced by various Prolog implementations recently. The implementation of them in SWI-Prolog is based on hProlog by Bart Demoen. In discussion with Bart it was decided that the semantics if hProlog @code{nb_setval/2}, which is equivalent to @code{nb_linkval/2} is not acceptable for normal Prolog users as the behaviour is influenced by how builtin predicates constructing terms (@code{read/1}, @code{=../2}, etc.) are implemented. GNU-Prolog provides a rich set of global variables, including arrays. Arrays can be implemented easily in SWI-Prolog using @code{functor/3} and @code{setarg/3} due to the unrestricted arity of compound terms. @node Extensions,Debugging,SWI-Prolog,Top @chapter Extensions to Prolog YAP includes several extensions that are not enabled by default, but that can be used to extend the functionality of the system. These options can be set at compilation time by enabling the related compilation flag, as explained in the @code{Makefile}