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, "Strings and Atoms").
24:- comment(summary, "Built-ins to create, convert and decompose strings and atoms").
25:- comment(categories, ["Built-In Predicates"]).
26
27
28%----------------------------------------------------------------------
29:- tool(number_string / 2).
30:- comment(number_string / 2, [
31	summary:"Conversion between any number and a string.",
32	amode:(number_string(+,-) is det),
33	amode:(number_string(-,+) is semidet),
34	desc:html("
35   If String is instantiated, its contents is interpreted as a number which
36   is in turn unified with Number.
37<P>
38   If Number is instantiated and String is a variable, String is bound to
39   the textual representation of the number as writeq/1 would produce it.
40<P>
41   If String does not represent a number, then number_string/2 fails.
42   The string must not contain leading or trailing white space.  For the
43   exact number token syntax, see the User Manual Syntax Appendix, and
44   note that details may depend on the context module's syntax options.
45<P>
46"),
47	args:["Number" : "Number or variable.", "String" : "String or variable."],
48	fail_if:"Fails if String does not represent a number",
49	exceptions:[5 : "Number is instantiated, but not to an number.", 5 : "String is instantiated, but not to a string.", 4 : "Both arguments are free variables (non-coroutine mode only)."],
50	eg:"
51   Success:
52   number_string(1989,X).       (gives X = \"1989\").
53   number_string(-7,X).         (gives X = \"-7\").
54   number_string(124.5,X).      (gives X = \"124.5\").
55   number_string(X,\"+12\").      (gives X = 12).
56   number_string(X,\"-7\").       (gives X = -7).
57   number_string(N,\"123.4\").     (gives N = 123.4).
58   number_string(3.0,\"3.0\").
59   number_string(3.0,\"+3.00\").
60   Fail:
61   number_string(N,\"- 15\").
62   number_string(N,\" +15\").
63   number_string(N,\"2 \").
64   number_string(N,\".5\").
65   number_string(N,\"Abcd\").
66   number_string(222,\"123\").
67   Error:
68   number_string(N,S).          (Error 4).
69   number_string(a,\"12\").       (Error 5).
70   number_string(N,1234).       (Error 5).
71
72
73",
74	see_also:[atomics_to_string / 2, term_string / 2, atom_string / 2, number / 1, sprintf/3, split_string / 4]]).
75
76
77%----------------------------------------------------------------------
78:- comment(integer_atom / 2, [
79	summary:"Conversion between an integer and an atom.
80It is more efficient to use number_string/2 wherever possible.
81
82",
83	amode:(integer_atom(+,-) is det),
84	amode:(integer_atom(-,+) is semidet),
85	desc:html("   If Integer is instantiated, converts it to its associated atomic
86   representation Atom.
87
88<P>
89   If Atom is instantiated, converts it to its integer form Integer.
90
91<P>
92   Atom may contain only digits possibly preceded by a + or a -.
93
94<P>
95"),
96	args:["Integer" : "Integer or variable.", "Atom" : "Atom or variable."],
97	fail_if:"Fails if Atom does not represent an integer",
98	exceptions:[5 : "Integer is instantiated, but not to an integer.", 5 : "Atom is instantiated, but not to an atom.", 4 : "Both arguments are free variables (non-coroutine mode only)."],
99	eg:"
100   Success:
101   integer_atom(1989,X).       (gives X = '1989').
102   integer_atom(X,'+12').      (gives X = 12).
103   integer_atom(-7,X).         (gives X = '-7').
104   integer_atom(X,'-7').       (gives X = -7).
105   integer_atom(N,'1234').     (gives N = 1234).
106   Fail:
107   integer_atom(I,'- 15').
108   integer_atom(I,' +15').
109   integer_atom(I,'2 ').
110   integer_atom(1234,'Abcd').
111   integer_atom(222,'123').
112   integer_atom(x,'+12').
113   Error:
114   integer_atom(A,B).          (Error 4).
115   integer_atom(124.5,X).      (Error 5).
116   integer_atom(N,1234).       (Error 5).
117
118
119
120",
121	see_also:[integer / 1, atom / 1, number_string / 2, sprintf/3]]).
122
123
124%----------------------------------------------------------------------
125:- comment(string_codes / 2, [
126	summary:"Codes is a list whose elements are the character codes of the characters in the string",
127	amode:(string_codes(+,-) is det),
128	amode:(string_codes(-,+) is det),
129	desc:html("
130   This predicate performs the mapping between a string and the
131   corresponding list of character codes.
132<P>
133   If String is instantiated, unifies Codes with the list whose elements
134   are the character codes for the character in the string.
135<P>
136   If Codes is instantiated, unifies String with the string composed from
137   the character codes given by the list elements.
138<P>
139"),
140    args:["String" : "String or variable.",
141	  "Codes" : "Codes of integer character codes and/or variables, or simply a variable."],
142    exceptions:[5 : "String is not a string.",
143	5 : "Codes is not a proper list.",
144	5 : "Codes contains non-integer elements.",
145	6 : "Condes contains integers that are not valid character codes.",
146	4 : "Both String and Codes are nonground (non-coroutine mode only)."],
147    eg:"
148   Success:
149   string_codes(S,[65,98,99]).          (gives S=\"Abc\").
150   string_codes(\"abc\",L).               (gives L=[97,98,99]).
151   string_codes(\"abc\",[97,A,99]).       (gives A=98).
152   string_codes(S,[127]).               (gives S=\"\\177\").
153   string_codes(\"abc\",[97|A]).          (gives A=[98,99]).
154   Fail:
155   string_codes(\"abc\",[98,99,100]).
156   Error:
157   string_codes(S,[A|[128]]).           (Error 4).
158   string_codes(S,[1|A]).               (Error 4).
159   string_codes('string',L).            (Error 5).
160   string_codes(S,\"list\").              (Error 5).
161   string_codes('string',[128]).        (Error 5).
162   string_codes(S,[\"B\"]).               (Error 5).
163   string_codes(S,[256]).               (Error 6).
164",
165	see_also:[string_code/3, string_chars/2, string_list/3, char_code/2]]).
166
167
168%----------------------------------------------------------------------
169:- comment(string_chars / 2, [
170	summary:"Chars is a list whose elements are the single-character atoms of the characters in the string",
171	amode:(string_chars(+,-) is det),
172	amode:(string_chars(-,+) is det),
173	desc:html("
174   This predicate performs the mapping between a string and the
175   corresponding list of single-character atoms.
176<P>
177   If String is instantiated, unifies Chars with the list whose elements
178   are the single-character atoms for the character in the string.
179<P>
180   If Chars is instantiated, unifies String with the string composed from
181   the single-character atoms given by the list elements.
182<P>
183"),
184    args:["String" : "String or variable.",
185	  "Chars" : "Chars of integer character codes and/or variables, or simply a variable."],
186    exceptions:[5 : "String is not a string.",
187	5 : "Chars is not a proper list.",
188	5 : "Chars contains non-atom elements.",
189	6 : "Condes contains atoms that do not represent characters.",
190	4 : "Both String and Chars are nonground (non-coroutine mode only)."],
191    eg:"
192   Success:
193   string_chars(S,['A',b,c]).           (gives S=\"Abc\").
194   string_chars(\"abc\",L).               (gives L=[a,b,c]).
195   string_chars(\"abc\",[a,A,c]).         (gives A=b).
196   string_chars(S,['\177']).                (gives S=\"\\177\").
197   string_chars(\"abc\",[a|A]).           (gives A=[b,c]).
198   Fail:
199   string_chars(\"abc\",[b,c,d]).
200   Error:
201   string_chars(S,[A|[128]]).           (Error 4).
202   string_chars(S,[1|A]).               (Error 4).
203   string_chars('string',L).            (Error 5).
204   string_chars(S,\"list\").              (Error 5).
205   string_chars('string',[128]).        (Error 5).
206   string_chars(S,[\"B\"]).               (Error 5).
207   string_chars(S,[256]).               (Error 6).
208",
209	see_also:[string_code/3, string_codes/2, string_list/3, char_code/2]]).
210
211
212%----------------------------------------------------------------------
213:- comment(string_list / 2, [
214	summary:"List is a list whose elements are the integer codes of the bytes in the string",
215	amode:(string_list(+,-) is det),
216	amode:(string_list(-,+) is det),
217	desc:html("
218   This predicate performs conversion between a byte string and the
219   corresponding list of integers in the range 0..255.
220<P>
221   If String is instantiated, unifies List with the list whose elements are
222   the integer codes for the bytes in the string.
223<P>
224   If List is instantiated, unifies String with the string composed from
225   the bytes given by the list elements in range 0..255.
226<P>
227"),
228	args:["String" : "String or variable.", "List" : "List of integers (in the range 0 to 255) and/or variables, or simply a variable."],
229	exceptions:[5 : "String is neither a string nor a variable.", 5 : "List is neither a list nor a variable.", 6 : "One (or more) elements of List are not integers in the range    0 to 255.", 4 : "Neither String or List are ground (non-coroutine mode only)."],
230	eg:"
231   Success:
232   string_list(S,[65,98,99]).          (gives S=\"Abc\").
233   string_list(\"abc\",L).               (gives L=[97,98,99]).
234   string_list(\"abc\",[97,A,99]).       (gives A=98).
235   string_list(S,[127]).               (gives S=\"\\177\").
236   string_list(\"abc\",[97|A]).          (gives A=[98,99]).
237   Fail:
238   string_list(\"abc\",[98,99,100]).
239   Error:
240   string_list(S,[A|[128]]).           (Error 4).
241   string_list(S,[1|A]).               (Error 4).
242   string_list('string',L).            (Error 5).
243   string_list(S,\"list\").              (Error 5).
244   string_list('string',[128]).        (Error 5).
245   string_list(S,[\"B\"]).               (Error 5).
246   string_list(S,[256]).               (Error 6).
247
248
249
250",
251	see_also:[string_list/3, string_codes/2, string_chars/2]]).
252
253
254%----------------------------------------------------------------------
255:- comment(string_list / 3, [
256	index:["utf8","unicode","chars","codes","octet","bytes"],
257	summary:"Conversion between string in different encodings and a character list",
258	amode:(string_list(+,-,+) is det),
259	amode:(string_list(-,+,+) is det),
260	desc:html("\
261   This predicate performs conversion between a string encoded in Format
262   and a list of the corresponding character representations.
263<P>
264   If String is instantiated, it is must be a valid string in the encoding
265   format specified by Format.  It is then decoded and List is unified with
266   a list of the corresponding character representations.
267<P>
268   If List is instantiated, it is must contain character representations
269   that are valid for the encoding format specified by Format.  These
270   characters are then encoded into a string which is unified with String.
271<P>
272   Currently supported formats are:
273<DL>
274<DT><STRONG>bytes</STRONG> or <STRONG>octet</STRONG><DD>
275    Every byte in the string corresponds to a list integer in the range 0..255.
276<DT><STRONG>chars</STRONG><DD>
277    Every character in the string corresponds to a single-character atom
278    in the list.  This format assumes a default character encoding.
279<DT><STRONG>codes</STRONG><DD>
280    Every character in the string corresponds to an integer character code
281    in the list.  This format assumes a default character encoding.
282<DT><STRONG>utf8</STRONG><DD>
283    The string is encoded in UTF-8 format and the list can contain integers
284    in the range 0..2^31-1.
285</DL>
286<P>
287   Note that string_list/2 can be defined as:
288<PRE>
289	string_list(S, L) :- string_list(S, L, bytes).
290</PRE>
291"),
292	args:["String" : "String or variable.",
293	    "List" : "A variable or a list of integers and/or variables.",
294	    "Format":"An atom."],
295	exceptions:[
296	    4 : "Format is not instantiated.",
297	    4 : "Neither String nor List are ground.",
298	    5 : "String is neither a string nor a variable.",
299	    5 : "List is neither a list nor a variable.",
300	    5 : "Format is not an atom.",
301	    6 : "One (or more) elements of List are not of the type"
302	    	" corresponding to Format.",
303	    6 : "Format is not a valid format specification.",
304	    6 : "One (or more) elements of List are not integers or atoms"
305	    	" in the valid range for Format."],
306
307	eg:"
308    [eclipse 1]: string_list(S,[65,66,67],bytes).
309    S = \"ABC\"
310    yes.
311
312    [eclipse 2]: string_list(S, [65,66,67], utf8).
313    S = \"ABC\"
314    yes.
315
316    [eclipse 3]: string_list(S, [65, 0, 700, 2147483647], bytes).
317    out of range in string_list(S, [65, 0, 700, 2147483647])
318
319    [eclipse 4]: string_list(S, [65, 0, 700, 2147483647], utf8).
320    S = \"A\\000\\312\\274\\375\\277\\277\\277\\277\\277\"
321    yes.
322",
323	see_also:[string_list/2, write/2, read_string/4]]).
324
325
326%----------------------------------------------------------------------
327:- comment(atom_string / 2, [
328	summary:"Conversion between an atom and a string.
329
330",
331	amode:(atom_string(+,-) is det),
332	amode:(atom_string(-,+) is det),
333	desc:html("   If Atom is instantiated, converts it to a string String.
334
335<P>
336   If String is instantiated, converts it to an atom Atom.
337
338<P>
339"),
340	args:["Atom" : "Atom or variable.", "String" : "String or variable."],
341	exceptions:[5 : "Atom is instantiated, but not to an atom.", 5 : "String is instantiated, but not to a string.", 4 : "Neither Atom nor String are instantiated (non-coroutine mode    only)."],
342	eg:"
343   Success:
344   atom_string('Tom',\"Tom\").
345   atom_string(tom,X).                 (gives X=\"tom\").
346   atom_string(X,\"4\").                 (gives X='4').
347   Fail:
348   atom_string('jo',\"joe\").
349   Error:
350   atom_string(X,Y).                   (Error 4).
351   atom_string(4,\"4\").                 (Error 5).
352   atom_string(tom,'tom').             (Error 5).
353
354
355
356",
357	see_also:[append_strings / 3, integer_atom / 2, sprintf/3, term_string / 2]]).
358
359
360%----------------------------------------------------------------------
361:- comment(string_concat / 3, [
362	summary:"Succeeds if String3 is the concatenation of String1 and String2.
363
364",
365	amode:(string_concat(+,+,-) is det),
366	amode:(string_concat(+,-,+) is det),
367	amode:(string_concat(-,+,+) is det),
368	amode:(string_concat(-,-,+) is multi),
369	desc:html("
370   Succeeds if String3 is the concatenation of String1 and String2.
371<P>
372   Used to find all possible solutions for the concatenation of String1 and
373   String2 to make String3.
374<P>
375   Note that if String1 and String2 are instantiated, it is more efficient
376   to use the predicate concat_strings/3.
377<P>
378   This predicate is an alias for append_strings/3.
379"),
380	args:["String1" : "String or variable.", "String2" : "String or variable.", "String3" : "String or variable."],
381	exceptions:[5 : "One (or more) of the arguments is instantiated, but not to a    string.", 4 : "String3 and at least one other argument are uninstantiated."],
382	eg:"
383Success:
384      string_concat(\"a\",B,\"abc\"). (gives B = \"bc\").
385      string_concat(A,B,\"a\").     (gives A=\"\"  B=\"a\";
386                                          A=\"a\" B=\"\").
387Fail:
388      string_concat(\"a\",\"b\",\"abc\").
389Error:
390      string_concat(A,\"bc\",C).        (Error 4).
391      string_concat(5,B,C).           (Error 5).
392      string_concat(A,'me',\"meme\").   (Error 5).
393
394
395
396",
397	see_also:[concat_strings / 3, atomics_to_string / 2, atomics_to_string / 3, sprintf/3]]).
398
399
400%----------------------------------------------------------------------
401:- comment(append_strings / 3, [
402	summary:"Succeeds if String3 is the concatenation of String1 and String2.
403
404",
405	amode:(append_strings(+,+,-) is det),
406	amode:(append_strings(+,-,+) is det),
407	amode:(append_strings(-,+,+) is det),
408	amode:(append_strings(-,-,+) is multi),
409	desc:html("   Succeeds if String3 is the concatenation of String1 and String2.
410
411<P>
412   Used to find all possible solutions for the concatenation of String1 and
413   String2 to make String3.
414
415<P>
416   Note that if String1 and String2 are instantiated, it is more efficient
417   to use the predicate concat_strings/3.
418
419<P>
420   This predicate is an alias for string_concat/3.
421"),
422	args:["String1" : "String or variable.", "String2" : "String or variable.", "String3" : "String or variable."],
423	exceptions:[5 : "One (or more) of the arguments is instantiated, but not to a    string.", 4 : "String3 and at least one other argument are uninstantiated."],
424	eg:"
425Success:
426      append_strings(\"a\",B,\"abc\"). (gives B = \"bc\").
427      append_strings(A,B,\"a\").     (gives A=\"\"  B=\"a\";
428                                          A=\"a\" B=\"\").
429Fail:
430      append_strings(\"a\",\"b\",\"abc\").
431Error:
432      append_strings(A,\"bc\",C).        (Error 4).
433      append_strings(5,B,C).           (Error 5).
434      append_strings(A,'me',\"meme\").   (Error 5).
435
436
437
438",
439	see_also:[string_concat/3, concat_strings / 3, atomics_to_string / 2, atomics_to_string / 3, sprintf/3]]).
440
441
442%----------------------------------------------------------------------
443:- comment(substring / 4, [
444	summary:"Succeeds if String2 is the substring of String1 starting at position
445Position and of length Length.
446
447",
448	amode:(substring(+, +, +, -) is semidet),
449	amode:(substring(+, +, -, +) is semidet),
450	amode:(substring(+, +, -, -) is nondet),
451	amode:(substring(+, -, +, -) is nondet),
452	amode:(substring(+, -, -, +) is nondet),
453	amode:(substring(+, -, -, -) is multi),
454	desc:html("   Succeeds if String2 is a substring of String1 starting at position
455   Position and of length Length.
456
457<P>
458   On backtracking, all such substrings are found.
459
460<P>
461   The first character of a string is at position 1.
462
463<P>
464Note
465   If String1 and String2 are instantiated, it is more efficient to use the
466   predicates substring/3 and/or string_length/2.
467
468<P>
469"),
470	args:["String1" : "String.", "Position" : "Integer (from 1 upwards) or variable.", "Length" : "Integer (from 0 upwards) or variable.", "String2" : "String or variable."],
471	fail_if:"String1 does not have a substring at the required position and/or of the required length, or String2 does not occur within String1",
472	exceptions:[5 : "String1 is instantiated, but not to a string.", 5 : "String2 is neither a string nor a variable.", 5 : "Either (or both) of Position or Length are neither integers    nor variables.", 4 : "String1 is not instantiated."],
473	eg:"
474Success:
475  substring(\"abcabc\",3,1,\"c\").
476  substring(\"abcabc\",6,1,\"c\").
477  substring(\"abcabc\",P,1,\"c\"). (gives P=3; P=6).
478  substring(\"abcabc\",3,3,S).   (gives S=\"cab\").
479  substring(\"abc\",P,L,\"b\").    (gives P=2, L=1).
480
481  [eclipse]: substring(\"ab\",P,1,S).
482  P=1
483  S=\"a\"     More? (;)
484  P=2
485  S=\"b\"
486  yes.
487
488  [eclipse]: substring(\"ab\",1,L,S).
489  L=0
490  S=\"\"      More? (;)
491  L=1
492  S=\"a\"     More? (;)
493  L=2
494  S=\"ab\"
495  yes,
496
497  [eclipse]: substring(\"ab\",P,L,S), writeq((P,L,S)), nl, fail.
498  1 , 0 , \"\"            % on backtracking, returns all
499  1 , 1 , \"a\"           %   substrings of String1.
500  1 , 2 , \"ab\"
501  2 , 0 , \"\"
502  2 , 1 , \"b\"
503  3 , 0 , \"\"
504  no (more) solution.
505
506Fail:
507  substring(\"joey\",P,L,\"joy\").
508  substring(\"joey\",P,2,\"joe\").
509
510Error:
511  substring(S1,P,L,S2).                (Error 4).
512  substring(S1,1,2,\"bc\").              (Error 4).
513  substring(S1,1,2,'str').             (Error 4).
514  substring('string',2,3,S2).          (Error 5).
515  substring(\"string\",2,3,'str').       (Error 5).
516  substring(\"string\",0,L,S2).          (Error 6).
517  substring(\"string\",1,-1,S2).         (Error 6).
518
519
520
521",
522	see_also:[substring / 3, substring / 5, string_length / 2, split_string / 4]]).
523
524
525%----------------------------------------------------------------------
526:- comment(sub_string / 5, [
527	summary:"Succeeds if SubString is a substring of String, with 
528    length Length, preceded by Before, and followed by After characters",
529	desc:html("This is a compatibility alias for substring/5."),
530	amode:(sub_string(+, +, +, -, -) is semidet),
531	amode:(sub_string(+, -, +, +, -) is semidet),
532	amode:(sub_string(+, +, -, +, -) is semidet),
533	amode:(sub_string(+, +, -, -, +) is semidet),
534	amode:(sub_string(+, -, -, +, +) is semidet),
535	amode:(sub_string(+, +, -, -, -) is nondet),
536	amode:(sub_string(+, -, +, -, -) is nondet),
537	amode:(sub_string(+, -, -, +, -) is nondet),
538	amode:(sub_string(+, -, -, -, +) is nondet),
539	amode:(sub_string(+, -, -, -, -) is multi),
540	args:["String" : "String.",
541	    "Before" : "Integer (from 0 upwards) or variable.",
542	    "Length" : "Integer (from 0 upwards) or variable.",
543	    "After" : "Integer (from 0 upwards) or variable.",
544	    "SubString" : "String or variable."],
545	fail_if:"String cannot be split into substrings of the required lengths, or SubString does not occur within String",
546	see_also:[substring/5]]).
547
548
549%----------------------------------------------------------------------
550:- comment(substring / 5, [
551	summary:"Succeeds if SubString is a substring of String, with 
552    length Length, preceded by Before, and followed by After characters",
553
554	desc:html("   Succeeds if String can be split into three substrings,
555    StringL, SubString and StringR, such that Before is
556    the length of StringL, Length is the length of SubString
557    and After is the length of StringR.
558
559<P>
560   On backtracking, all such substrings are found.
561
562<P>
563   Zero length substrings may be specified.
564
565<P>
566   This predicate is very versatile and can be used to
567   <UL>
568   <LI>check for substrings
569   <LI>extract substrings
570   <LI>search for substrings
571   </UL>
572
573<P>
574Note:
575   This predicate provides for strings the functionality that the ISO
576   sub_atom/5 predicate provides for atoms.
577
578<P>
579"),
580	amode:(substring(+, +, +, -, -) is semidet),
581	amode:(substring(+, -, +, +, -) is semidet),
582	amode:(substring(+, +, -, +, -) is semidet),
583	amode:(substring(+, +, -, -, +) is semidet),
584	amode:(substring(+, -, -, +, +) is semidet),
585	amode:(substring(+, +, -, -, -) is nondet),
586	amode:(substring(+, -, +, -, -) is nondet),
587	amode:(substring(+, -, -, +, -) is nondet),
588	amode:(substring(+, -, -, -, +) is nondet),
589	amode:(substring(+, -, -, -, -) is multi),
590
591	args:["String" : "String.", "Before" : "Integer (from 0 upwards) or variable.", "Length" : "Integer (from 0 upwards) or variable.", "After" : "Integer (from 0 upwards) or variable.", "SubString" : "String or variable."],
592	fail_if:"String cannot be split into substrings of the required lengths, or SubString does not occur within String",
593	exceptions:[
594	    5 : "String is instantiated, but not to a string.",
595	    5 : "SubString is neither a string nor a variable.",
596	    5 : "Any of Before, Length or After are neither integers nor variables.",
597	    5 : "Any of Before, Length or After negative integers.",
598	    4 : "String is not instantiated."],
599	eg:"
600Success:
601  substring(\"abracadabra\",0,5,_,S2). (gives S2=\"abrac\").
602  substring(\"abracadabra\",_,5,0,S2). (gives S2=\"dabra\").
603  substring(\"abracadabra\",3,L,3,S2). (gives L=5, S2=\"acada\").
604  substring(\"abracadabra\",B,2,A,ab). (gives B=0, A=9; B=7, A=2).
605  substring(\"Banana\",3,2,_,S2).      (gives S2=\"an\").
606
607  [eclipse]: substring(\"ab\",B,1,A,S).
608  B=0
609  A=1
610  S=\"a\"     More? (;)
611  B=1
612  A=0
613  S=\"b\"
614  yes.
615
616  [eclipse]: substring(\"charity\",B,3,A,S2).
617  B=0
618  A=4
619  S2=\"cha\" More? (;)
620  B=1
621  A=3
622  S2=\"har\" More? (;)
623  B=2
624  A=2
625  S2=\"ari\" More? (;)
626  B=3
627  A=1
628  S2=\"rit\" More? (;)
629  B=4
630  A=0
631  S2=\"ity\"
632  yes.
633
634  [eclipse]: substring(\"abab\",B,L,A,S), writeq((B,L,A,S)), nl, fail.
635  0, 0, 4, \"\"           % on backtracking, returns all
636  0, 1, 3, \"a\"          %   substrings of String.
637  0, 2, 2, \"ab\"
638  0, 3, 1, \"aba\"
639  0, 4, 0, \"abab\"
640  1, 0, 3, \"\"
641  1, 1, 2, \"b\"
642  1, 2, 1, \"ba\"
643  1, 3, 0, \"bab\"
644  2, 0, 2, \"\"
645  2, 1, 1, \"a\"
646  2, 2, 0, \"ab\"
647  3, 0, 1, \"\"
648  3, 1, 0, \"b\"
649  4, 0, 0, \"\"
650  no (more) solution.
651
652Fail:
653  substring(\"joey\",B,L,A,\"joy\").
654  substring(\"joey\",B,2,A\"joe\").
655
656Error:
657  substring(S1,B,L,A,S2).              (Error 4).
658  substring(S1,1,2,3,\"bc\").            (Error 4).
659  substring(S1,1,2,3,'str').           (Error 4).
660  substring('string',2,3,1,S2).        (Error 5).
661  substring(\"string\",2,3,1,'str').     (Error 5).
662  substring(\"string\",a,3,1,S2).        (Error 5).
663  substring(\"string\",-1,L,A,S2).       (Error 6).
664
665
666
667",
668	see_also:[substring / 3, substring / 4, string_length / 2, split_string / 4]]).
669
670
671%----------------------------------------------------------------------
672:- comment(atom_length / 2, [
673	summary:"Succeeds if Length is the length of Atom.
674
675",
676	amode:(atom_length(+,-) is det),
677	desc:html("   The length of an atom Atom is unified with Length.  The length of an
678   atom is the number of characters in the atom's name.
679
680<P>
681    Note that (like all predicates that return a number as their last
682    argument), this predicate can be used as a function inside arithmetic
683    expressions.
684"),
685	args:["Atom" : "Atom.", "Length" : "Integer or variable."],
686	exceptions:[4 : "Atom is not instantiated (non-coroutine mode only).", 5 : "Atom is instantiated, but not to an atom.", 5 : "Length is neither an integer nor a variable."],
687	eg:"
688Success:
689      atom_length(test, 4).
690      atom_length(test,L).         (gives L = 4).
691      atom_length(as, X).          (gives X = 2).
692      atom_length('4', 1).
693
694Fail:
695      atom_length(test, 5).
696
697Error:
698      atom_length(Atom, 2).        (Error 4).
699      atom_length(Atom, 2.0).      (Error 5).
700      atom_length(4, 1).           (Error 5).
701      atom_length(as, 2.0).        (Error 5).
702
703
704
705",
706	see_also:[atom / 1, atom_string / 2, string_length / 2]]).
707
708
709%----------------------------------------------------------------------
710:- comment(concat_atoms / 3, [
711	summary:"Succeeds if Dest is the concatenation of Src1 and Src2.
712It is more efficient to use concat_strings/3 whenever possible.
713
714",
715	amode:(concat_atoms(+,+,-) is det),
716	desc:html("   Dest is unified with the concatenation of Src1 and Src2.
717   The use of this predicate is discouraged in favour of concat_strings/3,
718   because the creation of new atoms involves entering them into a
719   dictionary whose garbage collection is relatively expensive.
720
721<P>
722"),
723	args:["Src1" : "Atom.", "Src2" : "Atom.", "Dest" : "Atom or variable."],
724	exceptions:[4 : "Either (or both) of Src1 and Src2 is not instantiated    (non-coroutine mode only).", 5 : "Either (or both) of Src1 and Src2 is instantiated, but not    to an atom.", 5 : "Dest is neither an atom nor a variable."],
725	eg:"
726Success:
727      concat_atoms(abc,def,abcdef).
728
729      [eclipse]: [user].
730       filename(File,Full) :-
731            name(File,L),
732            member(0'.,L) -> Full = File ;
733                          concat_atoms(File,'.pl',Full).
734       user compiled 208 bytes in 0.00 seconds
735      yes.
736      [eclipse]: filename(a,P), filename('b.pl',F).
737      P = 'a.pl'
738      F = 'b.pl'
739      yes.
740
741Fail:
742      concat_atoms(ab,bc,abc).
743
744Error:
745      concat_atoms(art,X,artpaul).      (Error 4).
746      concat_atoms(art,\"paul\",X).       (Error 5).
747
748
749
750",
751	see_also:[concat_strings / 3, append_strings / 3, atom_string / 2]]).
752
753
754%----------------------------------------------------------------------
755:- comment(concat_strings / 3, [
756	summary:"Succeeds if Dest is the concatenation of Src1 and Src2.
757
758",
759	amode:(concat_strings(+,+,-) is det),
760	desc:html("   Dest is unified with the concatenation of Src1 and Src2.
761
762<P>
763"),
764	args:["Src1" : "String.", "Src2" : "String.", "Dest" : "String or variable."],
765	exceptions:[4 : "Either (or both) of Src1 and Src2 is not instantiated    (non-coroutine mode only).", 5 : "Either (or both) of Src1 and Src2 is instantiated, but not    to a string.", 5 : "Dest is neither a string nor a variable."],
766	eg:"
767Success:
768  concat_strings(\"abc\",\"def\",X). (gives X=\"abcdef\").
769
770  [eclipse]: [user].
771   absolutename(File,Abs) :-
772           string_list(File,List),
773           arg(1,List,0'/) -> Abs = File;
774                            (getcwd(Cwd),
775                             concat_strings(Cwd,File,Abs)).
776   user compiled 256 bytes in 0.02 seconds
777  yes.
778  [eclipse]: absolutename(\"d.pl\",P), absolutename(\"/usr/bin\",F).
779  P = \"/home/lp/user/d.pl\"
780  F = \"/usr/bin\"
781  yes.
782
783Fail:
784  concat_strings(\"ab\",\"bc\",\"abc\").
785
786Error:
787  concat_strings(\"a\",X,\"ab\").             (Error 4).
788  concat_strings(\"big\",'gest',X).         (Error 5).
789
790
791
792",
793	see_also:[append_strings / 3, concat_atoms / 3, sprintf/3]]).
794
795
796%----------------------------------------------------------------------
797:- comment(string_length / 2, [
798	summary:"Succeeds if Length is the length of the string String.
799
800",
801	amode:(string_length(+,-) is det),
802	desc:html("   The length of the string String is unified with Length.
803
804<P>
805    Note that (like all predicates that return a number as their last
806    argument), this predicate can be used as a function inside arithmetic
807    expressions.
808"),
809	args:["String" : "String.", "Length" : "Integer or variable."],
810	exceptions:[4 : "String is not instantiated (non-coroutine mode only).", 5 : "String is instantiated, but not to a string.", 5 : "Length is neither an integer nor a variable."],
811	eg:"
812Success:
813      string_length(\"Peter \",X).  (gives X=6).
814      string_length(\"Peter \",6).
815      string_length(\"401.35\",6).
816
817Fail:
818      string_length(\"Peter\",6).
819
820Error:
821      string_length(Str,Len).            (Error 4).
822      string_length(Str,6).              (Error 4).
823      string_length(\"small\",5.0).        (Error 5).
824      string_length(Str,instantiated).   (Error 5).
825      string_length(Str,46.2)            (Error 5).
826      string_length('this one',L).       (Error 5).
827
828
829
830",
831	see_also:[append_strings / 3, atom_length / 2, concat_strings / 3]]).
832
833
834%----------------------------------------------------------------------
835:- comment(substring / 3, [
836	summary:"Succeeds if String2 is a substring of String1 beginning at position
837Position.
838
839",
840	amode:(substring(+,+,+) is semidet),
841	amode:(substring(+,+,-) is semidet),
842	desc:html("   Used to test that String2 is a substring of String1 beginning at
843   position Position.  In this case, String1 and String2 are strings and
844   Position is an integer.
845
846<P>
847   Also used to find the first position in String1 that its substring
848   String2 begins.  In this case, String1 and String2 are strings and
849   Position is a variable.
850
851<P>
852   String positions must be positive and start at 1.
853
854<P>
855"),
856	args:["String1" : "String.", "String2" : "String.", "Position" : "Integer or variable."],
857	fail_if:"Fails if String2 is not a substring of String1 beginning at position Position",
858	exceptions:[4 : "Either String1 or String2 (or both) are not instantiated.", 5 : "Either String1 or String2 (or both) are instantiated, but    not to strings.", 5 : "Position is neither an integer nor a variable.", 6 : "Position is not a positive integer."],
859	eg:"
860Success:
861      substring(\"str\",\"st\",1).
862      substring(\"abcabcabc\",\"bc\",X)     (gives X=2).
863      substring(\"abcabcabc\",\"bc\",8).
864      substring(\"abc\",\"\",X).            (gives X=1).
865      substring(\"abc\",\"\",2).
866Fail:
867      substring(\"astring\",\"strg\",2).
868      substring(\"\",\"a\",X).
869Error:
870      substring(S,\"str\",1).             (Error 4).
871      substring('str',S,1).             (Error 5).
872      substring(\"st\",\"s\",1.0).          (Error 5).
873      substring(\"ab\",\"a\",-2).           (Error 6).
874
875
876
877",
878	see_also:[substring / 5, split_string / 4]]).
879
880
881%----------------------------------------------------------------------
882:- comment(split_string / 4, [
883	summary:"Decompose String into SubStrings according to separators SepChars and
884padding characters PadChars.
885
886",
887	amode:(split_string(+,+,+,-) is det),
888	desc:html("   The string String is decomposed into sub-strings which are returned
889   as a list of strings SubStrings.  Every character occurring in
890   SepChars is considered a separator, and every character occurring
891   in PadChars is considered a padding character.
892
893<P>
894   The string String is split at the separators, and any padding
895   characters around the resulting sub-strings are removed. Neither
896   the separators nor the padding characters occur in SubStrings.
897
898<P>
899   Characters that occur both in SepChars and PadChars are considered
900   separators, but such that a sequence of them is considered to be
901   only one separator. Moreover, when they occur at the beginning or
902   end of the string, they are ignored, ie. treated like padding.
903
904<P>
905   The predicate can also be used to trim leading and trailing padding
906   from a string by giving an empty separator string.
907
908<P>
909"),
910	args:["String" : "A string.", "SepChars" : "A string.", "PadChars" : "A string.", "SubStrings" : "A variable or list."],
911	exceptions:[4 : "String, SepChars or PadChars is not instantiated.", 5 : "String, SepChars or PadChars is not a string.", 5 : "List is neither an string nor a variable."],
912	eg:"
913     % split at every /
914     [eclipse]: split_string(\"/usr/local/eclipse\", \"/\", \"\", L).
915     L = [\"\", \"usr\", \"local\", \"eclipse\"]
916     yes.
917
918     % split at every sequence of /
919     [eclipse]: split_string(\"/usr/local//eclipse/\", \"/\", \"/\", L).
920     L = [\"usr\", \"local\", \"eclipse\"]
921     yes.
922
923     % split and strip padding
924     [eclipse 4]: split_string(\" comma, separated , data items \",
925                                                        \",\", \" \\t\", L).
926     L = [\"comma\", \"separated\", \"data items\"]
927     yes.
928
929     % just strip padding
930     [eclipse]: split_string(\"   Hello world...\", \"\", \" .\", L).
931     L = [\"Hello world\"]
932     yes.
933
934
935
936
937",
938	see_also:[atom_string / 2, atomics_to_string / 2, atomics_to_string / 3, number_string / 2, read_string / 3, read_string / 4, read_token / 2, read_token / 3, term_string / 2, library(regex)]]).
939
940
941%----------------------------------------------------------------------
942:- comment(concat_atom / 2, [
943	summary:"Succeeds if Dest is the concatenation of the atomic terms contained in List.
944It is more efficient to use atomics_to_string/2 whenever possible.
945
946",
947	amode:(concat_atom(++,-) is det),
948	desc:html("   Dest is unified with the concatenation of the atomic terms contained in
949   List.  List may contain numbers, atoms and strings.  The result of the
950   concatenation is always an atom.
951
952<P>
953   The use of this predicate is discouraged in favour of atomics_to_string/2,
954   because the creation of new atoms involves entering them into a
955   dictionary whose garbage collection is relatively expensive.
956
957<P>
958"),
959	args:["List" : "List of atomic terms.", "Dest" : "Atom or variable."],
960	exceptions:[4 : "List is not instantiated (non-coroutine mode only).", 4 : "List contains free variables (non-coroutine mode only).", 5 : "List is instantiated, but not to a list of atomic terms.", 5 : "Dest is neither an atom nor a variable."],
961	eg:"
962Success:
963      concat_atom([abc,def],abcdef).
964
965      concat_atom([\"Str1\",\"Str2\"],X).
966                             X = 'Str1Str2'.
967
968      concat_atom([the,man,\" is aged \",20],X).
969                             X = 'theman is aged 20'.
970
971      concat_atom([1,2,3],X)
972                             X = '123'.
973
974Fail:
975      concat_atom([ab,bc],abc).
976
977Error:
978      concat_atom(A,X).        (Error 4).
979      concat_atom([abc,D],X).  (Error 4).
980      concat_atom(art,X).      (Error 5).
981
982
983
984",
985	see_also:[atomics_to_string / 2, concat_atoms / 3, atom_string / 2, atomics_to_string / 3]]).
986
987
988%----------------------------------------------------------------------
989:- comment(atomics_to_string / 2, [
990	summary:"Succeeds if Dest is the concatenation of the atomic terms contained in
991List.
992
993",
994	amode:(atomics_to_string(++,-) is det),
995	desc:html("
996   Dest is unified with the concatenation of the atomic terms contained in
997   List.  List may contain numbers, atoms and strings.  The result of the
998   concatenation is always a string.
999"),
1000	args:["List" : "List of atomic terms.", "Dest" : "String or variable."],
1001	exceptions:[4 : "List is not instantiated (non-coroutine mode only).", 4 : "List contains free variables (non-coroutine mode only).", 5 : "List is instantiated, but not to a list of atomic terms.", 5 : "Dest is neither an string nor a variable."],
1002	eg:"
1003Success:
1004      atomics_to_string([abc,def],\"abcdef\").
1005
1006      atomics_to_string([\"Str1\",\"Str2\"],X).
1007                             X = \"Str1Str2\".
1008
1009      atomics_to_string([the,man,\" is aged \",20],X).
1010                             X = \"theman is aged 20\".
1011
1012      atomics_to_string([1,2,3],X).
1013                             X = \"123\".
1014
1015Fail:
1016      atomics_to_string([ab,bc],\"abc\").
1017
1018Error:
1019      atomics_to_string(A,X).        (Error 4).
1020      atomics_to_string([abc,D],X).  (Error 4).
1021      atomics_to_string(art,X).      (Error 5).
1022",
1023	see_also:[atomics_to_string/3, concat_atom / 2, concat_strings / 3, append_strings / 3, atom_string / 2,  split_string / 4, sprintf/3]]).
1024
1025
1026%----------------------------------------------------------------------
1027:- comment(atomics_to_string / 3, [
1028	summary:"String is the string formed by concatenating the elements of List with
1029an instance of Glue beween each of them.
1030
1031",
1032	amode:(atomics_to_string(++,+,-) is det),
1033	desc:html("   String is the string formed by concatenating the elements of List
1034   with an instance of Glue beween each of them.  List may contain
1035   numbers, atoms and strings.  The result of the concatenation is
1036   always a string.
1037
1038<P>
1039   Note that atomics_to_string/2 can be defined as
1040
1041<P>
1042<PRE>
1043       atomics_to_string(List, String) :-
1044           atomics_to_string(List, \"\", String).
1045</PRE>
1046"),
1047	args:["List" : "List of atomic terms.", "Glue" : "A string or atom.", "String" : "A string or variable."],
1048	exceptions:[4 : "List is not instantiated (non-coroutine mode only).", 4 : "List contains free variables (non-coroutine mode only).", 5 : "List is instantiated, but not to a list of atomic terms.", 5 : "String is neither an string nor a variable.", 5 : "Glue is neither an string nor an atom."],
1049	eg:"
1050Success:
1051    atomics_to_string([usr,\"local\",bin], \"/\", \"usr/local/bin\").
1052    atomics_to_string([1,2,3], \" -> \", \"1 -> 2 -> 3\").
1053
1054Error:
1055    atomics_to_string(A,\"-\",X).        (Error 4).
1056    atomics_to_string([abc,D],\",\",X).  (Error 4).
1057    atomics_to_string(art,\",\",X).      (Error 5).
1058    atomics_to_string([a,b],3,X).      (Error 5).
1059",
1060	see_also:[atomics_to_string / 2, concat_strings / 3, append_strings / 3, atom_string / 2, split_string / 4, sprintf/3]]).
1061
1062
1063%----------------------------------------------------------------------
1064:- comment(concat_string / 2, [
1065	summary:"Succeeds if Dest is the concatenation of the atomic terms contained in
1066List.
1067
1068",
1069	amode:(concat_string(++,-) is det),
1070	desc:html("   Dest is unified with the concatenation of the atomic terms contained in
1071   List.  List may contain numbers, atoms and strings.  The result of the
1072   concatenation is always a string.
1073<P>
1074   This is a deprecated alias for atomics_to_string/2,
1075"),
1076	args:["List" : "List of atomic terms.", "Dest" : "String or variable."],
1077	exceptions:[4 : "List is not instantiated (non-coroutine mode only).", 4 : "List contains free variables (non-coroutine mode only).", 5 : "List is instantiated, but not to a list of atomic terms.", 5 : "Dest is neither an string nor a variable."],
1078	eg:"
1079Success:
1080      concat_string([abc,def],\"abcdef\").
1081
1082      concat_string([\"Str1\",\"Str2\"],X).
1083                             X = \"Str1Str2\".
1084
1085      concat_string([the,man,\" is aged \",20],X).
1086                             X = \"theman is aged 20\".
1087
1088      concat_string([1,2,3],X).
1089                             X = \"123\".
1090
1091Fail:
1092      concat_string([ab,bc],\"abc\").
1093
1094Error:
1095      concat_string(A,X).        (Error 4).
1096      concat_string([abc,D],X).  (Error 4).
1097      concat_string(art,X).      (Error 5).
1098
1099
1100
1101",
1102	see_also:[concat_atom / 2, concat_strings / 3, append_strings / 3, atom_string / 2, join_string / 3, split_string / 4, sprintf/3]]).
1103
1104
1105%----------------------------------------------------------------------
1106:- comment(join_string / 3, [
1107	summary:"String is the string formed by concatenating the elements of List with
1108an instance of Glue between each of them.
1109
1110",
1111	amode:(join_string(++,+,-) is det),
1112	desc:html("   String is the string formed by concatenating the elements of List
1113   with an instance of Glue between each of them.  List may contain
1114   numbers, atoms and strings.  The result of the concatenation is
1115   always a string.
1116
1117<P>
1118   Note that concat_string/2 can be defined as
1119
1120<P>
1121<PRE>
1122       concat_string(List, String) :-
1123           join_string(List, \"\", String).
1124</PRE>
1125   This is a deprecated alias for atomics_to_string/3.
1126"),
1127	args:["List" : "List of atomic terms.", "Glue" : "A string or atom.", "String" : "A string or variable."],
1128	exceptions:[4 : "List is not instantiated (non-coroutine mode only).", 4 : "List contains free variables (non-coroutine mode only).", 5 : "List is instantiated, but not to a list of atomic terms.", 5 : "String is neither an string nor a variable.", 5 : "Glue is neither an string nor an atom."],
1129	eg:"
1130Success:
1131    join_string([usr,\"local\",bin], \"/\", \"usr/local/bin\").
1132    join_string([1,2,3], \" -> \", \"1 -> 2 -> 3\").
1133
1134Error:
1135    join_string(A,\"-\",X).        (Error 4).
1136    join_string([abc,D],\",\",X).  (Error 4).
1137    join_string(art,\",\",X).      (Error 5).
1138    join_string([a,b],3,X).      (Error 5).
1139
1140
1141
1142",
1143	see_also:[atomics_to_string / 2, concat_strings / 3, append_strings / 3, atom_string / 2, split_string / 4, sprintf/3]]).
1144
1145
1146%----------------------------------------------------------------------
1147:- comment(get_string_code / 3, [
1148	summary:"Succeeds if Code is the value of the Index'th character code in String",
1149	amode:(get_string_code(+,+,-) is det),
1150	args:[
1151		"Index":"Integer between 1 and the length of String",
1152		"String":"String",
1153		"Code":"Variable or Integer"
1154	],
1155	desc:html("\
1156    This predicate extracts the Index'th character code from the given
1157    string String.  Character codes in the string are numbered from 1
1158    (analogous to array indices in subscript/3 and arg/3).
1159    <P>
1160    Note that (like all predicates that return a number as their last
1161    argument), this predicate can be used as a function inside arithmetic
1162    expressions.
1163"),
1164	exceptions:[
1165	    5 : "Index is not an integer",
1166	    5 : "String is not a string",
1167	    5 : "Code is instantiated but not to an integer",
1168	    6 : "Index is an integer less than 1 or greater than String's length",
1169	    4 : "Either Index or String are uninstantated"],
1170	eg:"
1171   get_string_code(1, \"abc\", 97).     % succeeds
1172   get_string_code(3, \"abc\", C).      % gives C = 99
1173
1174   get_string_code(2, \"abc\", 100).    % fails
1175
1176   get_string_code(_, \"abc\", C).      % Error 4
1177   get_string_code(1, _, C).          % Error 4
1178   get_string_code(1.5, \"abc\", C).    % Error 5
1179   get_string_code(1, abc, C).        % Error 5
1180   get_string_code(0, \"abc\", C).      % Error 6
1181   get_string_code(4, \"abc\", C).      % Error 6
1182",
1183	see_also:[string_code/3, string_codes/2, string_list/2, char_code/2]]).
1184
1185
1186%----------------------------------------------------------------------
1187:- comment(string_code / 3, [
1188	summary:"Succeeds if Code is the value of the Index'th character code in String",
1189	amode:(string_code(+,+,-) is det),
1190	amode:(string_code(-,+,+) is nondet),
1191	amode:(string_code(-,+,-) is nondet),
1192	args:[
1193		"Index":"Variable or integer between 1 and the length of String",
1194		"String":"String",
1195		"Code":"Variable or non-negative integer"
1196	],
1197	desc:html("\
1198    This predicate maps the index position Index to the corresponding
1199    character code in the given string String.  Character codes in the
1200    string are numbered from 1 (analogous to array indices in subscript/3
1201    and arg/3).  Index positions of zero or greater than the string length
1202    lead to failure.
1203    <P>
1204    The predicate may be used to extract the Index'th character, to find
1205    the position(s) of a particular character code, or to enumerate all
1206    positions and character codes in the string.
1207    <P>
1208    For simply extracting the Index'th character code from a string,
1209    the deterministic variant get_string_code/3 might be preferred
1210    for efficiency and stricter error checking.
1211    <P>
1212    For backward compatibility with earlier versions of ECLiPSe, the 
1213    call pattern string_code(+String,+Index,-Code) is also allowed.
1214"),
1215	exceptions:[
1216	    4 : "String is uninstantated",
1217	    5 : "String is instantiated, but not a string",
1218	    24 : "Index is instantiated, but not an integer",
1219	    5 : "Code is instantiated, but not an integer",
1220	    6 : "Index or Code is a negative integer"],
1221	eg:"
1222   string_code(1, \"abc\", 0'a).        % succeeds
1223   string_code(1, \"abc\", 97).         % succeeds
1224   string_code(3, \"abc\", C).          % gives C = 0'c
1225   string_code(I, \"abc\", 0'c).        % gives I = 3
1226   string_code(I, \"abcb\", 0'b).       % gives I = 2 ; I = 4 on backtracking
1227   string_code(I, \"ab\", C).           % gives I=1,C=0'a ; I=2,C=0'b on backtracking
1228
1229   string_code(2, \"abc\", 100).        % fails
1230   string_code(I, \"abc\", 0'd).        % fails
1231   string_code(0, \"abc\", C).          % fails
1232   string_code(4, \"abc\", C).          % fails
1233   string_code(I, \"\", C).             % fails
1234
1235   string_code(1, S, 0'c).            % Error 4
1236   string_code(1, abc, C).            % Error 5
1237   string_code(1.5, \"abc\", C).        % Error 5
1238   string_code(I, \"abc\", b).          % Error 5
1239   string_code(-1, \"abc\", C).         % Error 6
1240   string_code(I, \"abc\", -1).         % Error 6
1241",
1242	see_also:[get_string_code/3, string_codes/2, string_list/2, char_code/2]]).
1243
1244
1245%----------------------------------------------------------------------
1246:- comment(string_char / 3, [
1247	summary:"Succeeds if Char is the value of the Index'th character in String",
1248	amode:(string_char(+,+,-) is det),
1249	amode:(string_char(-,+,+) is nondet),
1250	amode:(string_char(-,+,-) is nondet),
1251	args:[
1252		"Index":"Variable or integer between 1 and the length of String",
1253		"String":"String",
1254		"Char":"Variable or single-character atom"
1255	],
1256	desc:html("\
1257    This predicate maps the index position Index to the corresponding
1258    character in the given string String.  Characters in the string
1259    are numbered from 1 (analogous to array indices in subscript/3
1260    and arg/3).  Index positions of zero or greater than the string length
1261    lead to failure.
1262    <P>
1263    The predicate may be used to extract the Index'th character, to find
1264    the position(s) of a particular character, or to enumerate all
1265    positions and characters in the string.
1266"),
1267	exceptions:[
1268	    4 : "String is uninstantated",
1269	    5 : "String is instantiated, but not a string",
1270	    24 : "Index is instantiated, but not an integer",
1271	    5 : "Char is instantiated, but not an atom",
1272	    6 : "Index is a negative integer",
1273	    6 : "Char is a non-characte atom"],
1274	eg:"
1275   string_char(1, \"abc\", a).          % succeeds
1276   string_char(3, \"abc\", C).          % gives C = c
1277   string_char(I, \"abc\", c).          % gives I = 3
1278   string_char(I, \"abcb\", b).         % gives I = 2 ; I = 4 on backtracking
1279   string_char(I, \"ab\", C).           % gives I=1,C=a ; I=2,C=b on backtracking
1280
1281   string_char(2, \"abc\", d).          % fails
1282   string_char(I, \"abc\", d).          % fails
1283   string_char(0, \"abc\", C).          % fails
1284   string_char(4, \"abc\", C).          % fails
1285   string_char(I, \"\", C).             % fails
1286
1287   string_char(1, S, c).              % Error 4
1288   string_char(1, abc, C).            % Error 5
1289   string_char(1.5, \"abc\", C).        % Error 5
1290   string_char(I, \"abc\", 0'b).        % Error 5
1291   string_char(-1, \"abc\", C).         % Error 6
1292   string_char(I, \"abc\", bb).         % Error 6
1293",
1294	see_also:[string_code/3, string_chars/2, string_list/2, char_code/2]]).
1295
1296
1297%----------------------------------------------------------------------
1298:- comment(text_to_string / 2, [
1299	summary:"Convert different text representations to a string",
1300	amode:(text_to_string(++,-) is det),
1301	desc:html("
1302   This predicate converts different text representations to a string.
1303   Text is an atom, string, list of character codes, or list of
1304   single-character atoms.
1305<P>
1306   Note that the atom '[]' represents the empty list [], and is
1307   therefore converted to the empty string.
1308<P>
1309   Apart from error handling, this is a shorthand for
1310<PRE>
1311    text_to_string(Text, String) :-
1312	( Text == [] -> String = ""
1313	; atom(Text) -> atom_string(Text, String)
1314    	; string(Text) -> String = Text
1315	; is_list(Text), Text = [C|_], atom(C) -> string_chars(String, Text)
1316	; is_list(Text), Text = [C|_], integer(C) -> string_codes(String, Text)
1317	).
1318</PRE>
1319"),
1320    args:[
1321	"Text" : "An atom, string or list of characters.",
1322    	"String" : "Variable or string."],
1323    exceptions:[
1324	4 : "Text is nonground.",
1325	5 : "Text is neither atom, string, nor a proper list.",
1326	5 : "Text is a list, but contains neither purely atoms nor purely integers.",
1327	6 : "Text is a list of atoms that do no all represent characters",
1328	6 : "Text is a list of integers that do no all represent characters"],
1329    eg:"
1330  Success:
1331
1332    text_to_string([0'a,0'b,0'c],S)     % gives S==\"abc\".
1333    text_to_string([a,b,c],S)	        % gives S==\"abc\".
1334    text_to_string(abc,S)               % gives S==\"abc\".
1335    text_to_string(\"abc\",S)             % gives S==\"abc\".
1336    text_to_string([],S)                % gives S==\"\".
1337
1338  Fail:
1339    text_to_string(abc,abc)             % gives S==\"abc\".
1340
1341  Error:
1342    text_to_string(T,S)                 % Error 4
1343    text_to_string([a,B,c],S)           % Error 4
1344    text_to_string([a,0'b,c],S)         % Error 5
1345    text_to_string(123,S)               % Error 5
1346    text_to_string([a,bb,c],S)          % Error 6
1347    text_to_string([97,-1,99],S)        % Error 6
1348",
1349	see_also:[string_codes/2, string_chars/2, string_list/3, atom_string/2]]).
1350
1351
1352%----------------------------------------------------------------------
1353:- comment(string_upper / 2, [
1354	summary:"Convert string to upper case",
1355	amode:(string_upper(++,-) is det),
1356	desc:html("
1357   This predicate converts a string to its upper case version, i.e.
1358   converts all lower case characters to upper case, if possible.
1359"),
1360    args:[
1361	"String" : "A string",
1362    	"Upper" : "Variable or string"],
1363    exceptions:[
1364	4 : "String is nonground.",
1365	5 : "String is not a string."],
1366    eg:"
1367    string_upper(\"Eclipse-6.2\", S)       % gives S == \"ECLIPSE-6.2\"
1368",
1369	see_also:[string_lower/2]]).
1370
1371
1372%----------------------------------------------------------------------
1373:- comment(string_lower / 2, [
1374	summary:"Convert string to lower case",
1375	amode:(string_lower(++,-) is det),
1376	desc:html("
1377   This predicate converts a string to its lower case version, i.e.
1378   converts all lower case characters to lower case, if possible.
1379"),
1380    args:[
1381	"String" : "A string",
1382    	"Upper" : "Variable or string"],
1383    exceptions:[
1384	4 : "String is nonground.",
1385	5 : "String is not a string."],
1386    eg:"
1387    string_lower(\"ECLiPSe-6.2\", S)       % gives S == \"eclipse-6.2\"
1388",
1389	see_also:[string_upper/2]]).
1390
1391
1392