1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8% 
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License. 
13% 
14% The Original Code is  The ECLiPSe Constraint Logic Programming System. 
15% The Initial Developer of the Original Code is  Cisco Systems, Inc. 
16% Portions created by the Initial Developer are
17% Copyright (C) 2006 Cisco Systems, Inc.  All Rights Reserved.
18% 
19% Contributor(s): 
20% 
21% END LICENSE BLOCK
22
23:- comment(alias, "Term Manipulation").
24:- comment(summary, "Built-ins to convert, compose, decompose and modify terms").
25:- comment(categories, ["Built-In Predicates"]).
26
27:- tool(bytes_to_term / 2).
28:- tool(add_attribute / 2).
29:- tool(subscript / 3).
30:- tool(term_string / 2).
31:- tool(term_string / 3).
32:- tool(term_to_bytes / 2).
33:- tool(update_struct / 4).
34:- tool(meta_attribute / 2).
35
36
37:- comment('C' / 3, [
38	summary:"Specifies how DCG grammar rules get a token from their input.
39
40",
41	amode:('C'(+,-,-) is semidet),
42	amode:('C'(-,+,+) is det),
43	desc:html("   This predicate is only useful in connection with definite clause grammar
44   rules (DCG). There is a global default definition of 'C'/3 which
45   consists of the single clause 'C'([Token|Rest], Token, Rest).  The Input
46   argument represents the parsing input before consuming Token and Rest is
47   the input after consuming Token.
48
49<P>
50   DCGs normally operate on lists of tokens.  However, by redefining 'C'/3,
51   it is possible to let them manipulate other data structures.  The
52   example shows how to parse directly from an I/O stream.
53
54<P>
55"),
56	args:["Input" : "A List or a variable.", "Token" : "A term or a variable.", "Rest" : "A List or a variable."],
57	fail_if:"Fails if Input is not a non-empty list",
58	eg:"
59[eclipse 1]: [user].
60 sentence --> noun, [is], adjective.
61 noun --> [prolog] ; [lisp].
62 adjective --> [boring] ; [great].
63user       compiled traceable 560 bytes in 0.05 seconds
64
65yes.
66[eclipse 2]: phrase(sentence, [prolog,is,great], []).
67
68yes.
69[eclipse 3]: [user].
70:- local 'C'/3.       % to avoid a redefinition warning
71'C'(Stream-Pos0, Token, Stream-Pos1) :-
72        seek(Stream, Pos0),
73        read_string(Stream, \" \", _, TokenString),
74        atom_string(Token, TokenString),
75        at(Stream, Pos1).
76user       compiled traceable 308 bytes in 0.00 seconds
77
78yes.
79[eclipse 4]: open(string(\"prolog is great\"), read, S),
80             phrase(sentence, S-0, S-End).
81S = 9
82End = 15     More? (;)
83yes.
84
85
86
87",
88	see_also:[phrase / 3]]).
89
90:- comment(add_attribute / 2, [
91	summary:"Add dynamically an attribute to a variable",
92	amode:(add_attribute(?,?) is semidet),
93	desc:html("<P>\
94   Adds an attribute to a variable.  The attribute name is taken as the name
95   of the context module.  There must have been an attribute declaration
96   (meta_attribute/2) with the same name as the context module.
97<P>
98   If Var is a free variable, it will be turned into an attributed variable
99   with a single attribute Attribute whose name is the name of the context
100   module.  If Var is already an attributed variable with other attributes,
101   then the new attribute will be added to it.
102<P>
103   Otherwise, if the attribute slot is already occupied, or Var is already
104   instantiated, then a new attributed variable with the single attribute
105   Attribute is created, and subsequently unified with Var.
106<P>
107   Use add_attribute/3 to add an explicitly named attribute.
108<P>
109"),
110	args:["Var" : "Any term.", "Attribute" : "Any term."],
111	fail_if:"Fails if Var is not a free variable and its unification with the new attributed variable fails",
112	exceptions:[270 : "There is no attribute declared in the context module."],
113	eg:"
114[eclipse 6]: meta_attribute(eclipse, []).
115
116yes.
117[eclipse 3]: add_attribute(X, a), printf(\"%QPMw\", X).
118X{suspend : _g270 , a}
119X = X
120yes
121",
122	see_also:[meta_attribute / 2, add_attribute / 3]]).
123
124:- comment(add_attribute / 3, [
125	summary:"Add dynamically an attribute to a variable.
126
127",
128	amode:(add_attribute(?,?,+) is semidet),
129	desc:html("\
130   Adds an attribute with name AttrName and value Attribute to a variable.
131   There must have been a preceding attribute declaration (meta_attribute/2)
132   for AttrName.
133<P>
134   If Var is a free variable, it will be turned into an attributed variable
135   with a single attribute Attribute whose name is AttrName.
136   If Var is already an attributed variable with other attributes,
137   then the new attribute will be added to it.
138<P>
139   Otherwise, if the attribute slot for AttrName is already occupied, or
140   Var is already instantiated, then a new attributed variable with the
141   single attribute Attribute is created, and subsequently unified with Var.
142<P>
143   If AttrName is an atom, the attribute corresponds to a previous
144   meta_attribute declaration.  If AttrName is an integer, it is directly
145   used as an attribute index slot (this is mainly used by the compiler to
146   resolve attribute references at compile time).
147<P>
148"),
149	args:["Var" : "Any term.", "Attribute" : "Any term.", "AttrName" : "Integer or atom."],
150	fail_if:"Fails if Var is not a free variable and its unification with the new attributed variable fails",
151	exceptions:[270 : "There is no attribute declared as AttrName.",
152		6:"AttrName is an integer, but not a valid attribute index"],
153	eg:"
154[eclipse 6]: meta_attribute(extra, []).
155
156yes.
157[eclipse 3]: add_attribute(X, a, extra), printf(\"%QPMw\", X).
158X{suspend : _g270 , extra : a}
159X = X
160yes
161
162
163
164
165",
166	see_also:[meta_attribute / 2, add_attribute / 2]]).
167
168:- comment(bytes_to_term / 2, [
169	summary:"Converts String, which is supposed to be an encoding of a term, into Term.
170
171",
172	amode:(bytes_to_term(+,-) is det),
173	desc:html("   This predicate decodes strings produced by term_to_bytes/2 and
174   reconstructs the encoded term.  The string representation is
175   machine-independent, can be stored in files, sent over networks etc.
176   Note however that the string can contain arbitrary bytes,
177   including NUL and control characters.
178
179<P>
180   The predicate attempts to reconstruct the term with all its attached
181   variable attributes and delayed goals. For this to be possible, the
182   variable attributes and the predicates corresponding to delayed goals
183   must all be defined in the environment where the term is reconstructed.
184
185<P>
186   The term_to_bytes/bytes_to_term predicates differ from term_string/2
187   in that they do not create a human-readable representation, but are
188   significantly faster and convert the term with all its attributes.
189
190<P>
191"),
192	args:["String" : "A string produced by term_to_bytes/2.", "Term" : "A variable."],
193	exceptions:[5 : "String is not a string."],
194	eg:"
195[eclipse]: term_to_bytes(s(X),String), bytes_to_term(String, Term).
196String = \"\\000\\000\\000\\b\\001\\002\\013\\001\\001s\\000\\377\\006\\376\\006\\001X\\000\"
197Term = s(X)
198yes.
199
200
201
202",
203	see_also:[term_to_bytes / 2, copy_term / 2, copy_term / 3, writeq / 1, writeq / 2, write_canonical / 1, write_canonical / 2]]).
204
205:- comment(char_code / 2, [
206	summary:"Succeeds if Code is the numeric character code of the character Char.
207
208",
209	amode:(char_code(+,-) is det),
210	amode:(char_code(-,+) is det),
211	desc:html("   If Char is instantiated to a one-character atom or string,
212   Code is unified with the corresponding numeric character code,
213   depending on the character encoding in use.
214
215<P>
216   If Code is instantiated to an integer, Char is unified with the
217   corresponding one-character atom.
218
219<P>
220"),
221	args:["Char" : "One-character atom, string or variable.", "Code" : "Integer or variable."],
222	exceptions:[5 : "Char is instantiated, but not to a 1-character string or atom.", 5 : "Code is instantiated, but not to an integer.", 6 : "Code is instantiated to an integer outside the valid range for character codes.", 4 : "Neither Char nor Code are instantiated (non-coroutine mode only)."],
223	eg:"
224   Success:
225   char_code(b,98).
226   char_code(\"b\",98).
227   char_code(C,99).     (gives C=c).
228   char_code(a,I).      (gives I=97).
229   Fail:
230   char_code(a,98).
231   Error:
232   char_code(C,I).       (Error 4).
233   char_code(ab,I).      (Error 5).
234   char_code(7,I).       (Error 5).
235   char_code(C,-1).      (Error 6).
236
237
238
239",
240	see_also:[get_char / 1, get_char / 2, put_char / 1, put_char / 2, string_code/3, string_list / 2, string_list / 3]]).
241
242:- comment(copy_term / 3, [
243	summary:"A copy of OldTerm with new variables is created and unified with NewTerm.
244AttrVars is a list mapping the attributed variables in OldTerm to the corresponding
245variables in NewTerm.
246
247",
248	amode:(copy_term(?,-,-) is det),
249	desc:html("   A copy of OldTerm is created, ie.  a term that is similar to OldTerm but
250   the free variables of OldTerm have been replaced by new variables which
251   do not occur elsewhere.  In other words, the new term is a most general
252   variant of the old one in the sense of variant/2.
253
254<P>
255   This predicate is a more primitive version of copy_term/2 and does
256   not imply a particular handling of attributed variables. Instead it copies the
257   attributed variables as normal variables, and returns the AttrVars list as
258   a means to define the copying of attributed variables separately.  AttrVars is a
259   list of pairs [&lt;attributed variable&gt;|&lt;variable&gt;] which maps the
260   attributed variables in OldTerm to the corresponding fresh variables in
261   NewTerm.  By processing this list, the variables can be instantiated to
262   whatever the user defines as the copy of the attributed variable.
263
264<P>
265   Note that copy_term/2 is implemented as
266<P>
267<PRE>
268    copy_term(X, Y) :-
269        copy_term(X, Y, Metas),
270        apply_copy_term_handlers(Metas).
271</PRE>
272"),
273	args:["OldTerm" : "Prolog term.",
274		"NewTerm" : "Prolog term, normally a variable.",
275		"AttrVars" : "List of Pairs or a variable."],
276	eg:"
277[eclipse 1]: set_flag(output_mode, \"QPMV\").
278
279yes.
280[eclipse 3]: copy_term(s(a,X{a},Y, Z{b}), Copy, Metas).
281
282X = X_m234{a}
283Y = Y_g224
284Z = Z_m212{b}
285Copy = s(a, _g282, Y_g288, _g292)
286Metas = [[Z_m212{b}|_g292], [X_m234{a}|_g282]]
287yes.
288
289
290
291",
292	see_also:[copy_term / 2, copy_term_vars / 3, variant / 2, term_variables / 2]]).
293
294:- comment(copy_term_vars / 3, [
295	summary:"NewTerm gets unified with a variant of OldTerm where all occurrences
296of variables in Vars are replaced by fresh variables.
297
298",
299	amode:(copy_term_vars(?,?,-) is det),
300	desc:html("   A copy of OldTerm is created, ie. a term that is similar to OldTerm but
301   all occurrences of the variables mentioned in Vars have been replaced
302   by new variables which do not occur elsewhere.
303
304<P>
305   Attributed variables are treated like normal variables, except that their
306   attributes are copied as specified by the corresponding copy_term handler.
307   This would usually imply that properties of the variable which can be
308   interpreted as unary constraints (such as its domain) are copied, while
309   attributes that link the variable to other variables or objects are ignored.
310
311<P>
312   Subterms that do not contain any of the variables to replace are
313   not physically copied.
314
315<P>
316   Note that when the structure of the term to be copied is known, then
317   it is more efficient to use specialised unification code to do the job.
318
319<P>
320"),
321	args:["Vars" : "Prolog term, usually a variable or a list of variables.", "OldTerm" : "Prolog term.", "NewTerm" : "Prolog term."],
322	eg:"   [eclipse]: Term=s(X,Y,Z), copy_term_vars(Y, Term, Copy).
323   X = _79
324   Z = _81
325   Y = _60
326   Term = s(_79, _60, _81)
327   Copy = s(_79, _120, _81)
328   yes.
329
330
331
332",
333	see_also:[copy_term / 2, copy_term / 3, variant / 2, functor / 3, term_variables / 2]]).
334
335:- comment(dim / 2, [
336	summary:"Creates a multi-dimensional array or or computes the dimensions of an existing one",
337	amode:(dim(+,-) is det),
338	amode:(dim(-,++) is det),
339	args:["Array" : "Variable or array.",
340	    "Dimensions" : "Variable or list of integers."],
341	desc:html("\
342    Creates an array of arbitrary dimensions, or determines the dimensions
343    of an existing one.  Multi-dimensional arrays are represented in the
344    form of nested structures.
345<P>
346    When creating an array of dimensions [D1,..,Dn], a nested structure
347    is created with the top-level term having the functor []/D1, its
348    arguments being structures with functor []/D2, and so on.
349    The functor [] is chosen to remind of arrays.
350<P>
351    Empty arrays: the atom [] represents the empty array of any dimension.
352    This means that dimensions like [0], [3,0] and [3,0,4] all lead to
353    the creation of the empty array [].
354<P>
355    When determining the dimensions of an existing array, this predicate
356    only considers the sub-arrays on index position 1.  It is therefore
357    not reliable for ragged arrays.
358<P>
359    To get the size of one-dimensional arrays, it is more efficient to
360    use arity/2.
361"),
362	exceptions:[
363	    4 : "Both Array and Dimensions are not sufficiently instantiated.",
364	    5 : "Array is not an array (term with functor []/N).",
365	    5 : "Dimensions is not a list of integers.",
366	    6 : "An integer in Dimensions is negative.",
367	    6 : "Dimensions is the empty list."
368	    ],
369	eg:"
370?- dim(M, [3,4]).
371M = []([](_131, _132, _133, _134),
372       [](_126, _127, _128, _129),
373       [](_121, _122, _123, _124))
374yes.
375
376?- dim(M, [3,4]), dim(M, L).
377M = []([](_131, _132, _133, _134),
378       [](_126, _127, _128, _129),
379       [](_121, _122, _123, _124))
380L = [3, 4]
381yes.
382
383?- dim(M, [0]).
384M = []
385yes.
386
387?- dim(A, []).
388out of range in dim(A, [])
389
390",
391	see_also:[arg / 3, arity/2, subscript / 3, array_flat/3, functor / 3]]).
392
393
394:- comment(array_flat / 3, [
395	summary:"Flattens (reduces the number of dimensions) of a multi-dimensional array",
396	amode:(array_flat(+,+,-) is det),
397	args:[
398	    "N" : "Integer",
399	    "Array" : "Array, i.e. structure with functor []/?",
400	    "Flat" : "Variable or array"],
401	desc:html("\
402   Constructs an array Flat with the same elements, but N fewer dimensions
403   than Array.  The most common use is to create a flat, one-dimensional
404   array from a multi-dimensional one.  Note that multi-dimensional arrays
405   are in fact nested one-dimensional arrays.
406<P>
407   N specifies how many levels are flattened:  a positive value N means
408   that a M-dimensional array will be reduced to a (M-N)-dimensional one,
409   e.g. a 2-D array gets reduced to a 1-D array.  When N is given as -1,
410   all array nesting is removed, and a 1-D array on the non-array elements
411   is produced.  In practice, it is however recommended to always use a
412   positive value for N, as this avoids ambiguities with respect to the
413   interpretation of subterm as nested array or array element.  With a
414   value of 0 the original array is returned unchanged.
415<P>
416   The elements in the Flat array are in the same order as they would be
417   encountered in a depth-first left-to-right traversal of Array.
418<P>
419   In the top N levels of Array, terms with functor []/M are interpreted
420   as arrays, in particular [] is interpreted as an empty array and thus
421   eliminated.
422"),
423	exceptions:[
424	    4 : "N or Array is a variable",
425	    5 : "N is not an integer",
426	    5 : "Array is not an array",
427	    6 : "N is less than -1",
428	    24 : "N is not an integer, but possibly an arithmetic expression"
429	],
430	eg:"
431?- array_flat(0, []([](a,b,c),[](d,e,f)), A).      % no change
432A = []([](a, b, c), [](d, e, f))
433
434?- array_flat(1, []([](a,b,c),[](d,e,f)), A).      % 2-D to 1-D
435A = [](a, b, c, d, e, f)
436
437?- array_flat(2, []([](a,b,c),[](d,e,f)), A).      % still 2-D to 1-D
438A = [](a, b, c, d, e, f)
439
440?- dim(M, [2,2,2]), array_flat(2, M, A).           % 3-D to 1-D
441M = []([]([](_368,_369), [](_365,_366)), []([](_359,_360), [](_356,_357)))
442A = [](_368, _369, _365, _366, _359, _360, _356, _357)
443
444?- dim(M, [2,2,2]), array_flat(1, M, A).           % 3-D to 2-D
445M = []([]([](_368,_369), [](_365,_366)), []([](_359,_360), [](_356,_357)))
446A = []([](_368,_369), [](_365,_366), [](_359,_360), [](_356,_357))
447
448% mixed-dimensional 3-D to 2-D
449?- array_flat(1, [](a, [](b), []([](c)), [], d), A).
450A = [](a, b, [](c) ,d).
451
452?- array_flat(1, []([],[]), A).                     % empty arrays
453A = []
454",
455	see_also:[dim/2, subscript/3, array_concat/3, is_array/1, array_list/2, arg/3]]).
456
457
458:- comment(array_list / 2, [
459	summary:"Conversion between array and list",
460	amode:(array_list(+,-) is det),
461	amode:(array_list(-,+) is det),
462	args:[
463	    "Array" : "Array, i.e. structure with functor []/?, or variable",
464	    "List" : "List, or variable"],
465	desc:html("\
466   Converts lists to arrays and vice versa.  The behaviour is identical to
467<PRE>
468    array_list(A, L) :- A =.. [[]|L].
469</PRE>
470   except for error handling.
471<P>
472   The elements in the Array and List are identical and in the same order.
473"),
474	exceptions:[
475	    4 : "Both Array and List are variables (non-coroutining mode only)",
476	    5 : "Array is not an array, or List is not a list"
477	],
478	eg:"
479?- array_list([](a,b,c,d,e,f), L).
480L = [a,b,c,d,e,f]
481
482?- array_list(A, [a,b,c,d,e,f]),
483A = [](a,b,c,d,e,f)
484
485?- array_list([], L).
486L = []
487
488?- array_list(A, []),
489A = []
490
491?- array_list([]([](a,b),[](c,d)), L).
492L = [ [](a,b), [](c,d) ]
493",
494	see_also:[dim/2, subscript/3, array_concat/3, is_array/1, array_flat/3, arg/3]]).
495
496
497:- comment(array_concat / 3, [
498	summary:"Concatenate two arrays into one",
499	amode:(array_concat(+,+,-) is det),
500	args:[
501	    "Front" : "Array, i.e. structure with functor []/M",
502	    "Back" : "Array, i.e. structure with functor []/N",
503	    "Concat" : "Variable or array with functor []/(M+N)"],
504	desc:html("\
505   Succeeds if Concat is the concatenation of arrays Front and Back.
506"),
507	exceptions:[
508	    4 : "Front or Back is a variable (non-coroutining mode only)",
509	    5 : "Front, Back or Concat are neither variables nor arrays"
510	],
511	eg:"
512?- array_concat([](a,b,c), [](d,e), L).
513L = [](a,b,c,d,e)
514
515?- array_concat([](a,b,c), [], L).
516L = [](a,b,c)
517
518?- array_concat([], [](d,e), L).
519L = [](d,e)
520
521?- array_concat([], [], L).
522L = []
523
524?- array_concat([]([](a,b),[](c)), [](d,[](e)), L).
525L = []([](a,b), [](c), d, [](e))
526
527",
528	see_also:[dim/2, subscript/3, array_list/2, is_array/1, array_flat/3, arg/3]]).
529
530
531:- comment(meta_attribute / 2, [
532	index:[
533	    "attribute declaration",
534	    "unify handler",
535	    "test_unify handler",
536	    "get_bounds handler",
537	    "set_bounds handler",
538	    "copy_term handler",
539	    "suspension handler",
540	    "print handler",
541	    "delayed_goals_number handler",
542	    "suspension_lists declaration"
543	    ],
544	summary:"Declares the variable attribute Name with the corresponding handlers",
545	amode:(meta_attribute(+,++) is det),
546	desc:html("
547   This predicate is used to declare a variable attribute and/or the
548   corresponding handlers.  The Name is usually the name of module where
549   this attribute is being defined and used.  The unqualified use of
550   attributed variables, i.e.  terms in the form Var{Attr} is allowed only in
551   modules which have a defined attribute name, otherwise the qualified
552   usage Var{Name:Attr} is required.
553<P>
554   The Handlers argument specifies a list of handler predicates for several
555   built-in operations which require user-defined actions whenever an
556   attributed variable is encountered.  The list contains elements in the
557   form Operation:Pred, where Operation is the predefined name of the
558   built-in operation and Pred is the handler predicate specification.  The
559   handler definition module is assumed to be the module in which
560   meta_attribute/2 is being called; another module can be specified by
561   using the tool body predicate meta_attribute_body/3.  When true/0 is
562   specified as the handler or when no handler for a particular operation
563   is specified, this operation will ignore this extension.  If the
564   extension Name already exists, the specified handlers are updated, the
565   non-specified ones remain.
566<P>
567   The call meta_attribute(Name, []) can be used as a preliminary
568   declaration of a particular attribute, e.g.  to compile a module part
569   before the actual declaration is called, or when processing separate
570   files that belong to a particular module.
571<P>
572   The meta_attribute/2 predicate is sensitive to the flag debug_compile.
573   If it is on, the calls to the local handlers will be traceable (and
574   slower), if it is off, it will be the opposite.  All specified handlers
575   will be exported from their definition module.
576<P>
577<H3>Handler Declarations</H3>
578   The predefined operations and the corresponding handler arguments are
579   the following:
580<DL>
581<DT>unify<DD>
582<P>
583    Operation :   unification
584<P>
585    Handler :   handler(+Term, ?Attribute)
586<P>
587    Description :   The handler for the usual unification.  Term is the
588        term that was unified with the attributed variable, it is
589	either a nonvariable or an attributed variable.  Attribute is
590	the contents of the attribute slot corresponding to the
591	extension.  Note that, at this point in execution, the orginal
592	attributed variable no longer exists, because it has already
593	been bound to Term.  The optional third argument is the
594	suspend-attribute of the former variable; it may be needed to
595	wake the variable's 'constrained' suspension list.
596<P>
597	The handler's job is to determine whether the binding is
598	allowed with respect to the attribute.  This could for example
599	involve checking whether the bound term is in a domain
600	described by the attribute.  For variable-variable bindings,
601	typically the remaining attribute must be updated to reflect
602	the intersection of the two individual attributes.  In case of
603	success, suspension lists inside the attributes may need to be
604	scheduled for waking.
605<P>
606        If an attributed variable is unified with a standard variable, the
607        variable is bound to the attributed variable and no handlers are
608        invoked.  If an attributed variable is unified with another
609        attributed variable or a non-variable, the attributed variable is
610        bound (like a standard variable) to the other term and all handlers
611        for the unify operation are invoked.  Note that several attributed
612        variable bindings can occur e.g. during a head unification and also
613        during a single unification of compound terms.  The handlers are
614        only invoked at certain trigger points (usually before the next
615        regular predicate call).  Woken goals will start executing once
616	all unify-handlers are done.
617
618<P>
619
620<DT>test_unify<DD>
621<P>
622    Operation :   unification test
623<P>
624    Handler :   handler(+Term, ?Attribute)
625<P>
626    Description :   The handler for a unifiability test which is not
627        supposed to trigger constraints propagation.  It is used e.g.
628	in the not_unify/2 predicate.  The handler arguments are
629	equivalent to those of the unification handler, Term is the
630	term that was unified with the attributed variable, Attribute
631	is the attribute of this extension.  The handler's job is to
632	determine whether Attribute allows unification with Term (not
633	considering effects of woken goals).  During the execution of
634	the handler the attributed variable may be bound to Term,
635	however when all local handlers succeed, all bindings are
636	undone, and no waking occurs.
637<P>
638
639<DT>compare_instances<DD>
640<P>
641    Operation :   instance and variant tests
642<P>
643    Handler :   handler(-Res, ?TermL, ?TermR)
644<P>
645    Description :   The handler for the variant/2, instance/2 and
646	compare_instances/3 instance-testing predicates.  The handler
647	arguments are similar to those of compare_instances/3. At least
648	one of TermL or TermR will be an attributed variable whenever
649	the handler is invoked.  The handler should bind Res to &lt; if
650	the attributes imply that TermL is a proper instance of TermR,
651	&gt; if TermR is a proper instance of TermL, and = if the two
652	attributed variables are variants of each other (e.g. they have
653	identical domains).  If the terms are incomparable (not unifiable),
654	the handler must fail.  If the attribute being declared has no
655	bearing on the instance-relationship, this handler should remain
656	undefined.
657<P>
658
659<DT>copy_term<DD>
660<P>
661    Operation :   copying an attributed variable
662<P>
663    Handler :   handler(?AttrVar, ?Var)
664<P>
665    Description :   The handler for the copy_term/2 predicate.  AttrVar is
666        the attributed variable encountered in the copied term, Var is
667        its corresponding variable in the copy.  All extension handlers
668        receive the same arguments.  This means that if the attributed
669        variable should be copied as an attributed variable, the
670        handler must check if Var is still a free variable or if it was
671        already bound to an attributed variable by a previous handler.
672<P>
673
674<DT>delayed_goals_number<DD>
675<P>
676    Operation :   querying number of suspended goals of a variable
677<P>
678    Handler :   handler(?AttrVar, -GoalsNumber)
679<P>
680    Description :  The handler for the delayed_goals_number/2
681	predicate.  AttrVar is the attributed variable encountered in
682	the predicate.  The handler is supposed to return the number
683	of all suspended goals in this attribute.
684<P>
685
686<DT>get_bounds<DD>
687<P>
688    Operation :   get information about numeric variable bounds
689<P>
690    Handler :   handler(?AttrVar, -Lwb, -Upb)
691<P>
692    Description :  The handler for the get_var_bounds/3 predicate. 
693	The handler should only be defined if the attribute contains
694	information about numeric bounds.  The handler is only invoked
695	if the variable has the corresponding (non-empty) attribute. 
696	The handler should bind Lwb and Upb to numbers (any numeric
697	type) reflecting the attribute's information about lower and
698	upper bound of the variable, respectively.  If different
699	attributes return different bounds information,
700	get_var_bounds/3 will return the intersection of the bounds, even
701        if this is empty (Lwb > Upb).
702<P>
703
704<DT>set_bounds<DD>
705<P>
706    Operation :   impose new bounds on an attributed variable
707<P>
708    Handler :   handler(?AttrVar, +Lwb, +Upb)
709<P>
710    Description :  The handler for the set_var_bounds/3 predicate. 
711	The handler should only be defined if the attribute can
712	incorporate information about numeric variable bounds.  The
713	handler is only invoked if the variable has the corresponding
714	(non-empty) attribute.  Lwb and Upb are the numbers that were
715	passed to set_var_bounds/3, and the handler is expected to
716	update its own bounds representation accordingly.
717<P>
718
719<DT>suspensions<DD>
720<P>
721    Operation :   querying suspensions attached to a variable
722<P>
723    Handler :   handler(?AttrVar, -ListOfSuspLists, -Tail)
724<P>
725    Description :  The handler for the suspensions/2 predicate. 
726	AttrVar is an attributed variable.  The handler should bind
727	ListOfSuspLists to a list containing all the attribute's
728	suspension lists and ending with Tail.
729<P>
730
731<DT>print<DD>
732<P>
733    Operation :   printing the attribute
734<P>
735    Handler :   handler(?AttrVar, -Attribute)
736<P>
737    Description : Printing the attribute in printf/2, 3 when the m option
738        is specified.  AttrVar is the attributed variable being printed,
739        Attribute is the term which will be printed as a value for this
740        attribute, qualified by the attribute name.  If no handler is
741        specified for an attribute, or the print handler fails, the
742        attribute will not be printed.  If there is only one attribute with
743        an associated print handler, the attribute value is not qualified
744        with the attribute name.
745</DL>
746The following handlers are still supported for compatibility,
747but their use is not recommended:
748<DL>
749<DT>delayed_goals<DD>
750<P>
751    Operation :   querying suspended goals of a variable (obsolete)
752<P>
753    Handler :   handler(?AttrVar, ?Goals, -GoalsTail)
754<P>
755    Description :   The handler for the delayed_goals/2 predicate.
756        AttrVar is the attributed variable encountered in the predicate.
757        The handler is supposed to create a difference list of all
758        goals in the suspended lists for this attribute. This handler
759	should not be used anymore, define a suspensions-handler instead.
760<P>
761<DT>pre_unify<DD>
762<P>
763    Operation :   pre-unification notification (compatibility only)
764<P>
765    Handler :   handler(?AttrVar, +Term)
766<P>
767    Description :  The handler is invoked before unification.  The
768	first argument is the attributed variable to be unified, the
769	second argument is the term it is going to be unified with. 
770	This handler is provided only for compatibility with SICStus
771	Prolog and its use is not recommended, because it is less
772	efficient than the <EM>unify</EM> handler and because its
773	semantics is somewhat unclear, there may be cases where
774	changes inside this handler may have unexpected effects.
775<P>
776</DL>
777<P>
778<H3>Suspension List Declaration</H3>
779The following entry is used to declare the valid suspension lists that
780the attribute defines:
781<DL>
782<DT>suspension_lists</DT><DD>
783<P>
784    Operation : declare suspension list names
785<P>
786    Handler :   list of name:indexlist
787<P>
788    Description :   This specifies which attribute slots (arguments in the
789        attribute structure) are suspension lists, and how they are called.
790	It is possible to declare aliases, i.e. several names for the same
791	suspension list, or a common name for more than one suspension list.
792	Note that in addition to this declaration, there must be an exported
793	struct-declaration with the same name as the attribute.  Using this,
794	the suspension_lists declarations can then be written as
795	susp_list_name:[(fieldname of attrname)]
796<P>
797</DD>
798</DL>
799"),
800	args:["Name" : "Atom", "Handlers" : "List or nil."],
801	exceptions:[4 : "The arguments are not ground.", 5 : "The first argument is not an atom or the second one is not a    list in the required format.", 6 : "The specified operation is not implemented or the handler    arity is wrong."],
802	eg:"
803% Sample source directives
804
805:- meta_attribute(myattr, []).
806
807:- meta_attribute(thing, [unify:unify_things/3, print_things/2]).
808
809:- export struct(dom(values,min,max)).
810:- meta_attribute(dom, [
811	unify:unify_doms/3,
812	print_doms/2,
813	suspension_lists:[
814		min:[(min of dom)],
815		max:[(max of dom)],
816		both:[(min of dom),(max of dom)]
817	    ]
818    ]).
819
820
821% Example session
822
823?- writeq(X{a}).
824undefined variable attribute in add_attribute(X, a, eclipse)
825syntax error : in source transformation
826| write(X{a}).
827|             ^ here
828
829?- meta_attribute(eclipse, []).
830yes.
831
832?- writeq(X{a}).
833X{suspend : _g386 , a}
834X = X
835yes.
836",
837    see_also:[not_unify/2, instance/2, variant/2, compare_instances/3,
838	copy_term/2, delayed_goals_number/2, delayed_goals/2,
839	set_var_bounds/3, get_var_bounds/3, printf/2, printf/3, suspensions/2,
840	add_attribute / 2]]).
841
842
843:- comment(meta_bind / 2, [
844	summary:"The attributed variable Meta is bound to the term Term without triggering the
845metaterm-unification event.
846
847",
848	amode:(meta_bind(-,?) is det),
849	desc:html("\
850   The attributed variable Meta is treated like a standard variable and bound to
851   Term.  The difference compared to using normal unification is that meta_bind/2
852   does not raise the meta-unification event, as is normally the case
853   whenever a attributed variable is bound.  An example of its use is in the handler
854   for the meta-unification event itself, e.g. when the attributed variable is to be
855   bound to a new one with a different attribute.
856
857<P>
858"),
859	args:["Meta" : "An attributed variable.", "Term" : "Prolog term."],
860	exceptions:[4 : "Meta is a free variable.", 5 : "Meta is instantiated."],
861	eg:"
862    [eclipse 2]: meta_bind(X{a}, 3).
863
864    X = 3
865    yes.
866
867    [eclipse 5]: [user].
868     change_attribute(X{_Old}, New) ?- meta_bind(X, _{New}).
869
870    yes.
871    [eclipse 6]: change_attribute(X{a}, b), printf(\"%Mw\", [X]).
872    X{b}
873
874Error:
875    meta_bind(_, a).                    (Error 4).
876    meta_bind(a, a).                    (Error 5).
877
878
879
880",
881	see_also:[meta / 1]]).
882
883:- comment(setarg / 3, [
884	summary:"Destructively replaces the Nth argument of the compound term Term with the
885term Arg.
886
887",
888	amode:(setarg(+,+,?) is det),
889	desc:html("   Destructively replaces the Nth argument of the compound term Term with
890   the term Arg.  The assignment is undone on backtracking.
891
892<P>
893   The use of this built-in is strongly discouraged, due to its non-logical
894   behaviour!  It is provided only to enable the implementation of certain
895   low-level operations that could otherwise not be provided with the same
896   efficiency.  Surprising side effects can occur when you don't know
897   exactly what you are doing.  In particular, it must be assured by the
898   programmer that the old argument value is not needed any longer and that
899   the old argument was not aliased to some other location.  The old value
900   should also not be a variable.
901
902<P>
903   If N is a list of integers and Term is a nested structure, then Arg
904   is the subterm of Term described by this list of integers.
905   E.g. setarg([2,1,3], Term, Arg) is the same as arg(2, Term, T1),
906   arg(1, T1, T2), setarg(3, T2, Arg).
907
908<P>
909"),
910	args:["N" : "Integer not greater than the arity of Term, or a list
911 of integers.", "Term" : "Compound term or external data handle.", "Arg" : "Prolog term."],
912	exceptions:[4 : "Either N or Term (or both) is not instantiated.", 5 : "N is instantiated, but not to an integer.", 5 : "Term is instantiated, but not to a compound term.", 6 : "N is an integer less than 1 or greater than the arity of    Term."],
913	eg:"
914Success:
915      [eclipse]: T = s(a, b, c), setarg(2, T, hello).
916      T = s(a, hello, c)
917      yes.
918      [eclipse]: T = s(a, b, c), ( setarg(2, T, hello) ; true ).
919      T = s(a, hello, c)     More? (;)
920      T = s(a, b, c)
921      yes.
922Unpredictable result:
923    [eclipse 10]: S=s(A), T=t(A), setarg(1, T, b).
924    S = s(A)  or  S = s(b)
925    A = b     or  A = A
926    T = t(b)
927
928
929
930",
931	see_also:[arg / 3, xset / 3]]).
932
933:- comment(term_to_bytes / 2, [
934	summary:"String is a ground encoding of Term, suitable for writing to a file,
935transmitting over a network etc.
936
937",
938	amode:(term_to_bytes(?,-) is det),
939	desc:html("   This predicate produces a string which contains an encoded representation
940   of the term Term. This representation is machine-independent, can be stored
941   in files, sent over networks etc. Note however that the string can contain
942   arbitrary bytes, including NUL and control characters.
943
944<P>
945   The predicate attempts to convert the term with all its attached
946   variable attributes and delayed goals. If this is not wanted,
947   you can strip those by first copying the term using copy_term/2 or
948   copy_term/3.
949
950<P>
951   The term_to_bytes/bytes_to_term predicates differ from term_string/2
952   in that they do not create a human-readable representation, but are
953   significantly faster and convert the term with all its attributes.
954
955<P>
956"),
957	args:["Term" : "Prolog term.", "String" : "A variable."],
958	exceptions:[5 : "String is neither variable nor string."],
959	eg:"
960[eclipse]: term_to_bytes(s(X),String), bytes_to_term(String, Term).
961String = \"\\000\\000\\000\\b\\001\\002\\013\\001\\001s\\000\\377\\006\\376\\006\\001X\\000\"
962Term = s(X)
963yes.
964
965
966
967",
968	see_also:[bytes_to_term / 2, copy_term / 2, copy_term / 3, writeq / 1, writeq / 2, write_canonical / 1, write_canonical / 2]]).
969
970:- comment(term_variables / 2, [
971	summary:"Succeeds if VarList is the list of all variables in Term.",
972	amode:(term_variables(?,-) is det),
973	desc:html("<P>
974   This predicate collects all the variables inside Term into the list
975   VarList.  Every variable occurs only once in VarList, even if it occurs
976   several times in Term.  The order of the variables in the list is not
977   specified.
978</P><P>
979   As usual, attributed variables are also considered variables.
980</P><P>
981   This predicate terminates even with cyclic terms.
982</P>
983"),
984	args:["Term" : "Prolog term.", "VarList" : "List or variable."],
985	exceptions:[5 : "VarList instantiated but not to a list."],
986	eg:"
987Success:
988    term_variables(atom, []).
989    term_variables(Term, Vs).       % gives Vs = [Term]
990    term_variables(f(a,B,c), Vs).   % gives Vs = [B]
991    term_variables([X,Y,Z], Vs).    % gives Vs = [Z,Y,X]
992    term_variables([X,Y,X], Vs).    % gives Vs = [Y,X]
993    term_variables(s(X{a}), Vs).    % gives Vs = [X{a}]
994
995Fail:
996    term_variables(f(a,B,c), []).
997",
998	see_also:[term_variables_array/2, nonground / 1, nonground / 2, nonground / 3, nonvar / 1, var / 1]]).
999
1000
1001:- comment(term_variables_array / 2, [
1002	summary:"Succeeds if VarArr is an array containing all variables in Term.",
1003	amode:(term_variables_array(?,-) is det),
1004	desc:html("<P>
1005   This predicate collects all the variables inside Term into an array
1006   VarArr.  Every variable occurs only once in VarArr, even if it occurs
1007   several times in Term.  The order of the variables in the array corresponds
1008   to the order in which they are first encountered during a left-to-right,
1009   depth-first traversal of Term.
1010</P><P>
1011   As usual, attributed variables are also considered variables.
1012</P><P>
1013   This predicate terminates even with cyclic terms.
1014</P>
1015"),
1016	args:["Term" : "Prolog term.", "VarArr" : "Array or variable."],
1017	eg:"
1018Success:
1019    term_variables_array(atom, []).
1020    term_variables_array(Term, Vz).       % gives Vz = [](Term)
1021    term_variables_array(f(a,B,c), Vz).   % gives Vz = [](B)
1022    term_variables_array([X,Y,Z], Vz).    % gives Vz = [](X,Y,Z)
1023    term_variables_array([X,Y,X], Vz).    % gives Vz = [](X,Y)
1024    term_variables_array(s(X{a}), Vz).    % gives Vz = [](X{a})
1025
1026Fail:
1027    term_variables_array(f(a,B,c), []).
1028",
1029	see_also:[term_variables/2, nonvar / 1, var / 1]]).
1030
1031:- comment(copy_term / 2, [
1032	summary:"A copy of OldTerm with new variables is created and unified with NewTerm.
1033
1034",
1035	amode:(copy_term(?,-) is det),
1036	desc:html("\
1037   A copy of OldTerm is created, ie.  a term that is similar to OldTerm but
1038   the free variables of OldTerm have been replaced by new variables which
1039   do not occur elsewhere.  In other words, the new term is a most general
1040   variant of the old one, in the sense of variant/2.
1041
1042<P>
1043   Attributed variables are treated like normal variables, except that their
1044   attributes are copied as specified by the corresponding copy_term handler.
1045   This would usually imply that properties of the variable which can be
1046   interpreted as unary constraints (such as its domain) are copied, while
1047   attributes that link the variable to other variables or objects are ignored.
1048
1049<P>
1050   If the term to be copied contains ground subterms (subterms without
1051   variables), then these subterms are shared between the original and
1052   the copy.  This optimization is only visible when using the nonlogical
1053   setarg/3 primitive on such a subterm - the safest way to enforce
1054   copying in such circumstances is to add a dummy variable argument.
1055
1056<P>
1057   Note that when the structure of the term to be copied is known, then
1058   it is more efficient to use specialised unification code or a combination
1059   of functor/3 and arg/3 to do the job.
1060
1061<P>
1062"),
1063	args:["OldTerm" : "Prolog term.", "NewTerm" : "Prolog term."],
1064	eg:"
1065   Success:
1066   copy_term(a, C).          (gives C=a).
1067   copy_term(s(X,a,Y,X), C). (gives C=s(_1, a, _2, _1)).
1068   copy_term([X,2|Y], C).    (gives C=[_1, 2| _2]).
1069   copy_term(X, C).
1070   copy_term(X, s(1,2,3)).
1071
1072   X::5..8, copy_term(f(X), C).	(gives C=f(_1{5..8})).
1073
1074   Fail:
1075   copy_term(s(X,X), s(3,4)).
1076",
1077	see_also:[copy_term_vars / 3, copy_term / 3, variant / 2, functor / 3, term_variables / 2]]).
1078
1079:- comment(functor / 3, [
1080	summary:"Succeeds if the compound term Term has functor Functor and arity Arity or
1081if Term and Functor are atomic and equal, and Arity is 0.
1082
1083",
1084	amode:(functor(+,-,-) is det),
1085	amode:(functor(-,+,+) is det),
1086	desc:html("   If Term is instantiated, its functor is unified with Functor and its
1087   arity with Arity.
1088
1089<P>
1090   If Term is not instantiated, it is bound to a term with functor Functor
1091   and arity Arity.
1092
1093<P>
1094   This predicate regards atomic terms (number, atom or string) as
1095   terms with arity 0 and functor equal to the term.
1096
1097<P>
1098   To query only the arity of a term, arity/2 can be used instead of functor/3.
1099"),
1100	args:["Term" : "Prolog term.", "Functor" : "Atomic term or variable.", "Arity" : "Positive integer or variable."],
1101	exceptions:[4 : "Term and either (or both) of Functor and Arity are    uninstantiated (non-coroutine mode only).", 5 : "Arity is neither a variable nor an integer.", 5 : "Functor is neither a variable nor an atomic term.", 6 : "Arity is a negative integer."],
1102	eg:"
1103   Success:
1104   functor(f(1,2),f,2).
1105   functor(f(1,2),F,A).  (gives F=f, A=2).
1106   functor(T,f,3).       (gives T=f(_g50, _g52, _g54)).
1107   functor(T,.,2).       (gives T=[_g48 | _g50]).
1108   functor([],F,A).      (gives F=[], A=0).
1109   functor(\"s\",F,A).     (gives F=\"s\", A=0).
1110   Fail:
1111   functor(f(1,2),f,3).
1112   functor(\"compound(g)\",compound,1).
1113   functor(f(1,2),\"f\",2).
1114   Error:
1115   functor(T,F,A).                    (Error 4).
1116   functor(\"f\",[f],X).                (Error 5).
1117   functor(X,[a],Y).                  (Error 5).
1118   functor(f(1,2),f,-1).              (Error 6).
1119
1120
1121
1122",
1123	see_also:[arity/2, (=..) / 2, arg / 3]]).
1124
1125:- comment(arity / 2, [
1126	summary:"Succeeds if Arity is the arity of Term.",
1127	amode:(arity(+,-) is det),
1128	desc:html("
1129    If Term is instantiated, its arity (number of arguments) is unified
1130    with Arity.  For compound terms, this is the number of arguments,
1131    for atomic terms it is 0.  As usual, non-empty lists are considered
1132    compound terms with arity 2.
1133<P>
1134    Note that (like all predicates that return a number as their last
1135    argument), this predicate can be used as a function inside arithmetic
1136    expressions, e.g.
1137<PRE>
1138	..., (I > arity(Term) -> writeln(error), fail ; arg(I, Term, Arg) ).
1139</PRE>
1140"),
1141	args:["Term" : "Prolog term.", "Arity" : "Variable or integer."],
1142	exceptions:[4 : "Term is uninstantiated (non-coroutine mode only)."],
1143	eg:"
1144Success:
1145   arity(f(1,2),2).
1146   arity(f(1,2),A).    (gives A=2).
1147   arity([],A).        (gives A=0).
1148   arity(\"s\",A).     (gives A=0).
1149   arity(33,A).        (gives A=0).
1150
1151Fail:
1152   arity(f(1,2),3).
1153   arity(\"compound(g)\",1).
1154
1155Error:
1156   arity(_,A).         (Error 4).
1157",
1158	see_also:[(=..) / 2, arg / 3, functor/3]]).
1159
1160:- comment((=..) / 2, [
1161	summary:"Univ --- Succeeds if List is the list which has Term's functor as its first
1162element and Term's arguments, if any, as its successive elements.
1163
1164",
1165	template:"?Term =..  ?List",
1166	amode:(=..(+,-) is det),
1167	amode:(=..(-,+) is det),
1168	desc:html("   If Term is atomic and/or List is a single-element list, unifies this
1169   element with Term.
1170
1171<P>
1172   Otherwise, either Term is instantiated to a compound term, or List is
1173   instantiated to a list, or both.  In which case, ``univ'' unifies Term
1174   with functor(Arg1, Arg2, ..., ArgN), and List with [Functor', Arg1',
1175   Arg2', .., argN'], where functor is unified with Functor', Arg1 is
1176   unified with Arg1', etc.  functor must be an atom, and it must be
1177   possible to determine the length of List from either Term or List.
1178
1179<P>
1180"),
1181	args:["Term" : "Prolog term.", "List" : "List or variable."],
1182	exceptions:[5 : "List is instantiated, but not to a list.", 4 : "functor is not specified within Term or List (non-coroutine    mode only).", 4 : "The length of List cannot be determined (non-coroutine mode    only)."],
1183	eg:"
1184   Success:
1185   Term =.. [likes,david,play]. (gives Term = likes(david,play)).
1186   s([1,4,5,6]) =.. List.       (gives List = [s,[1,4,5,6]]).
1187   zero_arity =.. List.         (gives List = [zero_arity]).
1188   1234 =.. List.               (gives List = [1234]).
1189   \"string\" =.. List.           (gives List = [\"string\"]).
1190   2.9 =.. List.                (gives List = [2.9]).
1191   f(1,X,3) =.. [Y,Z,2,W].      (gives X=2; Y=f; Z=1; W=3).
1192   f(1,X,3) =.. [A,B,C,D].      (gives A=f; B=1; C=2; D=3).
1193   f(A) =.. List.               (gives A=_g74; List=[f,_g74]).
1194   Term =.. [f,A].              (gives Term=f(_g76); A=_g76).
1195   f(1,2,3) =.. [f | A].        (gives A=[1,2,3]).
1196   a =.. [X].                   (gives X=a)
1197Fail:
1198  likes(man,play) =.. [likes,man,work].
1199
1200Error:
1201  Term =.. List.        (Error 4).
1202  Term =.. [Var,1,2,3]. (Error 4). % functor of Term is
1203                                   %   not specified.
1204  Term =.. [f | A].     (Error 4). % arity of Term is
1205                                   %   not specified.
1206  Term =.. [f,a,b | X]. (Error 4).
1207  Term =.. my_atom.     (Error 5).
1208  Term =.. [1,2,3].     (Error 5).
1209  Term =.. [a|b].       (Error 5).
1210  Term =.. [f,a,b | c]. (Error 5).
1211
1212
1213
1214",
1215	see_also:[arg / 3, arity/2, functor / 3]]).
1216
1217:- comment(arg / 3, [
1218	summary:"Succeeds if Arg is the Nth argument of the compound term Term.
1219
1220",
1221	amode:(arg(+,+,-) is det),
1222	desc:html("   If Term is a structure, unifies Arg with the Nth argument of a structure
1223   Term.
1224
1225<P>
1226   If Term is a list (N must be either the integer 1 (for the head) or 2
1227   (for the tail), unifies Arg with the head or tail of the list.  This is
1228   a consequence of the fact that ./2 is the list functor and
1229   .(a,.(b,.(c,[]))) is the same as [a,b,c].
1230
1231<P>
1232   If N is a list of integers and Term is a nested structure, then Arg
1233   is the subterm of Term described by this list of integers.
1234   E.g. arg([2,1,3], Term, Arg) is the same as arg(2, Term, T1),
1235   arg(1, T1, T2), arg(3, T2, Arg).
1236
1237<P>
1238"),
1239	args:["N" : "Integer not greater than the arity of Term, or a list.", "Term" : "Compound term.", "Arg" : "Prolog term."],
1240	exceptions:[4 : "Either N or Term (or both) is not instantiated    (non-coroutine mode only).", 5 : "N is instantiated, but not to an integer or list of integers.", 5 : "Term is instantiated, but not to a compound term.", 6 : "N is an integer less than 1 or greater than the arity of    Term."],
1241	eg:"
1242Success:
1243      arg(2,foo(boo,moo),moo).
1244      arg(2,.(a,b,c),b).
1245      arg(2,.(a,b),b).
1246      arg(2,term1(term2(a,b),c),c).
1247      arg(2,f(a,f(a,b)),f(X,Y)).        (gives X=a; Y=b).
1248      arg(2,[a,b,c],[b,c]).
1249      arg(2,.(a,.(b,.(c,[]))),[b,c]).
1250      arg(2,[1],[]).
1251      arg([2,1], f(a,g(b,c)), X).       (gives X=b).
1252Fail:
1253      arg(2,f(a,f(a,b)),f(X,X)).
1254Error:
1255      arg(N,f(1,2),1).         (Error 4).
1256      arg(N,[],X),             (Error 5).
1257      arg(0,foo(boo,moo),moo). (Error 6).
1258      arg(3,foo(boo,moo),moo). (Error 6).
1259
1260
1261",
1262	see_also:[arity/2, functor / 3, (=..) / 2, subscript / 3]]).
1263
1264:- comment(term_string / 2, [
1265	summary:"Conversion between a Prolog term and a string.
1266
1267",
1268	amode:(term_string(?,-) is det),
1269	amode:(term_string(-,+) is det),
1270	desc:html("
1271   If String is instantiated, its contents are parsed, and if the whole
1272   string can be parsed as one Prolog term it is unified with Term.  If
1273   String is not instantiated, Term is written into a string (using
1274   writeq/2) and String is bound to it.
1275<P>
1276   To customize the way the term is converted into a string, e.g. to include
1277   attributed variable print handlers, use term_string/3 with appropriate
1278   Options, or use sprintf/3.
1279"),
1280	args:["Term" : "Prolog term.", "String" : "String or a variable."],
1281	exceptions:[5 : "String is instantiated, but not to a string.", 7 : "String cannot be converted to a Prolog term."],
1282	eg:"
1283Success:
1284      term_string(T, \"look\").      (gives T=look).
1285      term_string(T, \"26.0\").      (gives T=26.0).
1286      term_string(T, \"f(1,2).\").   (gives T=f(1,2)).
1287      term_string(T, \"f(1,2)\").    (gives T=f(1,2)).
1288      term_string(f(1,2),L).       (gives L=\"f(1, 2)\").
1289      term_string(f(1,2),\"f(1, 2)\").
1290      term_string(atom,S).         (gives S=\"atom\").
1291      term_string(.(a,.(1,[])),S). (gives S=\"[a, 1]\").
1292      term_string(2.60,\"2.6\").
1293      term_string(2.6,\"2.60\").
1294      term_string(T,S).            (gives T=_g94; S=\"_g94\").
1295
1296Fail: term_string(2.6,\"2.5\").
1297
1298Error:
1299      term_string(T,atom).              (Error 5).
1300      [eclipse]: term_string(T,\"F(1,2)\").  % String not a string
1301      F(1,2)                               % of a prolog term
1302       ^ (here?)
1303      syntax error: unexpected token
1304      string contains unexpected characters in term_string(T, \"F(1,2)\")
1305",
1306	see_also:[term_string/3, number_string/2, read/2, writeq/2, sprintf/3]]).
1307
1308:- comment(term_string / 3, [
1309	summary:"Configurable conversion between a Prolog term and a string.",
1310	amode:(term_string(?,-,+) is det),
1311	amode:(term_string(-,+,+) is det),
1312	desc:html("
1313   If String is instantiated, its contents are parsed (using read_term/3
1314   and the given Options).
1315<P>
1316   If String is not instantiated, Term is written into a string (using
1317   write_term/3 with options corresponding to writeq/2, followed and
1318   possibly overridden by the given Options).
1319<P>
1320   Inapplicable options are silently ignored.
1321<P>
1322</PRE>
1323"),
1324	args:["Term" : "Prolog term.",
1325	    "String" : "String or a variable.",
1326	    "Options" : "List of read or write options"],
1327	exceptions:[
1328	    4 : "Options is insufficiently instantiated.",
1329	    5 : "String is instantiated, but not to a string.",
1330	    5 : "Options is not a list or does not only contain compound terms.",
1331	    6 : "Options is a list containing compound terms that are not valid options.",
1332	    7 : "String cannot be converted to a Prolog term."],
1333	eg:"
1334    ?- term_string([1,a], S, [dotlists(true)])
1335    S = \".(1,.(a,[]))\"
1336
1337    ?- term_string(['A',3+4], S, [quoted(false),operators(false)])
1338    S = \"['A',+(3,4)]\"
1339
1340    ?- term_string(T, \"[1,Y,_]\", [variable_names(V)]).
1341    T = [1, Y, _208]
1342    V = ['Y' = Y]
1343
1344",
1345    see_also:[term_string/2, number_string/2, read_term/3, write_term/3, sprintf/3]]).
1346
1347
1348:- comment(subscript / 3, [
1349	summary:"Accesses the subterm Elem of Term, as specified by Subscript",
1350	amode:(subscript(+,++,-) is det),
1351	desc:html("   If term is a compound term, e.g. a vector represented as a structure,
1352   or a matrix represented as a structure of structures and so on, then
1353   subscript/3 provides access to the term's components.
1354   Subscript is a list of (sub)structure argument indices describing
1355   which element to access.
1356<P>
1357   The indices can be either an integer expression or a range in the form 
1358   Lower..Upper where Lower and Upper are integer expressions. The
1359   expressions are evaluated and the corresponding components (or the
1360   components in the range specified) accessed.
1361<P>
1362   If Term is a string, Subscript must be a list of the form [Index], and
1363   Elem is obtained via string_code(Index, Term, Elem).
1364<P>
1365   If Term is an external data handle, Subscript must be a list of the form
1366   [Index], and Elem is obtained via xget(Term, Index, Elem).
1367<P>
1368   The main use for this predicate is to provide array syntax in arithmetic
1369   expressions. Consider the arithmetic expression
1370<PRE>
1371    X is Mat[I,J] + 1
1372</PRE>
1373    which the ECLiPSe parser parses as
1374<PRE>
1375    X is subscript(Mat,[I,J]) + 1
1376</PRE>
1377    and the arithmetic evaluation mechanism turns that into
1378<PRE>
1379    subscript(Mat,[I,J],T), +(T,1,X)
1380</PRE>
1381    If Subscript contains a range of the form From..To, then
1382    this results in the retrieval of a list of elements with
1383    the indices from From to To.
1384<P>
1385   NOTE: subscript/3 implements a superset of the functionality of arg/3.
1386   So arg/3 is likely to be faster than subscript/3 in cases where they
1387   implement the same functionality, i.e. structure argument lookup or
1388   one/multi-dimensional array element lookup.
1389<P>
1390"),
1391	args:["Term" : "Compound term (possibly nested), string, or external data handle.", 
1392              "Subscript" : "A list of integers, ranges or integer arithmetic expressions.", "Elem" : "Prolog term."],
1393	exceptions:[4 : "Term or Subscript are not sufficiently instantiated.", 5 : "Term not compound or Subscript not integer list.", 6 : "Subscript out of range."],
1394	eg:"
1395    [eclipse 6]: subscript(s(t(a,b),t(c,d),t(e,f)), [3,2], X).
1396    X = f
1397    yes.
1398
1399    [eclipse 11]: Vector = v(12,13,14,15), X is Vector[3].
1400    X = 14
1401    Vector = v(12, 13, 14, 15)
1402    yes.
1403
1404    [eclipse 12]: Matrix = m(r(1,2,3),r(4,5,6),r(7,8,9)), X is Matrix[2,1].
1405    X = 4
1406    Matrix = m(r(1, 2, 3), r(4, 5, 6), r(7, 8, 9))
1407    yes.
1408
1409    [eclipse 18]: Matrix = m(r(1,2,3),r(4,5,6),r(7,8,9)), Row is Matrix[2].
1410    Row = r(4, 5, 6)
1411    Matrix = m(r(1, 2, 3), r(4, 5, 6), r(7, 8, 9))
1412    yes.
1413
1414    [eclipse 5]: Matrix = m(r(1,2,3),r(4,5,6),r(7,8,9)), 
1415                 subscript(Matrix, [2,1..3], Row),
1416                 subscript(Matrix, [1..3,2], Col),
1417                 subscript(Matrix, [2..3,1..2], Sub).
1418    Matrix = m(r(1, 2, 3), r(4, 5, 6), r(7, 8, 9))
1419    Row = [4, 5, 6]
1420    Col = [2, 5, 8]
1421    Sub = [[4, 5], [7, 8]]
1422    yes.
1423
1424
1425
1426",
1427	see_also:[arg / 3, dim / 2, string_code/3, xget / 3, array_flat/3]]).
1428
1429
1430:- comment(get_var_bounds / 3, [
1431	summary:"Retrieve bounds of a numeric variable in a generic way",
1432	amode:(get_var_bounds(?,-,-) is det),
1433	desc:html("\
1434    This predicate is intended to be used on attributed variables that
1435    have a numeric domain.  The bound information is collected from the
1436    variable's attributes via their get_bounds-handlers. If several
1437    attributes contain bound information, the results are intersected
1438    to produce the tightest bound information available. An empty bound
1439    (Lower > Upper) can be returned.
1440<P>
1441    The bounds are always returned as floating point numbers, regardless
1442    of any integrality constraint on the variable.
1443"),
1444	args:["Var" : "Variable or number.",
1445	    "Lower" : "Float or variable.",
1446	    "Upper" : "Float or variable."],
1447	exceptions:[5 : "Var is not a variable or number"],
1448%	fail_if:"Fails if the bounds from several attributes have an empty intersection",
1449	eg:"
1450    [eclipse 1]: lib(fd), lib(ic).
1451    yes.
1452
1453    [eclipse 2]: ic:(X::3.0..9.0), fd:(X::1..7), get_var_bounds(X,L,U).
1454    X = X{ic : 3.0..9.0, fd:[1..7]}
1455    L = 3.0
1456    U = 7.0
1457    Yes (0.00s cpu)
1458
1459    [eclipse 3]: get_var_bounds(X,L,U).
1460    X = X
1461    L = -1.0Inf
1462    U = 1.0Inf
1463    yes.
1464
1465    [eclipse 4]: get_var_bounds(5,L,U).
1466    L = 5.0
1467    U = 5.0
1468    yes.
1469
1470    [eclipse 5]: get_var_bounds(a,L,U).
1471    type error in get_var_bounds(a, L, U)
1472",
1473	see_also:[set_var_bounds / 3, "get_bounds handler"]]).
1474
1475
1476:- comment(set_var_bounds / 3, [
1477	summary:"Impose bounds on a numeric variable in a generic way",
1478	amode:(set_var_bounds(?,+,+) is semidet),
1479	desc:html("\
1480    This predicate is intended to be used on attributed variables that
1481    have a numeric domain.  The bound information is distributed to the
1482    variable's attributes via their set_bounds-handlers.  Only existing
1483    attributes are involved, no new attributes are created!
1484<P>
1485    The bounds can be given as any numeric type, the set_bounds handlers
1486    are expected to interpret them appropriately.
1487"),
1488	args:["Var" : "Variable or number.",
1489	    "Lower" : "A number.",
1490	    "Upper" : "A number."],
1491	fail_if:"Fails if imposing the bounds results in an empty domain",
1492	exceptions:[5 : "Var is not a variable or number"],
1493	eg:"
1494    [eclipse 1]: lib(fd), lib(ic).
1495    yes.
1496
1497    % update both attributes:
1498    [eclipse 2]: ic:(X::3.0..9.0), fd:(X::1..7), set_var_bounds(X, 5, 6.5).
1499    X = X{ic : 5.0..6.5, fd:[5, 6]}
1500    yes.
1501
1502    % no attribute - no effect:
1503    [eclipse 13]: set_var_bounds(X, 5, 6.5).
1504    X = X
1505    yes.
1506
1507    [eclipse 15]: set_var_bounds(0, 5, 6.5).
1508    no (more) solution.
1509
1510    [eclipse 14]: set_var_bounds(a, 3,7).
1511    type error in set_var_bounds(a, 3, 7)
1512",
1513	see_also:[get_var_bounds / 3, "set_bounds handler"]]).
1514
1515
1516:- comment(update_struct/4, [
1517    summary:"NewStruct is the same as OldStruct except that the fields in FieldList have been replaced",
1518    amode:(update_struct(+,+,+,-) is det),
1519    amode:(update_struct(+,+,-,+) is det),
1520    args:["StructName":"An atom (the structure name)",
1521	"FieldList":"A list of name:Value structures, or one such structure",
1522	"OldStruct":"Structure or variable",
1523	"NewStruct":"Variable or structure"],
1524    desc:html("\
1525	This predicate is only useful together with structure declarations.
1526	Its purpose is to allow updating a structure's fields (by creating
1527	a new, updated structure) without having to know all the fields of
1528	the structure, or its arity.
1529<P>
1530	update_struct/4 creates a new structure NewStruct which is identical
1531	to another structure OldStruct, except that the fields listed
1532	in FieldList contain the values in FieldList, while all fields not
1533	mentioned in FieldList retain the same values in OldStruct and
1534	NewStruct.
1535<P>
1536	update_struct/4 is usually expanded at compile time into two
1537	simple, efficient unifications (see example).
1538"),
1539    exceptions:[4:"StructName or FieldList is a variable",
1540	4:"A member of FieldList (or its tail) is insufficiently instantiated",
1541	5:"StructName is not an atom, or FieldList is not a proper list",
1542	5:"An Element of FieldList is not an atom:term structure",
1543	6:"StructName is not the name of a declared, visible structure",
1544	6:"A field name in FieldList is not a field of the structure denoted by StructName"
1545    ],
1546    eg:"
1547    ?- local struct(person(name,address,age,salary)).
1548    yes.
1549
1550    ?- Old = person{name:john,salary:4000,address:here,age:30},
1551       update_struct(person, [salary:5000,address:there], Old, New).
1552
1553    Old = person(john, here, 30, 4000)
1554    New = person(john, there, 30, 5000)
1555    yes.
1556
1557    ?- update_struct(person, [salary:5000], Old, New).
1558
1559    Old = person(_244, _245, _246, _247)
1560    New = person(_244, _245, _246, 5000)
1561    yes.
1562
1563
1564    % Compilation: The code
1565
1566    set_salary(Old, New, NewSalary) :-
1567    	update_struct(person, [salary:NewSalary], Old, New).
1568
1569    % is compiled into
1570
1571    set_salary(Old, New, NewSalary) :-
1572	Old = person(X1, X2, X3, _),
1573	New = person(X1, X2, X3, NewSalary).
1574",
1575    see_also:[struct/1,(=)/2]]).
1576
1577