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 I/O").
24:- comment(summary, "Built-ins for input/output of complex terms").
25:- comment(categories, ["Built-In Predicates"]).
26
27:- tool(expand_macros / 2).
28:- tool(portray_term / 3).
29:- tool(print / 1).
30:- tool(print / 2).
31:- tool(printf / 2).
32:- tool(printf / 3).
33:- tool(read / 1).
34:- tool(read / 2).
35:- tool(read_annotated / 2).
36:- tool(read_annotated / 3).
37:- tool(read_term / 2).
38:- tool(read_term / 3).
39:- tool(readvar / 3).
40:- tool(sprintf / 3).
41:- tool(write / 1).
42:- tool(write / 2).
43:- tool(write_canonical / 1).
44:- tool(write_canonical / 2).
45:- tool(write_term / 2).
46:- tool(write_term / 3).
47:- tool(writeclause / 1).
48:- tool(writeclause / 2).
49:- tool(writeln / 1).
50:- tool(writeln / 2).
51:- tool(writeq / 1).
52:- tool(writeq / 2).
53
54:- comment(expand_macros / 2, [
55        summary:"Apply macro transformations to Term",
56        amode:(expand_macros(?,-) is det),
57        desc:html("\
58    Applies macro-transformations to Term, if any are visible in the
59    caller module. If no transformation is visible, TransTerm is identical
60    to Term.
61    <P>
62    Normally, macro expansion is performed implicitly by the parser, i.e.
63    when using either the compiler or term-input builtins like read/1,2,
64    read_term/2,3 or readvar/2,3.
65    <P>
66    For certain meta-programming applications, where one needs to work with
67    the original unexpanded form of the input, this is undesirable.
68    In such cases, macro-expansion can be switched off during reading
69    and later performed explicitly using expand_macros/2.
70    <P>
71    For reading input without macro expansion, set the stream-flag
72    macro_expansion to off before reading (see set_stream_property/3
73    or open/4), or use the facilities of the library(source_processor).
74"),
75        args:["Term" : "A term.",
76                "TransTerm" : "A variable."],
77        eg:"
78    % Given the program:
79
80        t(water, wine).
81        :- local macro(water, t/2, []).
82
83
84    % Implicit macro expansion by read/1:
85    ?- open(string(\"water\"),read,S),
86        read(S,X),
87        close(S).
88    X = wine
89    yes.
90
91    % Implicit macro expansion switched off:
92    ?- open(string(\"water\"),read,S,[macro_expansion(off)]),
93        read(S,X),
94        close(S).
95    X = water
96    yes.
97
98    % Explicit macro expansion:
99    ?- open(string(\"water\"),read,S,[macro_expansion(off)]),
100        read(S,X),
101        expand_macros(X,Y),
102        close(S).
103    X = water
104    Y = wine
105    yes.
106
107    % All occurrences are expanded:
108    ?- open(string(\"[water,beer,fizzy(water)]\"),read,S,[macro_expansion(off)]),
109        read(S,X),
110        expand_macros(X,Y),
111        close(S).
112    X = [water, beer, fizzy(water)]
113    Y = [wine, beer, fizzy(wine)]
114    yes.
115",
116        see_also:[macro/3, expand_clause/2, expand_goal/2,
117                open/4, set_stream_property/3, library(source_processor),
118                portray/3, portray_term/3]]).
119
120
121:- comment(portray_term / 3, [
122        summary:"Apply portray (write) transformations to Term",
123        amode:(portray_term(?,-,+) is det),
124        desc:html("\
125    Applies portray-transformations to Term, if any are visible in the
126    caller module. If no transformation is visible, TransTerm is identical
127    to Term.
128    <P>
129    This predicate is intended mainly for testing purposes, because
130    portray-transformations are normally performed implicitly by the
131    term output predicates write/1,2, writeln/1,2, print/1,2,
132    display/1,2, printf/2,3 or write_term/2,3.  
133"),
134        args:["Term" : "A term.",
135                "TransTerm" : "A variable.",
136                "As" : "One of the atoms 'term', 'goal' or 'clause'"],
137        eg:"
138    % Given the program:
139
140        :- local portray(s/1, tr_s/2, []).
141        tr_s(0, 0).
142        tr_s(s(S), N) :- tr_s(S, N1), N is N1+1.
143
144
145    % Implicit portray transformation by write/1:
146    ?- S = s(s(s(0))), write(S).
147    3
148    yes.
149
150    % Explicit portray transformation
151    % Note: no transformation done by writeq/1
152    ?- S = s(s(s(0))), writeq(S), portray_term(S, P, term), writeq(P).
153    s(s(s(0)))
154    3
155    yes.
156",
157        see_also:[portray/3, expand_clause/2, expand_goal/2, expand_macros/2]]).
158
159
160:- comment(read_exdr / 2, [
161        summary:"A term in EXDR-format is read from the input stream Stream and
162converted to the corresponding ECLiPSe term Term.
163
164",
165        amode:(read_exdr(+,-) is semidet),
166        desc:html("    The predicates write_exdr/2 and read_exdr/2 can be used for letting
167    ECLiPSe programs exchange data with the host language in an embedded
168    environment (e.g.  Java, Tcl).  More generally, they allow exchanging
169    data with agents written in programming languages that define a
170    mapping from EXDR format to the language's data structures.
171<P>
172    EXDR defines the abstract data types Integer, Long, Double, String,
173    List, Nil, Struct and Anonymous Variable. Their mapping to ECLiPSe
174    data types is as follows:
175<PRE>
176        EXDR type       ECLiPSe type        e.g.
177        ----------------------------------------------
178        Integer         integer             123
179        Long            integer             10000000000
180        Double          float               12.3
181        String          string              \"abc\"
182        List            ./2                 [a,b,c]
183        Nil             []/0                []
184        Struct          compound or atom    foo(bar,3)
185        Anon.Variable   var                 _
186</PRE>
187    Not all ECLiPSe terms have an EXDR representation, e.g. integers longer
188    than 64 bits, rationals, suspensions or attributed variables.
189<P>
190    More information about EXDR format, including the specification of the
191    serialised encoding, can be found in the Embedding and Interfacing Manual.
192"),
193        args:[
194            "Stream" : "Stream handle or alias (atom)",
195            "Term" : "A variable."],
196        fail_if:"Fails when reaching end of file",
197        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 7 : "EXDR term corrupted.", 190 : "End of file (default handler fails)", 192 : "Stream is not an input stream.", 193 : "Stream is an illegal stream specification.", 264 : "Not EXDR format.", 265 : "Unknown EXDR format version."],
198        eg:"
199Success:
200    ?- open(queue(\"\"),update,q),
201                 write_exdr(q, foo(12.3,123,[\"hello\",_])),
202                 read_exdr(q, Term),
203                 close(q).
204
205    Term = foo(12.3, 123, [\"hello\", _131])
206    yes.
207
208Error:
209    read_exdr(S, a(b,c)).    (Error 4).
210    read_exdr(output, X).    (Error 192).
211    read_exdr(atom, X).      (Error 193).
212
213
214
215",
216        see_also:[write_exdr / 2, read / 1, read / 2]]).
217
218:- comment(write_canonical / 1, [
219        summary:"The term Term is written on the stream output in a form that ignores
220operator declarations and can be read in.
221
222",
223        amode:(write_canonical(?) is det),
224        desc:html("   Used to write the term Term in a form that can be read back independent
225   of the current operator declarations.  Atoms and strings are quoted,
226   operator declarations are ignored, lists are printed as ./2 structures,
227   the (stream-specific or global) print_depth flag is not taken into account,
228   variable attributes are printed, and variables are printed with unique
229   identifiers.
230
231<P>
232   write_canonical(Term) is equivalent to printf(\"%DMOQv.w\", Term)
233   or write_term(Term, [attributes(full),operators(false),quoted(true),
234           dotlists(true),variables(raw),depth(full),transform(false)]).
235
236<P>
237   Note that as usual, the output is buffered, so it may need to be flushed
238   either by closing the output stream, by writing again or by using
239   flush/1.
240
241<P>
242"),
243        args:["Term" : "Prolog term."],
244        eg:"
245   Equivalent to write_canonical(output, Term).
246   (see write_canonical/2 for details).
247
248
249
250",
251        see_also:[write / 1, write / 2, writeq / 1, writeq / 2, write_canonical / 2]]).
252
253:- comment(write_canonical / 2, [
254        summary:"The term Term is written on the output stream Stream in a form that ignores
255operator declarations and can be read in.
256
257",
258        amode:(write_canonical(+,?) is det),
259        desc:html("   Used to write the term Term in a form that can be read back independent
260   of the current operator declarations.  Atoms and strings are quoted,
261   operator declarations are ignored, lists are printed as ./2 structures,
262   the (stream-specific or global) print_depth flag is not taken into account,
263   variable attributes are printed, and variables are printed with unique
264   identifiers.
265
266<P>
267   write_canonical(S,Term) is equivalent to printf(S,\"%DMOQv.w\", Term)
268   or write_term(S,Term, [attributes(full),operators(false),quoted(true),
269           dotlists(true),variables(raw),depth(full),transform(false)]).
270
271<P>
272   Note that as usual, the output is buffered, so it may need to be flushed
273   either by closing the stream, by writing again or by using flush/1.
274
275<P>
276"),
277        args:[
278            "Stream" : "Stream handle or alias (atom)",
279            "Term" : "Prolog term."],
280        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output stream.", 193 : "Stream is an illegal stream specification."],
281        eg:"
282   Success:
283    ?- write_canonical(output, 'A'+[a,B]).
284    +('A', .(a, .(_216, [])))
285    B = B
286    yes.
287
288Error:
289    write_canonical(S, a(b,c)).        (Error 4).
290    write_canonical(\"string\", a(b,c)). (Error 5).
291    write_canonical(input, X + 2).     (Error 192).
292    write_canonical(atom, X + 2).      (Error 193).
293
294
295
296",
297        see_also:[write / 1, write / 2, writeq / 1, writeq / 2, write_canonical / 1]]).
298
299:- comment(write_exdr / 2, [
300        summary:"The term Term is written onto the output stream Stream in EXDR-format
301(a format for communication with agents in other programming languages).
302
303",
304        amode:(write_exdr(+,?) is semidet),
305        desc:html("    The predicates write_exdr/2 and read_exdr/2 can be used for letting
306    ECLiPSe programs exchange data with the host language in an embedded
307    environment (e.g.  Java, Tcl).  More generally, they allow exchanging
308    data with agents written in programming languages that define a
309    mapping from EXDR format to the language's data structures.
310
311<P>
312    EXDR defines the abstract data types Integer, Long, Double, String,
313    List, Nil, Struct and Anonymous Variable. Their mapping to ECLiPSe
314    data types is as follows:
315
316<P>
317<PRE>
318        EXDR type       ECLiPSe type        e.g.
319        ----------------------------------------------
320        Integer         integer             123
321        Long            integer             10000000000
322        Double          float               12.3
323        String          string              \"abc\"
324        List            ./2                 [a,b,c]
325        Nil             []/0                []
326        Struct          compound or atom    foo(bar,3)
327        Anon.Variable   var                 _
328</PRE>
329    The type of the generated EXDR-term is the type resulting from the
330    \"natural\" mapping of the Eclipse terms.  Atoms are written as
331    structures of arity 0 (not as strings).
332<P>
333    Not all ECLiPSe terms have an EXDR representation, e.g. integers longer
334    than 64 bits, rationals, suspensions or improper lists.  The predicate
335    fails in this case, nevertheless writing a complete but simplified term
336    to the stream.  All information about variable sharing and variable
337    attributes in the ECLiPSe term is silently lost (no failure).
338<P>
339    Note that as with all output predicates, the output may be buffered,
340    so it may be necessary to flush either by closing the stream or by
341    using flush/1.
342<P>
343    If the output Stream has the compress-flag set, write_exdr/2 will use a
344    more compact variant of EXDR encoding, at the expense of encoding speed.
345<P>
346    More information about EXDR format, including the specification of the
347    serialised encoding, can be found in the Embedding and Interfacing Manual.
348"),
349        args:[
350            "Stream" : "Stream handle or alias (atom)",
351            "Term" : "Prolog term."],
352        fail_if:"Fails if the Term cannot be represented in EXDR format",
353        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output stream.", 193 : "Stream is an illegal stream specification."],
354        eg:"
355Success:
356    ?- open(queue(\"\"),update,q),
357                 write_exdr(q, foo(12.3,123,[\"hello\",_])),
358                 read_exdr(q, Term),
359                 close(q).
360
361    Term = foo(12.3, 123, [\"hello\", _131])
362    yes.
363
364Failure:
365    write_exdr(q, 617236126172).
366    write_exdr(q, 3_4).
367
368Error:
369    write_exdr(S, a(b,c)).        (Error 4).
370    write_exdr(input, X + 2).     (Error 192).
371    write_exdr(atom, X + 2).      (Error 193).
372
373
374
375",
376        see_also:[read_exdr / 2, flush / 1, set_stream_property/3, open/4]]).
377
378:- comment(display / 1, [
379        summary:"Term is displayed on the current output --- without considering operator
380definitions.
381
382",
383        amode:(display(?) is det),
384        desc:html("   Used to display an expression in standard parenthesised prefix notation,
385   onto the current output. This is mainly useful for debugging,
386   in order to see how a term has been parsed.
387<P>
388   display(Term) is equivalent to write_term(Term, [operators(false),
389   dotlists(true)]).
390<P>
391"),
392        args:["Term" : "Prolog term."],
393        eg:"   Equivalent to display(output, Term).  (see display/2).
394
395
396
397",
398        see_also:[display / 2, write / 1, write / 2, writeq / 1, writeq / 2]]).
399
400:- comment(display / 2, [
401        summary:"Term is displayed on the output stream Stream --- without considering
402operator definitions.
403
404",
405        amode:(display(+,?) is det),
406        desc:html("   Used to display an expression in standard parenthesised prefix notation,
407   onto the output stream Stream.
408<P>
409   display(S, Term) is equivalent to write_term(S, Term, [operators(false),
410   dotlists(true)]).
411<P>
412   Note that as usual, the output is buffered, so it may need to be flushed
413   either by closing the stream, by writing again or by using flush/1.
414
415<P>
416"),
417        args:[
418            "Stream" : "Stream handle or alias (atom)",
419            "Term" : "Prolog term."],
420        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output stream.", 193 : "Stream is an illegal stream specification."],
421        eg:"
422Success:
423      display(output, 3.0).                % displays 3.0
424      set_stream(a,output), display(a,hi). % displays hi
425
426      ?- open(file1,update,S), display(S, X+2), close(S).
427      X = _72
428      S = 6
429      yes.
430      ?- sh('cat file1').
431      +(_98, 2)
432      yes.
433Error:
434      display(S, a(b,c)).        (Error 4).
435      display(\"string\", a(b,c)). (Error 5).
436      display(9, X=2).           (Error 192). % stream not open
437      display(atom, X=2).        (Error 193).
438
439
440
441",
442        see_also:[display / 1, write / 1, write / 2]]).
443
444:- comment(print / 1, [
445        summary:"The term Term is written on the output stream according to the current
446operator declarations, using the predicate portray/2 or portray/1 if it
447exists.
448
449",
450        amode:(print(?) is det),
451        desc:html("   Used to print the term Term on the current output according to the
452   current operator declarations, i.e.  the same as write/1, however the
453   user has the possibility to influence the way the term is printed.  If
454   the predicate portray/2 is visible in the module where print/1 was
455   called from, it is used by print/1 in the following way:
456<P>
457  * If Term is a variable, it is printed using write/1.
458<P>
459  * If Term is a nonvariable or an attributed variable, then portray(output,
460    Term) is called.  If it succeeds, so does print/1.  Otherwise, if Term is
461    atomic, it is written using write/1 and the predicate succeeds.  If
462    Term is a compound term, its main functor is printed using write/1 and
463    print/1 is called recursively on its arguments.
464<P>
465   If portray/2 is not visible but portray/1 is, it is called instead of
466   portray/2.
467<P>
468   Note that when this predicate is used to print a list, only the elements
469   of the list, i.e.  the heads, are passed to the recursive calls of
470   print/2, but not the list tails.  Thus e.g.  a list [1,2,3] will be
471   passed once to portray/2 as a whole and then the elements 1, 2, 3, but
472   not [2,3], [3] and [].
473<P>
474   portray/1, 2 is used by the system when printing the answer bindings
475   in the top-level loop, and by the debugger to print trace lines.
476<P>
477   print(Term) is equivalent to write_term(Term, [portrayed(true),
478   numbervars(true)]).
479<P>
480   As usual, the output is buffered, so it may need to be flushed (e.g.
481   explicitly using flush/1).
482
483<P>
484Note
485   The output of print/1 is not necessarily in a form acceptable to
486   read/1,2.
487
488<P>
489"),
490        args:["Term" : "Prolog term."],
491        eg:"
492Success:
493    ?- [user].
494     portray(S, a) :- write(S, b).
495     user   compiled 100 bytes in 0.02 seconds
496    yes.
497    ?- print([a, b, c, d]).
498    [b, b, c, d]
499    yes.
500
501    ?- [user].
502     portray(S, '$VAR'(X)) :- write(S, 'X_'), write(S, X).
503     user   compiled 180 bytes in 0.00 seconds
504    yes.
505    ?- lib(numbervars).
506    yes.
507    ?- F=f(_,_,_,_), numbervars(F, 0, _), write(F).
508    f(A, B, C, D)                % default printing of '$VAR'/1
509    F = f(X_0, X_1, X_2, X_3)    % toplevel uses portray
510    yes.
511",
512        see_also:[display / 1, display / 2, print / 2, write / 1, write / 2, writeq / 1, writeq / 2]]).
513
514:- comment(print / 2, [
515        summary:"The term Term is written on the output stream Stream according to the
516current operator declarations, using the predicate portray/2 or portray/1
517if it exists.
518
519",
520        amode:(print(+,?) is det),
521        desc:html("   Used to print the term Term on the output stream Stream according to the
522   current operator declarations, i.e.  the same as write/2, however the
523   user has the possibility to influence the way the term is printed.  If
524   the predicate portray/2 is visible in the module where print/2 was
525   called from, it is used by print/2 in the following way:
526<P>
527  * If Term is a variable, it is printed using write/2.
528<P>
529  * If Term is a nonvariable or an attributed variable, then portray(Stream,
530    Term) is called.  If it succeeds, so does print/2.  Otherwise, if Term is
531    atomic, it is written using write/2 and the predicate succeeds.  If
532    Term is a compound term, its main functor is printed using write/2 and
533    print/2 is called recursively on its arguments.
534<P>
535   Note that when this predicate is used to print a list, only the elements
536   of the list, i.e.  the heads, are passed to the recursive calls of
537   print/2, but not the list tails.  Thus e.g.  a list [1,2,3] will be
538   passed once to portray/2 as a whole and then the elements 1, 2, 3, but
539   not [2,3], [3] and [].
540<P>
541   If portray/2 is not visible but portray/1 is, it is called instead of
542   portray/2, with the 'output' stream temporarily redirected to Stream.
543   Because of this side effect, defining portray/2 is preferrable.
544<P>
545   portray/1, 2 is used by the system when printing the answer bindings
546   in the top-level loop, and by the debugger to print trace lines.
547<P>
548   print(S, Term) is equivalent to write_term(S, Term, [portrayed(true),
549   numbervars(true)]).
550<P>
551   As usual, the output is buffered, so it may need to be flushed (e.g.
552   explicitly using flush/1).
553
554<P>
555Note
556   The output of print/2 is not necessarily in a form acceptable to
557   read/1,2 and there is no 'printq' predicate.
558
559<P>
560"),
561        args:[
562            "Stream" : "Stream handle or alias (atom)",
563            "Term" : "Prolog term."],
564        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output steam.", 193 : "Stream is not a stream specification."],
565        eg:"
566Success:
567    ?- [user].
568     portray(S, a) :- write(S, b).
569
570     p(a).
571     user   compiled 148 bytes in 0.00 seconds
572
573    yes.
574    ?- write(write(a)), nl, print(output, print(a)).
575    write(a)
576    print(b)
577    yes.
578    ?- trace.
579
580    yes.
581    Debugger switched on - creep mode
582    ?- p(a).
583      (1) 0  CALL   p(a) (dbg)?- output: write        ('o' typed)
584      (1) 0  CALL   p(a) (dbg)?- output: display
585      (1) 0  CALL   p(a) (dbg)?- output: print/writeq
586      (1) 0  CALL   p(b) (dbg)?- creep
587      (1) 0  EXIT   p(b) (dbg)?- creep
588
589    yes.
590
591Error:
592     print(S, a(b,c)).         (Error 4).
593     print(\"str\", a(b,c)).     (Error 5).
594     print(input, X).          (Error 192).
595     print(nostr, X + 2).      (Error 193).
596
597
598
599",
600        see_also:[display / 1, display / 2, print / 1, write / 1, write / 2, writeq / 1, writeq / 2]]).
601
602:- comment(printf / 2, [
603        summary:"The arguments in the argument list ArgList are interpreted according to the
604Format string and the result is printed to the output stream.
605
606",
607        amode:(printf(+,?) is det),
608        desc:html("   Format is either an atom or a string which can contain control sequences
609   of the form
610
611<P>
612   %AC or %NC
613
614<P>
615   where C is a single letter format control option and A or N are optional
616   parameters.  Any characters that are not part of a control sequence are
617   written to the output stream.
618
619<DL>
620  <DT>A<DD>
621    A may consist of:
622    a minus sign, a plus sign, a space , the character '#', a digit string
623    (or a '*'), a period, a digit string (or a '*') and a length modifier 'l'.
624<P>
625    This substring A is interpreted in the same way as in the 'C' routine
626    printf(3).
627
628  <DT>N<DD>
629    The argument N has to be a non-negative integer.
630</DL>
631
632   If the character '*' appears inside A or N it is replaced by the next
633   argument from ArgList.
634<P>
635
636   ArgList is a list of arguments which will be interpreted and possibly
637   printed by format control options.  If there is only one argument, it
638   need not be in a list.
639
640<P>
641   The elements from the argument list ArgList are interpreted according to
642   the following control options and printed to the output.  The arguments
643   must be of the type specified, or the corresponding event will be
644   raised.
645
646<DL>
647  <DT>%<STRONG>a</STRONG><DD>
648    The argument has to be an atom and is passed to write/1.
649
650  <DT>%<STRONG>A</STRONG><DD>
651    The argument has to be an atom. All its characters are converted
652    to upper case and the result is printed.
653
654  <DT>%N<STRONG>c</STRONG><DD>
655    The argument has to be a numeric ASCII code and is printed N times.  If
656    N is omitted, it defaults to 1.
657
658  <DT>%A<STRONG>d</STRONG><DD>
659    The argument has to be an integer and is printed according to the
660    substring A in signed decimal notation.
661
662  <DT>%A<STRONG>o</STRONG><DD>
663    The argument has to be an integer and is printed according to the
664    substring A in unsigned octal notation.
665
666  <DT>%A<STRONG>u</STRONG><DD>
667    The argument has to be an integer and is printed according to the
668    substring A in unsigned decimal notation.
669
670  <DT>%A<STRONG>x</STRONG><DD>
671    The argument has to be an integer and is printed according to the
672    substring A in unsigned hexadecimal notation.  (The letters abcdef are
673    used.)
674
675  <DT>%A<STRONG>X</STRONG><DD>
676    The argument has to be an integer and is printed according to the
677    substring A in unsigned hexadecimal notation.  (The letters ABCDEF are
678    used.)
679
680  <DT>%A<STRONG>e</STRONG><DD>
681    The argument has to be a floating-point number and is printed according
682    to the substring A in exponential notation.('e' is used for
683    exponentiation)
684
685  <DT>%A<STRONG>E</STRONG><DD>
686    The argument has to be a floating-point number and is printed according
687    to the substring A in exponential notation.  ('E' is used for
688    exponentiation)
689
690  <DT>%A<STRONG>f</STRONG><DD>
691    The argument has to be a floating-point number and is printed according
692    to the substring A in non-exponential form.
693
694  <DT>%A<STRONG>g</STRONG><DD>
695    The argument has to be a floating-point number and is printed according
696    to the substring A in exponential or non-exponential form, whichever
697    gives the best precision in minimum space.('e' is used for
698    exponentiation)
699
700  <DT>%A<STRONG>s</STRONG><DD>
701    The argument has to be a string or an atom and is printed according to
702    the substring A.
703
704  <DT>%N<STRONG>r</STRONG><DD>
705    The argument has to be an integer and it is printed as signed in radix
706    N using the digits 0-9 and letters a-z.  N must be greater than 1 and
707    less than 37.  If N is not specified, it defaults to 8.
708
709  <DT>%N<STRONG>R</STRONG><DD>
710    The argument has to be an integer and it is printed as signed in radix
711    N using the digits 0-9 and letters A-Z. N must be greater than 1 and
712    less than 37.  If N is not specified, it defaults to 8.
713
714<P>
715   The following control options can interpret arguments of any type.
716
717  <DT>%N<STRONG>i</STRONG><DD>
718    N arguments are ignored.  If N is omitted, it defaults to 1.
719
720  <DT>%<STRONG>k</STRONG><DD>
721    The argument is passed to display/1.  It is a synonym for %O.w.
722
723  <DT>%<STRONG>p</STRONG><DD>
724    The argument is passed to print/1.  It is a synonym for %Pw.
725
726  <DT>%<STRONG>q</STRONG><DD>
727    %q
728
729<DD>
730    The argument is passed to writeq/1.  It is a synonym for %QDvw.
731
732  <DT>%<STRONG>w</STRONG><DD>
733   The argument is by default passed to write/1.
734   However, the %w format recognises a number of control characters,
735   placed between the percent sign and w.  They give the user full
736   control over the various possibilities of printing Prolog terms.
737   A number immediately after the percent sign determines the depth
738   to which the term is printed, if an asterisk is used instead, the
739   depth is taken from the next argument in ArgList. The default depth
740   is determined by the setting of the (stream-specific or global)
741   print_depth flag.
742   After the optional depth, the following modifiers are recognized:
743
744<DL>
745      <DT><STRONG>O</STRONG><DD>
746        omit operator declarations.  All terms are written in the canonical
747        notation without operators.
748
749      <DT><STRONG>Q</STRONG><DD>
750        quote atoms and strings if necessary.
751
752      <DT><STRONG>.</STRONG><DD>
753        write lists in the dot functor notation rather than using the
754        square bracket notation, e.g. .(1, .(2, [])) rather than [1, 2].
755
756      <DT><STRONG>G</STRONG><DD>
757        print the term as a goal, i.e. goal write transformations will be
758        taken into account.
759
760      <DT><STRONG>P</STRONG><DD>
761        call the user-defined predicate portray/1, 2 in the way print/1, 2
762        does.
763
764      <DT><STRONG>D</STRONG><DD>
765        disregard the depth restriction of the print-depth flag and print
766        the whole term.
767
768      <DT><STRONG>U</STRONG><DD>
769        call portray/1, 2 even on variables.  This is to be used in
770        conjunction with the P option.  Note that attributed variables
771        are always portrayed.
772
773      <DT><STRONG>V</STRONG><DD>
774        print the full variable name, if available, either in the form
775        Name_Number, e.g. Alpha_132, or Name#Number, if the variable had
776        been given a name via lib(var_name). This is necessary to 
777        distinguish different variables with the same name.
778
779      <DT><STRONG>v</STRONG><DD>
780        print only the short variable form, i.e. even when available, the
781        variable name is not printed.  This is useful if a term should be
782        written and read back in several times.  If neither V nor v is
783        specified, variables are printed only with their name, if it is
784        available.  Variable without names are always printed in the v form.
785
786      <DT><STRONG>_</STRONG><DD>
787        print every variable as a simple underscore. Any information about
788        multiple occurrences of a variable is lost with this format. It is
789        mainly useful to produce output that can be compared easily with
790        the output of a different Eclipse session.
791
792      <DT><STRONG>I</STRONG><DD>
793        any term of the form '$VAR'(N), where N is a non-negative integer,
794        is printed as a variable name consisting of a capital letter
795        followed by a number. The capital letter is the ((N mod 26)+1)st
796        letter of the alphabet, and the integer is N//26.
797        If N is an atom, this atom gets printed instead of the term.
798
799      <DT><STRONG>K</STRONG><DD>
800        don't print blank space (around operators, after commas, etc.)
801        unless necessary.
802
803      <DT><STRONG>M</STRONG><DD>
804        print the full contents of all variable attributes.  This is
805        necessary if the term is to be written out and read back in.
806
807      <DT><STRONG>m</STRONG><DD>
808        variable attributes are printed using the corresponding print
809        handlers.  If neither M nor m is specified, attributed variables
810        are printed as variables, without any attribute.
811
812      <DT><STRONG>N</STRONG><DD>
813        print newline (NL) characters as newlines rather than as an
814        escape sequence, even when they occur in quoted atoms or strings.
815        This only makes sense together with the Q modifier.
816
817      <DT><STRONG>T</STRONG><DD>
818        do not apply any write transformations.
819
820      <DT><STRONG>C</STRONG><DD>
821        print the term as a clause, i.e.  clause macros will be taken into
822        account.
823
824      <DT><STRONG>F</STRONG><DD>
825	print a fullstop after the term, separated from the term by an
826	extra space, if necessary.
827
828      <DT><STRONG>L</STRONG><DD>
829	print a newline after the term (or as part of the fullstop
830	sequence, if used together with the F option).
831</DL>
832
833  <DT>%<STRONG>W</STRONG><DD>
834    Like %w, but the stream's default output options are taken into
835    account, unless overridden by the format options specified here.
836    Note in particular that a default setting may be cancelled by
837    prefixing the format character with a minus sign. E.g. if the stream
838    defaults specify that quotes should be printed (quoted(true)), this
839    can be overridden by a %-QW format string.
840
841</DL>
842   The following control options do not have a corresponding argument.
843<DL>
844  <DT>%<STRONG>%</STRONG><DD>
845    One % is printed.
846
847  <DT>%N<STRONG>n</STRONG><DD>
848    N newline sequences are printed.  If N is omitted it defaults to 1.
849    Which newline characters are printed depends on the setting of the
850    stream's end_of_line property. If the stream's flush-property is set
851    to end_of_line, the stream is also flushed.
852
853  <DT>%N<STRONG>t</STRONG><DD>
854    N tab characters are printed.  If N is omitted it defaults to 1.
855
856  <DT>%<STRONG>b</STRONG><DD>
857    The output buffer is flushed, the data is written into the file.
858</DL>
859"),
860        args:["Format" : "String or Atom.", "ArgList" : "List or any Term."],
861        exceptions:[5 : "Format is not an atom or a string.", 5 : "ArgList contains argument whose type does not correspond to    the control sequence.", 7 : "Format is not correct, it contains too many asterisks or a    control character is missing or there is a redundant character before    the control character.", 8 : "ArgList has not enough or too many arguments."],
862        eg:"   Equivalent to printf(output, Format, ArgList).  (see printf/3 for
863   details).
864
865
866
867",
868        see_also:[display / 1, display / 2, print / 1, print / 2, printf / 3, sprintf/3, write / 1, write / 2, writeq / 1, writeq / 2]]).
869
870:- comment(printf / 3, [
871        summary:"The arguments in the argument list ArgList are interpreted according to the
872Format string and the result is printed on the output Stream.
873
874",
875        amode:(printf(+,+,?) is det),
876        desc:html("   Format is either an atom or a string which can contain control sequences
877   of the form
878
879<P>
880   %AC or %NC
881
882<P>
883   where C is a single letter format control option and A or N are optional
884   parameters.  Any characters that are not part of a control sequence are
885   written to the output stream Stream.
886
887<DL>
888  <DT>A<DD>
889    A may consist of:
890    a minus sign, a plus sign, a space , the character '#', a digit string
891    (or a '*'), a period, a digit string (or a '*') and a length modifier 'l'.
892<P>
893    This substring A is interpreted in the same way as in the 'C' routine
894    printf(3).
895
896  <DT>N<DD>
897    The argument N has to be a non-negative integer.
898</DL>
899
900   If the character '*' appears inside A or N it is replaced by the next
901   argument from ArgList.
902<P>
903
904   ArgList is a list of arguments which will be interpreted and possibly
905   printed by format control options.  If there is only one argument, it
906   need not be in a list.
907
908<P>
909   The elements from the argument list ArgList are interpreted
910   according to the following control options and printed to the
911   output stream Stream.  The arguments must be of the type specified,
912   or the corresponding event will be raised.
913
914<DL>
915  <DT>%<STRONG>a</STRONG><DD>
916    The argument has to be an atom and is passed to write/1.
917
918  <DT>%<STRONG>A</STRONG><DD>
919    The argument has to be an atom. All its characters are converted
920    to upper case and the result is printed.
921
922  <DT>%N<STRONG>c</STRONG><DD>
923    The argument has to be a numeric ASCII code and is printed N times.  If
924    N is omitted, it defaults to 1.
925
926  <DT>%A<STRONG>d</STRONG><DD>
927    The argument has to be an integer and is printed according to the
928    substring A in signed decimal notation.
929
930  <DT>%A<STRONG>o</STRONG><DD>
931    The argument has to be an integer and is printed according to the
932    substring A in unsigned octal notation.
933
934  <DT>%A<STRONG>u</STRONG><DD>
935    The argument has to be an integer and is printed according to the
936    substring A in unsigned decimal notation.
937
938  <DT>%A<STRONG>x</STRONG><DD>
939    The argument has to be an integer and is printed according to the
940    substring A in unsigned hexadecimal notation.  (The letters abcdef are
941    used.)
942
943  <DT>%A<STRONG>X</STRONG><DD>
944    The argument has to be an integer and is printed according to the
945    substring A in unsigned hexadecimal notation.  (The letters ABCDEF are
946    used.)
947
948  <DT>%A<STRONG>e</STRONG><DD>
949    The argument has to be a floating-point number and is printed according
950    to the substring A in exponential notation.('e' is used for
951    exponentiation)
952
953  <DT>%A<STRONG>E</STRONG><DD>
954    The argument has to be a floating-point number and is printed according
955    to the substring A in exponential notation.  ('E' is used for
956    exponentiation)
957
958  <DT>%A<STRONG>f</STRONG><DD>
959    The argument has to be a floating-point number and is printed according
960    to the substring A in non-exponential form.
961
962  <DT>%A<STRONG>g</STRONG><DD>
963    The argument has to be a floating-point number and is printed according
964    to the substring A in exponential or non-exponential form, whichever
965    gives the best precision in minimum space.('e' is used for
966    exponentiation)
967
968  <DT>%A<STRONG>s</STRONG><DD>
969    The argument has to be a string or an atom and is printed according to
970    the substring A.
971
972  <DT>%N<STRONG>r</STRONG><DD>
973    The argument has to be an integer and it is printed as signed in radix
974    N using the digits 0-9 and letters a-z.  N must be greater than 1 and
975    less than 37.  If N is not specified, it defaults to 8.
976
977  <DT>%N<STRONG>R</STRONG><DD>
978    The argument has to be an integer and it is printed as signed in radix
979    N using the digits 0-9 and letters A-Z. N must be greater than 1 and
980    less than 37.  If N is not specified, it defaults to 8.
981
982<P>
983   The following control options can interpret arguments of any type.
984
985  <DT>%N<STRONG>i</STRONG><DD>
986    N arguments are ignored.  If N is omitted, it defaults to 1.
987
988  <DT>%<STRONG>k</STRONG><DD>
989    The argument is passed to display/1.  It is a synonym for %O.w.
990
991  <DT>%<STRONG>p</STRONG><DD>
992    The argument is passed to print/1.  It is a synonym for %Pw.
993
994  <DT>%<STRONG>q</STRONG><DD>
995    %q
996
997<DD>
998    The argument is passed to writeq/1.  It is a synonym for %QDvw.
999
1000  <DT>%<STRONG>w</STRONG><DD>
1001   The argument is by default passed to write/1.
1002   However, the %w format recognises a number of control characters,
1003   placed between the percent sign and w.  They give the user full
1004   control over the various possibilities of printing Prolog terms.
1005   A number immediately after the percent sign determines the depth
1006   to which the term is printed, if an asterisk is used instead, the
1007   depth is taken from the next argument in ArgList. The default depth
1008   is determined by the setting of the (stream-specific or global)
1009   print_depth flag.
1010   After the optional depth, the following modifiers are recognized:
1011
1012<DL>
1013      <DT><STRONG>O</STRONG><DD>
1014        omit operator declarations.  All terms are written in the canonical
1015        notation without operators.
1016
1017      <DT><STRONG>Q</STRONG><DD>
1018        quote atoms and strings if necessary.
1019
1020      <DT><STRONG>.</STRONG><DD>
1021        write lists in the dot functor notation rather than using the
1022        square bracket notation, e.g. .(1, .(2, [])) rather than [1, 2].
1023
1024      <DT><STRONG>G</STRONG><DD>
1025        print the term as a goal, i.e.  goal write transformations will
1026        be taken into account.
1027
1028      <DT><STRONG>P</STRONG><DD>
1029        call the user-defined predicate portray/1, 2 in the way print/1, 2
1030        does.
1031
1032      <DT><STRONG>D</STRONG><DD>
1033        disregard the depth restriction of the print-depth flag and print
1034        the whole term.
1035
1036      <DT><STRONG>U</STRONG><DD>
1037        call portray/1, 2 even on variables.  This is to be used in
1038        conjunction with the P option.  Note that attributed variables
1039        are always portrayed.
1040
1041      <DT><STRONG>V</STRONG><DD>
1042        print the full variable name, if available, either in the form
1043        Name_Number, e.g. Alpha_132, or Name#Number, if the variable had
1044        been given a name via lib(var_name). This is necessary to 
1045        distinguish different variables with the same name.
1046
1047      <DT><STRONG>v</STRONG><DD>
1048        print only the short variable form, i.e. even when available, the
1049        variable name is not printed.  This is useful if a term should be
1050        written and read back in several times.  If neither V nor v is
1051        specified, variables are printed only with their name, if it is
1052        available.  Variable without names are always printed in the v form.
1053
1054      <DT><STRONG>_</STRONG><DD>
1055        print every variable as a simple underscore. Any information about
1056        multiple occurrences of a variable is lost with this format. It is
1057        mainly useful to produce output that can be compared easily with
1058        the output of a different Eclipse session.
1059
1060      <DT><STRONG>I</STRONG><DD>
1061        any term of the form '$VAR'(N), where N is a non-negative integer,
1062        is printed as a variable name consisting of a capital letter
1063        followed by a number. The capital letter is the ((N mod 26)+1)st
1064        letter of the alphabet, and the integer is N//26.
1065        If N is an atom, this atom gets printed instead of the term.
1066
1067      <DT><STRONG>K</STRONG><DD>
1068        don't print blank space (around operators, after commas, etc.)
1069        unless necessary.
1070
1071      <DT><STRONG>M</STRONG><DD>
1072        print the full contents of all variable attributes.  This is
1073        necessary if the term is to be written out and read back in.
1074
1075      <DT><STRONG>m</STRONG><DD>
1076        variable attributes are printed using the corresponding print
1077        handlers.  If neither M nor m is specified, attributed variables
1078        are printed as variables, without any attribute.
1079
1080      <DT><STRONG>N</STRONG><DD>
1081        print newline (NL) characters as newlines rather than as an
1082        escape sequence, even when they occur in quoted atoms or strings.
1083        This only makes sense together with the Q modifier.
1084
1085      <DT><STRONG>T</STRONG><DD>
1086        do not apply any write transformations.
1087
1088      <DT><STRONG>C</STRONG><DD>
1089        print the term as a clause, i.e.  clause macros will be taken into
1090        account.
1091
1092      <DT><STRONG>F</STRONG><DD>
1093	print a fullstop after the term, separated from the term by an
1094	extra space, if necessary.
1095
1096      <DT><STRONG>L</STRONG><DD>
1097	print a newline after the term (or as part of the fullstop
1098	sequence, if used together with the F option).
1099</DL>
1100
1101  <DT>%<STRONG>W</STRONG><DD>
1102    Like %w, but the stream's default output options are taken into
1103    account, unless overridden by the format options specified here.
1104    Note in particular that a default setting may be cancelled by
1105    prefixing the format character with a minus sign. E.g. if the stream
1106    defaults specify that quotes should be printed (quoted(true)), this
1107    can be overridden by a %-QW format string.
1108
1109</DL>
1110   The following control options do not have a corresponding argument.
1111<DL>
1112  <DT>%<STRONG>%</STRONG><DD>
1113    One % is printed.
1114
1115  <DT>%N<STRONG>n</STRONG><DD>
1116    N newline sequences are printed.  If N is omitted it defaults to 1.
1117    Which newline characters are printed depends on the setting of the
1118    stream's end_of_line property. If the stream's flush-property is set
1119    to end_of_line, the stream is also flushed.
1120
1121  <DT>%N<STRONG>t</STRONG><DD>
1122    N tab characters are printed.  If N is omitted it defaults to 1.
1123
1124  <DT>%<STRONG>b</STRONG><DD>
1125    The output buffer is flushed, the data is written into the file.
1126</DL>
1127"),
1128        args:[
1129            "Stream" : "Stream handle or alias (atom)",
1130            "Format" : "String or Atom.", "ArgList" : "List or any Term."],
1131        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 5 : "Format is not an atom or a string.", 5 : "ArgList contains argument whose type does not correspond to    the control sequence.", 7 : "Format is not correct, it contains too many asterisks or a    control character is missing or there is a redundant character before    the control character.", 8 : "ArgList has not enough or too many arguments.", 192 : "Stream is not an output stream.", 193 : "Stream is not a stream specification."],
1132        eg:"
1133Success:
1134?- printf(output, \"abc %s ghi %+*.*E...\",
1135        [\"def\", 2, 3, 12.34]).
1136abc def ghi +1.234E+01...
1137yes.
1138?- printf(output, \"abc %12c %*n\", [77, 3]).
1139abc MMMMMMMMMMMM
1140
1141
1142
1143yes.
1144?- printf(output, \"abc %i def %a%2t%%\", [123, ghi]).
1145abc  def ghi            %
1146yes.
1147?- printf(output, \"%w\", ['A'+'B']).
1148A + B
1149yes.
1150?- printf(output, \"%q\", ['A'+'B']).
1151'A' + 'B'
1152yes.
1153?- printf(output, \"%k\", ['A'+'B']).
1154+(A, B)
1155yes.
1156
1157Error:
1158      printf(S, \"%s\", [\"eclipse\"]).          (Error 4).
1159      printf(output, F, eclipse).            (Error 4).
1160      printf(\"output\", \"%s\", [\"eclipse\"]).   (Error 5).
1161      printf(output, \"%a\", 1).               (Error 5).
1162      printf(output, \"%*.*.*s\", [2, 3, 4,  \"eclipse\"]).
1163                                             (Error 7).
1164      printf(output, \"%d %d %d\", [1, 9]).    (Error 8).
1165      printf(9, \"%s\", [\"eclipse\"]).
1166                       (Error 192). % stream not open
1167      printf(atom, \"%s\", [\"eclipse\"]).       (Error 193).
1168      printf(s, comment%s, eclipse).
1169                                 '%' starts a comment
1170
1171
1172
1173",
1174    see_also:[display / 1, display / 2, print / 1, print / 2, printf / 2, sprintf/3,
1175        write / 1, write / 2, write_term/2, write_term/3, writeq / 1,
1176        writeq / 2]]).
1177
1178
1179:- comment(sprintf / 3, [
1180        summary:"The arguments in the argument list ArgList are interpreted according to the
1181Format string and the formatted result is unified with String.",
1182        amode:(sprintf(-,+,?) is det),
1183        desc:html("\
1184    This predicate works exactly like printf/2,3 except that the formatted
1185    result is delivered in the form of a string.  See printf/2,3 for details.
1186<P>
1187    Note that for simple cases it is usually more efficient to use
1188    primitives like concat_string/2, join_string/3 or number_string/2.
1189<P>
1190"),
1191        args:[
1192            "String" : "Variable or String.",
1193            "Format" : "String or Atom.",
1194            "ArgList" : "List or any Term."],
1195        exceptions:[
1196            5 : "String is instantiated to something other than a string.",
1197            5 : "Format is not an atom or a string.",
1198            5 : "ArgList contains argument whose type does not correspond to the control sequence.",
1199            7 : "Format is not correct, it contains too many asterisks or a control character is missing or there is a redundant character before the control character.",
1200            8 : "ArgList has not enough or too many arguments."],
1201        eg:"
1202Success:
1203?- sprintf(String, \"abc %s ghi %+*.*E...\", [\"def\", 2, 3, 12.34]).
1204String = \"abc def ghi +1.234E+01...\"
1205yes.
1206
1207?- sprintf(String, \"abc %12c %*n\", [77, 3]).
1208String = \"abc MMMMMMMMMMMM \\n\\n\\n\"
1209yes.
1210
1211?- sprintf(\"x9\", \"x%d\", [3]).
1212no.
1213",
1214    see_also:[concat_string/2, join_string/3, number_string/2, printf/2, printf/3]
1215]).
1216
1217
1218:- comment(read / 1, [
1219        summary:"Succeeds if the next term from the input stream is successfully read and
1220unified with Term.
1221
1222",
1223        amode:(read(-) is semidet),
1224        desc:html("   Used to read the next term from the input stream and unify it with Term.
1225   The term must be in Prolog term format i.e.  terminated by fullstop (a
1226   period and a blank space character), neither of which are retained by
1227   Prolog.
1228
1229<P>
1230   End of file acts like fullstop.  If only end of file is read, the event
1231   190 is raised and the default handler unifies Term with the atom
1232   end_of_file.
1233
1234<P>
1235   The default action for syntax errors is to print a warning and fail.
1236
1237<P>
1238"),
1239        args:["Term" : "Prolog term."],
1240        fail_if:"Fails if a syntax error was detected and no term could be read",
1241        exceptions:[190 : "End of file was encountered before reading any character.", 198 : "Trying to read even after the error 190 was raised."],
1242        eg:"   Equivalent to read(input, Term).  (see read/2 for details).
1243
1244
1245
1246",
1247        see_also:[read / 2]]).
1248
1249:- comment(read / 2, [
1250        summary:"Succeeds if the next term from the input stream Stream is successfully read
1251and unified with Term.
1252
1253",
1254        amode:(read(+,-) is semidet),
1255        desc:html("   Used to read the next term from the input stream Stream and unify it
1256   with Term.  If there is more than one Prolog term in the file, the term
1257   must be in Prolog term format i.e.  terminated by fullstop (a period and
1258   a blank space character), neither of which are retained by Prolog.
1259
1260<P>
1261   Otherwise, end of file acts like fullstop.  If only end of file is read,
1262   the event 190 is raised and the default handler unifies Term with the
1263   atom end_of_file.
1264
1265<P>
1266   The default action for syntax errors is to print a warning and fail.
1267
1268<P>
1269"),
1270        args:[
1271            "Stream" : "Stream handle or alias (atom)",
1272            "Term" : "Prolog term or variable."],
1273        fail_if:"Fails if a syntax error was detected and no term could be read",
1274        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 190 : "End of file was encountered before reading any character.", 192 : "Stream is not an input stream.", 193 : "Stream is an illegal stream specification.", 198 : "Trying to read even after the error 190 was raised."],
1275        eg:"
1276Success:
1277      ?- read(0,Term).
1278       atom.
1279      Term = atom
1280      yes.
1281
1282      ?- open(file1,write,s),write(s, 'f(1,2,3).\\ng(1,2'),
1283         write(s, ',3). h(1,2,3).\\ni.\\nj(1, 2\\n,3).').
1284      yes.
1285      ?- system('cat file1').
1286      f(1,2,3).
1287      g(1,2,3). h(1,2,3).
1288      i.
1289      j(1, 2
1290      ,3).
1291      yes.
1292      ?- open(file1,read,s), read(s,A), read(s,B),
1293         read(s,C), read(s,D), read(s,E), read(s,F).
1294      A = f(1, 2, 3)
1295      B = g(1, 2, 3)
1296      C = h(1, 2, 3)
1297      D = i
1298      E = j(1, 2, 3)
1299      F = end_of_file
1300      yes.
1301Fail:
1302      ?- read(0,a).
1303       b.
1304      no.
1305
1306      ?- read(0,X).
1307       f(1,2)m.
1308              ^ (here?)
1309      syntax error: postfix/infix operator expected
1310      no (more) solution.
1311Error:
1312      read(a(b,c),S).               (Error 4).
1313      read(\"string\", a(b,c)).       (Error 5).
1314      read(9, X=2).                 (Error 192). % stream not open
1315      read(atom, X=2).              (Error 193).
1316
1317
1318
1319",
1320        see_also:[read / 1, readvar / 3, read_token / 2, read_token / 3]]).
1321
1322:- comment(readvar / 3, [
1323        summary:"Succeeds if the next Prolog term from the input stream Stream is
1324successfully read and unified with Term, and any variables in Term are
1325collected in the list VarList, together with their names.
1326
1327",
1328        amode:(readvar(+,-,-) is semidet),
1329        desc:html("   Used to read the next term from the input stream Stream, unify it with
1330   Term and store any variables in Term to the list VarList.  This is a
1331   list of pairs in the format [VarName|Var].
1332
1333<P>
1334   VarName is the literal input variable name expressed as an atom; Var is
1335   the variable.  The first element of the pair Varname is the atom
1336   corresponding to the variable name, and the second element Var is the
1337   corresponding variable.
1338
1339<P>
1340   If there is more than one Prolog term in the file, the term must be in
1341   Prolog term format i.e.  terminated by a period and a blank space
1342   character, neither of which are retained by Prolog.
1343
1344<P>
1345"),
1346        args:[
1347            "Stream" : "Stream handle or alias (atom)",
1348            "Term" : "Prolog term.", "VarList" : "A Variable."],
1349        fail_if:"Fails if a syntax error was detected and no term could be read",
1350        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle, Varlist is not a    variable.", 190 : "End of file was encountered before reading any character.", 192 : "Stream is not an input stream.", 193 : "Stream is an illegal stream specification.", 198 : "Trying to read even after the error 190 was raised."],
1351        eg:"
1352Success:
1353      ?- readvar(input,Term,VarList).
1354       atom.
1355      Term = atom
1356      VarList = []
1357      yes.
1358
1359      ?- readvar(input,T,L).
1360       X.
1361      T = _50
1362      L = [['X'|_50]]
1363      yes.
1364
1365      ?- system('cat file1').
1366      f(X,Y).
1367      g(1,X).
1368      yes.
1369      ?- open(file1,update,r), readvar(r,T1,V1),
1370         readvar(r, T2,V2).
1371      T1 = f(_120, _122)
1372      V1 = [['X'|_120], ['Y'|_122]]
1373      T2 = g(1, _146)              % the clauses are separate,
1374      V2 = [['X'|_146]]            % so the X's are different.
1375      yes.
1376
1377Fail:
1378      ?- readvar(input, X + 2,V).
1379       X + 1.
1380      no.
1381
1382Error:
1383      readvar(S,a(b,c),V).          (Error 4).
1384      readvar(\"string\",a(b,c),V,).  (Error 5).
1385      readvar(output,X + 2,V).      (Error 192).
1386      readvar(atom,X + 2,V).        (Error 193).
1387
1388
1389
1390",
1391        see_also:[read / 1, read / 2]]).
1392
1393:- comment(write / 1, [
1394        summary:"The term Term is written on output stream according to the current operator
1395declarations.
1396
1397",
1398        amode:(write(?) is det),
1399        desc:html("\
1400   Used to write the term Term on the current output according to the
1401   current operator declarations.  Lists and compound terms are only
1402   printed up to the nesting depth specified by the (stream-specific
1403   or global) print_depth setting (cf. set_stream_property/3, set_flag/2).
1404<P>
1405   write(Term) is equivalent to write_term(Term, [numbervars(true)]).
1406
1407<P>
1408Note
1409   The output of write/1 is not necessarily in a form acceptable to
1410   read/1/2.
1411
1412<P>
1413"),
1414        args:["Term" : "Prolog term."],
1415        eg:"   Equivalent to write(output, Term).  (see write/2 for details).
1416
1417
1418
1419",
1420        see_also:[display / 1, display / 2, get_flag / 2, set_flag / 2, write / 2, writeln/1, writeq / 1, writeq / 2]]).
1421
1422:- comment(write / 2, [
1423        summary:"The term Term is written on the output stream Stream according to the
1424current operator declarations.
1425
1426",
1427        amode:(write(+,?) is det),
1428        desc:html("\
1429   Used to write the term Term on the output stream Stream according to the
1430   current operator declarations.  Lists and compound terms are only
1431   printed up to the nesting depth specified by the (stream-specific or
1432   global) print_depth setting (cf. set_stream_property/3, set_flag/2).
1433<P>
1434   write(Term) is equivalent to write_term(Term, [numbervars(true)]).
1435
1436<P>
1437   Note that as usual, the output is buffered, so it may need to be flushed
1438   (e.g.  explicitly using flush/1).
1439
1440<P>
1441Note
1442   The output of write/1 is not necessarily in a form acceptable to
1443   read/1,2.
1444
1445<P>
1446"),
1447        args:[
1448            "Stream" : "Stream handle or alias (atom)",
1449            "Term" : "Prolog term."],
1450        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output steam.", 193 : "Stream is an illegal stream specification."],
1451        eg:"
1452Success:
1453      ?- open(file1,update,s), write(s, X + 2), close(s).
1454      X = _72
1455      yes.
1456      ?- sh('cat file1').
1457      _72 + 2
1458      yes.
1459
1460Error:
1461      write(S, a(b,c)).          (Error 4).
1462      write(\"string\", a(b,c)).   (Error 5).
1463      write(9, X + 2).           (Error 192). % stream not open
1464      write(atom, X + 2).        (Error 193).
1465
1466
1467",
1468        see_also:[display / 1, display / 2, get_flag / 2, set_flag / 2, write / 1, writeln/2, writeq / 1, writeq / 2]]).
1469
1470:- comment(writeclause / 1, [
1471        summary:"The clause Clause is pretty printed on the current output .
1472
1473",
1474        amode:(writeclause(?) is det),
1475        desc:html("   Used to pretty print the clause Clause on the current output according
1476   to the current operator declarations.
1477
1478<P>
1479   When reading Prolog clauses from one file, and then writing to the
1480   current output, the latter part can be done using writeclause/1.  This
1481   is because the clauses are terminated by a period and a newline, which
1482   are not retained by Prolog.  writeclause/1 replaces these, and flushes
1483   the output.
1484
1485<P>
1486   writeclause/1,2 knows about the special meaning of ,/2, ;/2, -&gt;/2, fg,
1487   --&gt;/2 and :-/2 and prints the clause with the appropriate indentation of
1488   subgoals and some (redundant) parentheses to show the clause structure.
1489   Everything else is written as with writeq/1,2, so output of writeclause/1,2
1490   is readable for read/1,2.
1491<P>
1492"),
1493        args:["Clause" : "A Prolog term."],
1494        eg:"
1495        Equivalent to writeclause(output, Term).  (see writeclause/2 for details).
1496",
1497        see_also:[writeq / 1, writeclause / 2]]).
1498
1499:- comment(writeclause / 2, [
1500        summary:"The clause Clause is pretty printed on the output stream Stream .
1501
1502",
1503        amode:(writeclause(+,?) is det),
1504        desc:html("   Used to pretty print the clause Clause on the output stream Stream
1505   according to the current operator declarations.
1506
1507<P>
1508   When reading Prolog clauses from one file, and then writing to another,
1509   the latter part can be done using writeclause/2.  This is because the
1510   clauses are terminated by a period and a newline, which are not retained
1511   by prolog.  writeclause/2 replaces these, and flushes the output.
1512
1513<P>
1514   writeclause/1,2 knows about the special meaning of ,/2, ;/2, -&gt;/2, fg
1515   --&gt;/2 and :-/2 and prints the clause with the appropriate indentation of
1516   subgoals and some (redundant) parantheses to show the clause structure.
1517   Everything else is written as with writeq/1,2, so output of writeclause/1,2
1518   is readable for read/1,2.
1519<P>
1520"),
1521        args:[
1522            "Stream" : "Stream handle or alias (atom)",
1523            "Clause" : "A Prolog term."],
1524        exceptions:[
1525                4 : "Stream is not instantiated.",
1526                5 : "Stream is not an atom or a stream handle.",
1527                192 : "Stream is not an output stream.",
1528                193 : "Stream is an illegal stream specification."],
1529        eg:"
1530Success:
1531      ?- writeclause(output, f(1,2,3)), writeclause(output, h(2,3)).
1532      f(1, 2, 3) .
1533      h(2, 3) .
1534      yes.
1535
1536      ?- writeclause(output, X + 2).
1537      _56 + 2.
1538      yes.
1539
1540      ?- writeclause(output, a(k):-write(k)).
1541      a(k) :-
1542              write(k) .
1543      yes.
1544
1545      ?- writeclause(output, (a:-write(k),date(K))).
1546      a :-
1547              write(k),
1548              date(_68) .
1549      yes.
1550
1551      ?- open(file1,update,s), writeclause(s, X + 2), close(s).
1552      X = _72
1553      yes.
1554      ?- sh('cat file1').
1555      _72 + 2.
1556      yes.
1557
1558      ?- set_stream(a,output), writeclause(a, (:- dynamic f/1)).
1559      :- dynamic f / 1 .
1560      yes.
1561
1562      ?- writeclause(output, (head:-a1,a2;a3,a4->a5;a6)).
1563      head :-
1564                (
1565                    a1,
1566                    a2
1567                ;
1568                    (
1569                        a3,
1570                        a4
1571                    ->
1572                        a5
1573                    ;
1574                        a6
1575                    )
1576                ).
1577      yes.
1578
1579Error:
1580      writeclause(S, a(b,c)).         (Error 4).
1581      writeclause(\"string\" a(b,c)).   (Error 5).
1582",
1583        see_also:[writeq / 2, writeclause / 1]]).
1584
1585:- comment(writeln / 1, [
1586        summary:"The term Term is written on the current output according to the current
1587operator declarations.  Equivalent to write(Term),nl.
1588
1589",
1590        amode:(writeln(?) is det),
1591        desc:html("   Used to write the term Term (followed by a newline) on the current
1592   output according to the current operator declarations.
1593
1594<P>
1595"),
1596        args:["Term" : "Prolog term."],
1597        eg:"   Equivalent to writeln(output, Term).  (see writeln/2 for details).
1598
1599
1600
1601",
1602        see_also:[writeln / 2, write / 1, nl / 0]]).
1603
1604:- comment(writeln / 2, [
1605        summary:"The term Term is written on the output stream Stream according to the
1606current operator declarations.  Equivalent to write(Stream,Term),
1607nl(Stream).
1608
1609",
1610        amode:(writeln(+,?) is det),
1611        desc:html("   Used to write the term Term (followed by a newline) on the output stream
1612   Stream according to the current operator declarations.
1613
1614<P>
1615"),
1616        args:[
1617            "Stream" : "Stream handle or alias (atom)",
1618            "Term" : "Prolog term."],
1619        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output stream.", 193 : "Stream is an illegal stream specification."],
1620        eg:"
1621   Success:
1622      ?- open(file1,update,s), writeln(s, X + 2),
1623         writeln(s, Y + 3), close(s).
1624      X = _90
1625      Y = _78
1626      yes.
1627      ?- sh('cat file1').
1628      _90 + 2
1629      _78 + 3
1630      yes.
1631
1632Error:
1633      writeln(S, a(b,c)).        (Error 4).
1634      writeln(\"string\", a(b,c)). (Error 5).
1635      writeln(9, X + 2).         (Error 192).
1636      writeln(atom, X + 2).      (Error 193).
1637
1638
1639
1640",
1641        see_also:[writeln / 1, write / 1, write / 2]]).
1642
1643:- comment(writeq / 1, [
1644        summary:"The term Term is written on the current output in a form that can be read
1645in.
1646
1647",
1648        amode:(writeq(?) is det),
1649        desc:html("
1650   Used to write the term Term on the current output according to the
1651   current operator declarations.  Atoms and strings are quoted,
1652   operator expressions parenthesised (whenever necessary) and the
1653   (stream-specific or global) print_depth flag is not taken into
1654   account.  The output of writeq/1 can be read back, provided that
1655   the same operator declarations are in effect at write and read
1656   time.
1657<P>
1658   writeq(Term) is equivalent to printf(\"%DIMQvw\", Term)
1659   or write_term(Term, [attributes(full),quoted(true),numbervars(true),
1660   variables(raw),depth(full),transform(false)]).
1661
1662<P>
1663   Note that as usual, the output is buffered, so it may need to be flushed
1664   either by closing the stream, by writing again or by using flush/1.
1665
1666<P>
1667   Note also that although it is possible to print suspensions and external
1668   handles, these are printed in their printed representation as Prolog
1669   terms with functors such as 'BAG' (for bag objects). They will be read
1670   back in as such Prolog terms, rather than as their original type. 
1671
1672<P>
1673"),
1674        args:["Term" : "Prolog term."],
1675        eg:"   Equivalent to writeq(output, Term).  (see writeq/2 for details).
1676
1677
1678
1679",
1680        see_also:[printf / 2, write / 1, write / 2, writeq / 2]]).
1681
1682:- comment(writeq / 2, [
1683        summary:"The term Term is written on the output stream Stream in a form that can be
1684read in.
1685
1686",
1687        amode:(writeq(+,?) is det),
1688        desc:html("
1689   Used to write the term Term on the output stream Stream according
1690   to the current operator declarations.  Atoms and strings are
1691   quoted, operator expressions parenthesised (whenever necessary) and
1692   the (stream-specific or global) print_depth flag is not taken into
1693   account.  The output of writeq/2 can be read back, provided that
1694   the same operator declarations are in effect at write and read
1695   time.
1696<P>
1697   writeq(Term) is equivalent to printf(\"%DIMQvw\", Term)
1698   or write_term(Term, [attributes(full),quoted(true),numbervars(true),
1699   variables(raw),depth(full),transform(false)]).
1700
1701<P>
1702   Note that as usual, the output is buffered, so it may need to be flushed
1703   either by closing the stream, by writing again or by using flush/1.
1704
1705<P>
1706   Note also that although it is possible to print suspensions and external
1707   handles, these are printed in their printed representation as Prolog
1708   terms with functors such as 'BAG' (for bag objects). They will be read
1709   back in as such Prolog terms, rather than as their original type. 
1710
1711<P>
1712"),
1713        args:[
1714            "Stream" : "Stream handle or alias (atom)",
1715            "Term" : "Prolog term."],
1716        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 192 : "Stream is not an output stream.", 193 : "Stream is an illegal stream specification."],
1717        eg:"
1718   Success:
1719      ?- writeq(output, \"string\"),nl(output),
1720         writeq(output, head:-body).
1721      \"string\"
1722      head :- body
1723      yes.
1724
1725      ?- writeq(*(^(1,2),+(3,4))).
1726      1 ^ 2 * (3 + 4)
1727      yes.
1728Error:
1729      writeq(S, a(b,c)).        (Error 4).
1730      writeq(\"string\", a(b,c)). (Error 5).
1731      writeq(9, X + 2).         (Error 192).
1732      writeq(atom, X + 2).      (Error 193).
1733
1734
1735",
1736        see_also:[write / 1, write / 2, writeq / 1]]).
1737
1738
1739:- comment(write_term / 2, [
1740        summary:"The term Term is written to the current output in a format specified by Options",
1741        desc:html("\
1742<P>
1743    This is a generalisation of the predicates write/1, writeq/1, print/1,
1744    display/1, write_canonical/1. It is used to write an arbitrary term
1745    Term onto the current output stream according to the given options.
1746</P><P>
1747    <CODE>write_term(Term, Options)</CODE> is equivalent to
1748    <CODE>write_term(output, Term, Options)</CODE>.
1749    For details see write_term/3.
1750</P>
1751    "),
1752        amode:(write_term(?,++) is det),
1753        args:["Term" : "An arbitrary term",
1754                "Options" : "List of option terms"],
1755        eg:"
1756        Equivalent to write_term(output, Term, Options).
1757        See write_term/3 for examples.
1758",
1759        see_also:[write_term/3, display/1, print/1, printf / 2, write / 1, writeq / 1, write_canonical/1]]).
1760
1761:- comment(write_term / 3, [
1762        summary:"The term Term is written to the output stream Stream in a format specified by Options",
1763        amode:(write_term(+,?,++) is det),
1764        args:[
1765                "Stream" : "Stream handle or alias (atom)",
1766                "Term" : "An arbitrary term",
1767                "Options" : "List of option terms"],
1768        desc:html("\
1769<P>
1770    This is a generalisation of the predicates write/2, writeq/2, print/2,
1771    display/2, write_canonical/2. It is used to write an arbitrary term
1772    Term onto the current output stream according to the given options.
1773    Options is a (possibly empty) list of the following options:
1774</P>
1775<DL>
1776    <DT><STRONG>as(term)</STRONG> -- default</DT><DD><P>
1777        do not assume any particular meaning of the printed term.
1778        </P></DD>
1779
1780    <DT><STRONG>as(clause)</STRONG></DT><DD><P>
1781        print the term as a clause, i.e. clause macros will be taken into
1782        account.
1783        </P></DD>
1784
1785    <DT><STRONG>as(goal)</STRONG></DT><DD><P>
1786        print the term as a goal, i.e. goal write transformations will
1787        be taken into account.
1788        </P></DD>
1789
1790    <DT><STRONG>attributes(none)</STRONG> -- default</DT><DD><P>
1791        do not print any variable attributes, i.e. print attributed
1792        variables like plain variables.
1793        </P></DD>
1794
1795    <DT><STRONG>attributes(pretty)</STRONG></DT><DD><P>
1796        variable attributes are printed using the corresponding print
1797        handlers. See meta_attribute/2.
1798        </P></DD>
1799
1800    <DT><STRONG>attributes(full)</STRONG></DT><DD><P>
1801        print the full contents of all variable attributes.  This is
1802        necessary if the term is to be written out and read back in.
1803        </P></DD>
1804
1805    <DT><STRONG>compact(false)</STRONG> -- default</DT><DD><P>
1806        print extra blank space (around operators, after commas, etc.)
1807        for better readability.
1808        </P></DD>
1809
1810    <DT><STRONG>compact(true)</STRONG></DT><DD><P>
1811        don't print blank space unless necessary.
1812        </P></DD>
1813
1814    <DT><STRONG>depth(0)</STRONG> -- default</DT><DD><P>
1815        print the term only up to a maximum nesting depth determined
1816        by the (stream-specific or global) flag 'print_depth'. See
1817        get_stream_info/3 and get_flag/2.
1818        </P></DD>
1819
1820    <DT><STRONG>depth(MaxDepth)</STRONG></DT><DD><P>
1821        print the term only up to a maximum nesting depth of MaxDepth.
1822        MaxDepth is a positive integer.
1823        </P></DD>
1824
1825    <DT><STRONG>depth(full)</STRONG></DT><DD><P>
1826        do not observe any depth limit and print the whole term. Note that
1827        this will cause looping when the term is cyclic.
1828        </P></DD>
1829
1830    <DT><STRONG>dotlists(false)</STRONG> -- default</DT><DD><P>
1831        write lists in the common square bracket notation, e.g. [1, 2].
1832        </P></DD>
1833
1834    <DT><STRONG>dotlists(true)</STRONG></DT><DD><P>
1835        write lists in the dot functor notation rather than using the
1836        square bracket notation, e.g. .(1, .(2, [])) rather than [1, 2].
1837        </P></DD>
1838
1839    <DT><STRONG>newlines(false)</STRONG> -- default</DT><DD><P>
1840        print newline (NL) characters as escape sequence, when they
1841        occur in quoted atoms or strings.
1842        </P></DD>
1843
1844    <DT><STRONG>newlines(true)</STRONG></DT><DD><P>
1845        print newline (NL) characters as newlines rather than as an
1846        escape sequence, even when they occur in quoted atoms or strings.
1847        This only makes sense together with the quoted(true) option.
1848        </P></DD>
1849
1850    <DT><STRONG>nl(false)</STRONG> -- default</DT><DD><P>
1851	do no add a newline.
1852        </P></DD>
1853
1854    <DT><STRONG>nl(true)</STRONG></DT><DD><P>
1855        print a newline sequence (as with nl/1) after the term.  If this is
1856	used together with the fullstop(true) option, this newline serves
1857	as the blank space after the fullstop.
1858        </P></DD>
1859
1860    <DT><STRONG>fullstop(false)</STRONG> -- default</DT><DD><P>
1861	do no add a fullstop.
1862        </P></DD>
1863
1864    <DT><STRONG>fullstop(true)</STRONG></DT><DD><P>
1865	terminate the term with a fullstop (a dot followed by blank space),
1866	so it can be read back.  The blank space after the dot is a newline
1867	if the nl(true) option is present, otherwise a space character.
1868	If necessary, an extra space will be inserted before the fullstop,
1869	in order to separate it from the end of the term.
1870        </P></DD>
1871
1872    <DT><STRONG>numbervars(false)</STRONG> -- default</DT><DD><P>
1873        do not treat '$VAR'/1 terms specially.
1874        ISO-Prolog compatible.
1875        </P></DD>
1876
1877    <DT><STRONG>numbervars(true)</STRONG></DT><DD><P>
1878        any term of the form '$VAR'(N), where N is a non-negative integer,
1879        is printed as a variable name consisting of a capital letter
1880        followed by a number. The capital letter is the ((N mod 26)+1)st
1881        letter of the alphabet, and the integer is N//26.
1882        If N is an atom, this atom gets printed instead of the term.
1883        ISO-Prolog compatible.
1884        </P></DD>
1885
1886    <DT><STRONG>operators(true)</STRONG> -- default</DT><DD><P>
1887        obey operator declarations. All infix, prefix and postfix operators
1888        are printed in infix, prefix or postfix form, respectively.
1889        </P></DD>
1890
1891    <DT><STRONG>operators(false)</STRONG></DT></DT><DD><P><P>
1892        ignore operator declarations.  All terms are written in the canonical
1893        notation, with a functor followed by the arguments in parentheses.
1894        </P></DD>
1895
1896    <DT><STRONG>portrayed(false)</STRONG> -- default</DT><DD><P>
1897        do not use portray/1,2.
1898        </P></DD>
1899
1900    <DT><STRONG>portrayed(true)</STRONG></DT><DD><P>
1901        call the user-defined predicate portray/1,2 in the way print/1,2
1902        does.
1903        </P></DD>
1904
1905    <DT><STRONG>precedence(Prec)</STRONG></DT><DD><P>
1906	Prec is an integer between 0 and 1200 (default 1200), representing
1907	context operator precedence.  Can be used to force correct
1908	parenthesizing when partial terms are written as arguments of
1909	operators.  The written term will be enclosed in parentheses if
1910	its precedence is higher than Prec.
1911        </P></DD>
1912
1913    <DT><STRONG>quoted(false)</STRONG> -- default</DT><DD><P>
1914        do not print quotes around strings or atoms.
1915        ISO-Prolog compatible.
1916        </P></DD>
1917
1918    <DT><STRONG>quoted(true)</STRONG></DT><DD><P>
1919        quote atoms and strings if necessary.
1920        ISO-Prolog compatible.
1921        </P></DD>
1922
1923    <DT><STRONG>transform(true)</STRONG> -- default</DT><DD><P>
1924        apply portray (write) transformations before printing.
1925        </P></DD>
1926
1927    <DT><STRONG>transform(false)</STRONG></DT><DD><P>
1928        do not apply any portray (write) transformations.
1929        </P></DD>
1930
1931    <DT><STRONG>variables(default)</STRONG> -- default</DT><DD><P>
1932        print variables using their source name, if available.
1933        Otherwise print a system-generated name, which consists of
1934        an underscore and a number, e.g. <CODE>_123</CODE>.
1935        Note that this format cannot be reliably read back, because
1936        different variables may have the same source name.
1937        </P></DD>
1938
1939    <DT><STRONG>variables(raw)</STRONG></DT><DD><P>
1940        print all variables using a system-generated name, which
1941        consists of an underscore and a number, e.g. <CODE>_123</CODE>.
1942        This format is suitable when the term needs to be read back
1943        later.  It makes sure that multiple occurrences of the same
1944        variable have the same name, and different variables have
1945        different names.
1946        </P></DD>
1947
1948    <DT><STRONG>variables(full)</STRONG></DT><DD><P>
1949        print variables using their source name, if available, followed
1950        by a unique number, e.g. Alpha_132. Variables without source
1951        name are printed in the raw format. Since variables with
1952        identical source names are named apart, this format is suitable
1953        when the term needs to be read back later.
1954        </P></DD>
1955
1956    <DT><STRONG>variables(anonymous)</STRONG></DT><DD><P>
1957        print every variable as a simple underscore. Any information about
1958        multiple occurrences of a variable is lost with this format. It is
1959        mainly useful to produce output that can be compared easily with
1960        the output of a different Eclipse session.
1961        </P></DD>
1962
1963</DL>
1964<P>
1965    When an option is omitted altogether, then the corresponding option
1966    settings for the output stream will come into effect (see
1967    set_stream_property/3, get_stream_info/3, open/4).
1968</P>
1969    The following additional options are supported for compatibility
1970    with other Prolog systems:
1971<DL>
1972    <DT><STRONG>ignore_ops(true)</STRONG></DT><DD><P>
1973        the same as [operators(false),dotlists(true),transform(false)].
1974        ISO-Prolog compatibility.
1975        </P></DD>
1976
1977    <DT><STRONG>ignore_ops(false)</STRONG></DT><DD><P>
1978        the same as [operators(true),dotlists(false),transform(true)].
1979        ISO-Prolog compatibility.
1980        </P></DD>
1981
1982    <DT><STRONG>max_depth(0)</STRONG></DT><DD><P>
1983        the same as depth(full).
1984        SICStus-Prolog compatibility.
1985        </P></DD>
1986
1987    <DT><STRONG>max_depth(N)</STRONG></DT><DD><P>
1988        the same as depth(N).
1989        SICStus-Prolog compatibility.
1990        </P></DD>
1991
1992    <DT><STRONG>priority(Prec)</STRONG></DT><DD><P>
1993        the same as precedence(Prec).
1994        SICStus/SWI-Prolog compatibility.
1995        </P></DD>
1996</DL>
1997    The correspondence between write_term/2,3 and the other output predicates
1998    is as follows:
1999<DL>
2000    <DT>write(T)</DT><DD><P>
2001        write_term(T, [numbervars(true)])
2002        </P></DD>
2003
2004    <DT>writeln(T)</DT><DD><P>
2005        write_term(T, [numbervars(true),nl(true)])
2006        </P></DD>
2007
2008    <DT>writeq(T)</DT><DD><P>
2009        write_term(T, [variables(raw),attributes(full),transform(false),
2010        numbervars(true),quoted(true),depth(full)])
2011        </P></DD>
2012
2013    <DT>write_canonical(T)</DT><DD><P>
2014        write_term(T, [variables(raw),attributes(full),transform(false),
2015        quoted(true),depth(full),dotlist(true),operators(false)])
2016        </P></DD>
2017
2018    <DT>print(T)</DT><DD><P>
2019        write_term(T, [portrayed(true),numbervars(true)])
2020        </P></DD>
2021
2022    <DT>display(T)</DT><DD><P>
2023        write_term(T, [dotlist(true),operators(false)])
2024        </P></DD>
2025</DL>
2026<P>
2027   Note that as usual, the output is buffered, so it may need to be flushed
2028   either by closing the stream, by writing again or by using flush/1.
2029</P>
2030"),
2031        exceptions:[4 : "Stream is not instantiated.",
2032                5 : "Stream is not an atom or a stream handle.",
2033                5 : "Options is not a list of compound terms.",
2034                6 : "Options list contains a unrecognised option.",
2035                192 : "Stream is not an output stream.",
2036                193 : "Stream is an illegal stream specification."],
2037        eg:"
2038        ?- write_term(*(^(1,2),+(3,4)), []).
2039        1 ^ 2 * (3 + 4)
2040
2041        ?- write_term(*(^(1,2),+(3,4)), [operators(false)]).
2042        *(^(1, 2), +(3, 4))
2043
2044        ?- write_term(['a-b',\"cd\"], []). 
2045        [a-b, cd]
2046
2047        ?- write_term(['a-b',\"cd\"], [quoted(true)]).
2048        ['a-b', \"cd\"]
2049
2050        ?- write_term(['a-b',\"cd\"], [quoted(true),dotlists(true)]).
2051        .('a-b', .(\"cd\", []))
2052
2053        ?- write_term(hello, [fullstop(true)]).
2054	hello.
2055
2056        ?- write_term(***, [fullstop(true)]).
2057	*** .
2058
2059        ?- write('X = '), write_term(a=b, [precedence(699)]).
2060	X = (a = b)
2061",
2062        see_also:[write_term/2, display/2, print/2, printf / 3, write / 2,
2063        writeln/2, writeq / 2, write_canonical/2, get_stream_info/3, get_flag/2]]).
2064
2065
2066
2067
2068:- comment(read_term / 2, [
2069        summary:"Read a whole term in ECLiPSe syntax from the current input stream, according to Options",
2070        desc:html("\
2071<P>
2072    This is a generalisation of the predicates read/1 and readvar/3.
2073</P><P>
2074    <CODE>read_term(Term, Options)</CODE> is equivalent to
2075    <CODE>read_term(output, Term, Options)</CODE>.
2076    For details see read_term/3.
2077</P>
2078    "),
2079        amode:(read_term(-,+) is semidet),
2080        fail_if:"Fails if a syntax error was detected and no term could be read",
2081        args:["Term" : "An term, usually a variable",
2082                "Options" : "List of option terms"],
2083        exceptions:[
2084                5 : "Options is not a list of compound terms.",
2085                6 : "Options list contains a unrecognised option."],
2086        eg:"
2087        Equivalent to read_term(output, Term, Options).
2088        See read_term/3 for examples.
2089",
2090        see_also:[read_term/3, read/1, read/2, readvar/3, library(numbervars)]]).
2091
2092
2093
2094:- comment(read_term / 3, [
2095        summary:"Read a whole term in ECLiPSe syntax from the input stream Stream, according to Options",
2096        desc:html("\
2097<P>
2098    This is a generalisation of the predicates read/2 and readvar/3.
2099    Options is a (possibly empty) list of the following options:
2100</P>
2101<DL>
2102    <DT><STRONG>variables(Vars)</STRONG></DT><DD><P>
2103        returns a duplicate-free list of all the variables in the term
2104        that has been read (including anonymous variables).
2105        </P></DD>
2106
2107    <DT><STRONG>variable_names(VarsNames)</STRONG></DT><DD><P>
2108        returns a duplicate-free list of structures of the form
2109        Name=Var, where Var is a named (non-anonymous) variable which
2110        occurs in the term that has been read, and Name is an atom,
2111        representing the source name.  </P></DD>
2112
2113    <DT><STRONG>singletons(VarsNames)</STRONG></DT><DD><P>
2114        returns a list of structures of the form Name=Var, where Var
2115        is a named (non-anonymous) variable which occurs only once in
2116        the term that has been read, and Name is an atom, representing
2117        the source name.  </P></DD>
2118
2119</DL>
2120"),
2121        amode:(read_term(+,-,++) is semidet),
2122        fail_if:"Fails if a syntax error was detected and no term could be read",
2123        args:[
2124                "Stream" : "Stream handle or alias (atom)",
2125                "Term" : "An term, usually a variable",
2126                "Options" : "List of option terms"],
2127        exceptions:[4 : "Stream is not instantiated.",
2128                5 : "Stream is not an atom or a stream handle.",
2129                5 : "Options is not a list of compound terms.",
2130                6 : "Options list contains a unrecognised option.",
2131                192 : "Stream is not an input stream.",
2132                193 : "Stream is an illegal stream specification."],
2133        eg:"
2134        ?- read_term(T, []).
2135         foo(X,_,bar(X,Y,_Z)).
2136
2137        T = foo(X, _255, bar(X, Y, _Z))
2138
2139
2140        ?- read_term(T, [variable_names(VN)]).
2141         foo(X,_,bar(X,Y,_Z)).
2142
2143        T = foo(X, _260, bar(X, Y, _Z))
2144        VN = ['X' = X, 'Y' = Y, '_Z' = _Z]
2145
2146
2147        ?- read_term(T, [variables(V),variable_names(VN),singletons(S)]).
2148         foo(X,_,bar(X,Y,_Z)).
2149
2150         T = foo(X, _278, bar(X, Y, _Z))
2151         V = [X, _278, Y, _Z]
2152         VN = ['X' = X, 'Y' = Y, '_Z' = _Z]
2153         S = ['_Z' = _Z, 'Y' = Y]
2154",
2155        see_also:[read_term/2, readvar/3, read/1, read / 2, set_stream_property/3]]).
2156
2157
2158:- comment(read_annotated / 2, [
2159        summary:"Read term with type and source position information",
2160        amode:(read_annotated(+,-) is semidet),
2161        desc:html("<P>\
2162    This is defined as
2163<PRE>
2164    read_annoated(Stream, AnnTerm) :-
2165        read_annotated(Stream _Term, AnnTerm).
2166</PRE>
2167        </P>"),
2168        args:[
2169                "Stream" : "Stream handle or alias (atom)",
2170                "AnnTerm" : "Variable or term"],
2171        fail_if:"Fails if a syntax error was detected and no term could be read",
2172        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 190 : "End of file was encountered before reading any character.", 192 : "Stream is not an input stream.", 193 : "Stream is an illegal stream specification.", 198 : "Trying to read even after the error 190 was raised."],
2173        see_also:[read_annotated/3]]).
2174
2175:- comment(read_annotated / 3, [
2176        summary:"Read term with type and source position information",
2177        amode:(read_annotated(+,-,-) is semidet),
2178        desc:html("<P>\
2179    Reads the next input term (up to the end of file, or up to a fullstop)
2180    from from the input stream Stream, and returns this term as Term, and
2181    a descriptor AnnTerm.  AnnTerm is structurally similar to Term and
2182    contains all information about the term, plus additional type information,
2183    variable names, and source position annotations for all subterms.
2184</P><P>
2185    The structure of the descriptive terms is as follows:
2186    <PRE>
2187        :- export struct(annotated_term(
2188                term,                   % var, atomic or compound
2189                type,                   % term type (see below)
2190                file,                   % source file name (atom)
2191                line,                   % source line (integer)
2192                from, to                % source position (integers)
2193                ...
2194        )).
2195    </PRE>
2196</P><P>
2197    The type-field describes the type of the parsed term and is one of
2198    the following:
2199<PRE>
2200    integer
2201    float
2202    rational
2203    breal
2204    atom
2205    string
2206    compound            term is compound (with annotated subterms)
2207    anonymous           term is a variable (was anonymous (_) in source)
2208    var(NameAtom)       term is a variable (with the given source name)
2209    var                 term is a variable (introduced by macro expansion)
2210    end_of_file         end of file was read (term is end_of_file)
2211</PRE>
2212    These type names correspond to the ones used in type_of/2, except that
2213    they convey additional information about variables and end_of_file..
2214</P><P>
2215    In the case of atomic terms and variables, the term-field simply
2216    contains the plain parsed term. For compound terms, the term-field
2217    contains a structure whose functor is the functor of the plain term,
2218    but whose arguments are annotated versions of the plain term arguments.
2219</P><P>
2220    E.g. the source term
2221<PRE>
2222        3
2223</PRE>
2224    is parsed as
2225<PRE>
2226        annotated_term(3, integer, ...)
2227</PRE>
2228</P><P>
2229    The source term
2230<PRE>
2231        foo(bar, X, _, 3)
2232</PRE>
2233    is parsed as
2234<PRE>
2235        annotated_term(foo(
2236            annotated_term(bar, atom, ...),
2237            annotated_term(X, var('X'), ...),
2238            annotated_term(_, anonymous, ...),
2239            annotated_term(3, integer, ...)),
2240        compound, ...)
2241</PRE>
2242</P><P>
2243    The source term
2244<PRE>
2245        [1,2]
2246</PRE>
2247    is parsed as
2248<PRE>
2249        annotated_term(.(
2250            annotated_term(1, integer, ...),
2251                annotated_term(.(
2252                        annotated_term(2, integer, ...),
2253                        annotated_term([], atom, ...)),
2254                    compound, ...)),
2255            compound, ...)
2256</PRE>
2257</P><P>
2258The file/line/from/to-fields of an annotated term describe the
2259\"source position\" of the term.  The fields contain:
2260<DL>
2261<DT>file</DT><DD>
2262    The canonical file name of the source file (an atom), or the
2263    empty atom '' if the source is not a file or not known.
2264</DD>
2265<DT>line</DT><DD>
2266    The line number in the source stream (positive integer).
2267</DD>
2268<DT>from, to</DT><DD>
2269    The exact term position as integer offsets in the source stream,
2270    starting at from and ending at to-1.
2271</DD>
2272</DL>
2273The source position of a whole (sub)term is defined as the source position
2274of the unique token (sometimes token pair) which represents that (sub)term.
2275The representing token (pair) is defined as follows:
2276<UL>
2277<LI>atoms, strings and unsigned numbers are represented by their
2278    corresponding IDENTIFIER, NUMBER or STRING token.
2279
2280<LI>signed numbers are represented by two consecutive tokens (sign+number)
2281
2282<LI>compound terms in canonical notation are represented by two consecutive
2283    tokens (functor and opening parenthesis)
2284
2285<LI>compound terms in operator syntax are represented by the operator's
2286    IDENTIFIER token
2287
2288<LI>lists:
2289<P>
2290  a proper list [a,b] has subterms
2291        <PRE>
2292        [a,b]   represented by the [ token,
2293        [b]     represented by the , token,
2294        []      represented by the ] token,
2295        a       represented by itself,
2296        b       represented by itself.
2297        </PRE>
2298  a general list [a,b|T] has subterms
2299        <PRE>
2300        [a,b|T] represented by the [ token,
2301        [b|T]   represented by the , token,
2302        T       represented by itself,
2303        a       represented by itself,
2304        b       represented by itself.
2305        </PRE>
2306  Note that the | and ] tokens do not represent any term.
2307</P>
2308
2309<LI>special notations:
2310<P>
2311  {X}
2312<PRE>
2313        '{}'(X) represented by the { token,
2314        X       represented by itself
2315</PRE>
2316  X[Args]
2317<PRE>
2318        subscript(X, [...]) represented by the [ token,
2319        X,Args  represented by themselves
2320</PRE>
2321  X{Args}
2322<PRE>
2323        'with attributes'(X,[Args]) represented by { token,
2324        X,Args  represented by themselves
2325</PRE>
2326  a{Args}
2327<PRE>
2328        with(a,[Args])  represented by the { token
2329        a,Args  represented by themselves
2330</PRE>
2331  X(Args)
2332<PRE>
2333        apply(X,[Args]) represented by the ( token
2334        X,Args  represented by themselves
2335</PRE>
2336</P>
2337</UL>
2338<P>
2339    Terms that were read from source may be subject to macro expansion
2340    (see macro/3, expand_macros/2).  In that case, term components
2341    that were introduced by the expansion may not have an exactly
2342    corresponding item in the source (but will usually inherit a
2343    meaningful, though not necessarily unique, source position). 
2344    Moreover, variables that were newly introduced by the expansion
2345    have a type-field of 'var' without name information.  Also,
2346    'anonymous' variables may have more than one occurrence after expansion.
2347</P><P>
2348    If only end of file is read, the event 190 is raised. The default
2349    handler unifies Term with an annotated term of the form
2350    annotated_term{term:end_of_file,type:end_of_file}, and the source
2351    location is the last position in the file.
2352</P><P>
2353    The default action for syntax errors is to print a warning and fail.
2354</P>
2355"),
2356        args:[
2357                "Stream" : "Stream handle or alias (atom)",
2358                "Term" : "Variable or term",
2359                "AnnTerm" : "Variable or term"],
2360        fail_if:"Fails if a syntax error was detected and no term could be read",
2361        exceptions:[4 : "Stream is not instantiated.", 5 : "Stream is not an atom or a stream handle.", 190 : "End of file was encountered before reading any character.", 192 : "Stream is not an input stream.", 193 : "Stream is an illegal stream specification.", 198 : "Trying to read even after the error 190 was raised."],
2362        eg:"
2363?- read_annotated(input,T,AT).
2364 33.
2365
2366T = 33
2367AT = annotated_term(33, integer, user, 1, 0, 2)
2368Yes (0.00s cpu)
2369
2370
2371?- read_annotated(input,T,AT).
2372 foo(bar).
2373
2374T = foo(bar)
2375AT = annotated_term(foo(
2376            annotated_term(bar, atom, user, 2, 8, 11)
2377        ), compound, user, 2, 4, 8)
2378Yes (0.00s cpu)
2379
2380
2381?- read_annotated(input,X).
2382 a + 3.
2383
2384T = a + 3
2385AT = annotated_term(
2386            annotated_term(a, atom, user, 3, 14, 15)
2387        +   annotated_term(3, integer, user, 3, 18, 19),
2388        compound, user, 3, 16, 17)
2389Yes (0.00s cpu)
2390
2391
2392?- read_annotated(input,X).
2393 [a,b].
2394
2395T = [a, b]
2396AT = annotated_term([
2397            annotated_term(a, atom, user, 4, 22, 23)|
2398            annotated_term([
2399                    annotated_term(b, atom, user, 4, 24, 25)|
2400                    annotated_term([], atom, user, 4, 25, 26)
2401                ], compound, user, 4, 23, 24)
2402        ], compound, user, 4, 21, 22)
2403Yes (0.00s cpu)
2404",
2405        see_also:[read_annotated/2, read / 1, readvar / 3, read_token / 2, read_token / 3,
2406        expand_macros/2, macro/3, type_of/2]]).
2407
2408