0.6.10.1:
[sbcl.git] / src / code / string.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB!IMPL")
11
12 (defun string (x)
13   #!+sb-doc
14   "Coerces X into a string. If X is a string, X is returned. If X is a
15    symbol, X's pname is returned. If X is a character then a one element
16    string containing that character is returned. If X cannot be coerced
17    into a string, an error occurs."
18   (cond ((stringp x) x)
19         ((symbolp x) (symbol-name x))
20         ((characterp x)
21          (let ((res (make-string 1)))
22            (setf (schar res 0) x) res))
23         (t
24          (error 'simple-type-error
25                 :datum x
26                 :expected-type 'stringable
27                 :format-control "~S cannot be coerced to a string."
28                 :format-arguments (list x)))))
29
30 (eval-when (:compile-toplevel)
31 ;;; WITH-ONE-STRING is used to set up some string hacking things. The
32 ;;; keywords are parsed, and the string is hacked into a
33 ;;; simple-string.
34 (sb!xc:defmacro with-one-string ((string start end) &body forms)
35   `(let ((,string (if (stringp ,string) ,string (string ,string))))
36      (with-array-data ((,string ,string)
37                        (,start ,start)
38                        (,end (or ,end (length (the vector ,string)))))
39        ,@forms)))
40 ;;; WITH-STRING is like WITH-ONE-STRING, but doesn't parse keywords.
41 (sb!xc:defmacro with-string (string &rest forms)
42   `(let ((,string (if (stringp ,string) ,string (string ,string))))
43      (with-array-data ((,string ,string)
44                        (start)
45                        (end (length (the vector ,string))))
46        ,@forms)))
47 ;;; WITH-TWO-STRINGS is used to set up string comparison operations. The
48 ;;; keywords are parsed, and the strings are hacked into SIMPLE-STRINGs.
49 (sb!xc:defmacro with-two-strings (string1 string2 start1 end1 cum-offset-1
50                                             start2 end2 &rest forms)
51   `(let ((,string1 (if (stringp ,string1) ,string1 (string ,string1)))
52          (,string2 (if (stringp ,string2) ,string2 (string ,string2))))
53      (with-array-data ((,string1 ,string1 :offset-var ,cum-offset-1)
54                        (,start1 ,start1)
55                        (,end1 (or ,end1 (length (the vector ,string1)))))
56        (with-array-data ((,string2 ,string2)
57                          (,start2 ,start2)
58                          (,end2 (or ,end2 (length (the vector ,string2)))))
59          ,@forms))))
60 ) ; EVAL-WHEN
61
62 (defun char (string index)
63   #!+sb-doc
64   "Given a string and a non-negative integer index less than the length of
65   the string, returns the character object representing the character at
66   that position in the string."
67   (declare (optimize (safety 1)))
68   (char string index))
69
70 (defun %charset (string index new-el)
71   (declare (optimize (safety 1)))
72   (setf (char string index) new-el))
73
74 (defun schar (string index)
75   #!+sb-doc
76   "SCHAR returns the character object at an indexed position in a string
77    just as CHAR does, except the string must be a simple-string."
78   (declare (optimize (safety 1)))
79   (schar string index))
80
81 (defun %scharset (string index new-el)
82   (declare (optimize (safety 1)))
83   (setf (schar string index) new-el))
84
85 (defun string=* (string1 string2 start1 end1 start2 end2)
86   (with-two-strings string1 string2 start1 end1 offset1 start2 end2
87     (not (%sp-string-compare string1 start1 end1 string2 start2 end2))))
88
89 (defun string/=* (string1 string2 start1 end1 start2 end2)
90   (with-two-strings string1 string2 start1 end1 offset1 start2 end2
91     (let ((comparison (%sp-string-compare string1 start1 end1
92                                           string2 start2 end2)))
93       (if comparison (- (the fixnum comparison) offset1)))))
94
95 (eval-when (:compile-toplevel :execute)
96
97 ;;; Lessp is true if the desired expansion is for string<* or string<=*.
98 ;;; Equalp is true if the desired expansion is for string<=* or string>=*.
99 (sb!xc:defmacro string<>=*-body (lessp equalp)
100   (let ((offset1 (gensym)))
101     `(with-two-strings string1 string2 start1 end1 ,offset1 start2 end2
102        (let ((index (%sp-string-compare string1 start1 end1
103                                         string2 start2 end2)))
104          (if index
105              (cond ((= (the fixnum index) (the fixnum end1))
106                     ,(if lessp
107                          `(- (the fixnum index) ,offset1)
108                        `nil))
109                    ((= (+ (the fixnum index) (- start2 start1))
110                        (the fixnum end2))
111                     ,(if lessp
112                          `nil
113                        `(- (the fixnum index) ,offset1)))
114                    ((,(if lessp 'char< 'char>)
115                      (schar string1 index)
116                      (schar string2 (+ (the fixnum index) (- start2 start1))))
117                     (- (the fixnum index) ,offset1))
118                    (t nil))
119              ,(if equalp `(- (the fixnum end1) ,offset1) 'nil))))))
120 ) ; EVAL-WHEN
121
122 (defun string<* (string1 string2 start1 end1 start2 end2)
123   (declare (fixnum start1 start2))
124   (string<>=*-body t nil))
125
126 (defun string>* (string1 string2 start1 end1 start2 end2)
127   (declare (fixnum start1 start2))
128   (string<>=*-body nil nil))
129
130 (defun string<=* (string1 string2 start1 end1 start2 end2)
131   (declare (fixnum start1 start2))
132   (string<>=*-body t t))
133
134 (defun string>=* (string1 string2 start1 end1 start2 end2)
135   (declare (fixnum start1 start2))
136   (string<>=*-body nil t))
137
138 (defun string< (string1 string2 &key (start1 0) end1 (start2 0) end2)
139   #!+sb-doc
140   "Given two strings, if the first string is lexicographically less than
141   the second string, returns the longest common prefix (using char=)
142   of the two strings. Otherwise, returns ()."
143   (string<* string1 string2 start1 end1 start2 end2))
144
145 (defun string> (string1 string2 &key (start1 0) end1 (start2 0) end2)
146   #!+sb-doc
147   "Given two strings, if the first string is lexicographically greater than
148   the second string, returns the longest common prefix (using char=)
149   of the two strings. Otherwise, returns ()."
150   (string>* string1 string2 start1 end1 start2 end2))
151
152 (defun string<= (string1 string2 &key (start1 0) end1 (start2 0) end2)
153   #!+sb-doc
154   "Given two strings, if the first string is lexicographically less than
155   or equal to the second string, returns the longest common prefix
156   (using char=) of the two strings. Otherwise, returns ()."
157   (string<=* string1 string2 start1 end1 start2 end2))
158
159 (defun string>= (string1 string2 &key (start1 0) end1 (start2 0) end2)
160   "Given two strings, if the first string is lexicographically greater
161   than or equal to the second string, returns the longest common prefix
162   (using char=) of the two strings. Otherwise, returns ()."
163   (string>=* string1 string2 start1 end1 start2 end2))
164
165 ;;; Note: (STRING= "PREFIX" "SHORT" :END2 (LENGTH "PREFIX")) gives
166 ;;; an error instead of returning NIL as I would have expected.
167 ;;; The ANSI spec for STRING= itself doesn't seem to clarify this
168 ;;; much, but the SUBSEQ-OUT-OF-BOUNDS writeup seems to say that
169 ;;; this is conforming (and required) behavior, because any index
170 ;;; out of range is an error. (So there seems to be no concise and
171 ;;; efficient way to test for strings which begin with a particular
172 ;;; pattern. Alas..) -- WHN 19991206
173 (defun string= (string1 string2 &key (start1 0) end1 (start2 0) end2)
174   #!+sb-doc
175   "Given two strings (string1 and string2), and optional integers start1,
176   start2, end1 and end2, compares characters in string1 to characters in
177   string2 (using char=)."
178   (string=* string1 string2 start1 end1 start2 end2))
179
180 (defun string/= (string1 string2 &key (start1 0) end1 (start2 0) end2)
181   #!+sb-doc
182   "Given two strings, if the first string is not lexicographically equal
183   to the second string, returns the longest common prefix (using char=)
184   of the two strings. Otherwise, returns ()."
185   (string/=* string1 string2 start1 end1 start2 end2))
186
187 (eval-when (:compile-toplevel :execute)
188
189 ;;; STRING-NOT-EQUAL-LOOP is used to generate character comparison loops for
190 ;;; STRING-EQUAL and STRING-NOT-EQUAL.
191 (sb!xc:defmacro string-not-equal-loop (end
192                                          end-value
193                                          &optional (abort-value nil abortp))
194   (declare (fixnum end))
195   (let ((end-test (if (= end 1)
196                       `(= index1 (the fixnum end1))
197                       `(= index2 (the fixnum end2)))))
198     `(do ((index1 start1 (1+ index1))
199           (index2 start2 (1+ index2)))
200          (,(if abortp
201                end-test
202                `(or ,end-test
203                     (not (char-equal (schar string1 index1)
204                                      (schar string2 index2)))))
205           ,end-value)
206        (declare (fixnum index1 index2))
207        ,@(if abortp
208              `((if (not (char-equal (schar string1 index1)
209                                     (schar string2 index2)))
210                    (return ,abort-value)))))))
211
212 ) ; EVAL-WHEN
213
214 (defun string-equal (string1 string2 &key (start1 0) end1 (start2 0) end2)
215   #!+sb-doc
216   "Given two strings (string1 and string2), and optional integers start1,
217   start2, end1 and end2, compares characters in string1 to characters in
218   string2 (using char-equal)."
219   (declare (fixnum start1 start2))
220   (with-two-strings string1 string2 start1 end1 offset1 start2 end2
221     (let ((slen1 (- (the fixnum end1) start1))
222           (slen2 (- (the fixnum end2) start2)))
223       (declare (fixnum slen1 slen2))
224       (if (or (minusp slen1) (minusp slen2))
225           ;;prevent endless looping later.
226           (error "Improper bounds for string comparison."))
227       (if (= slen1 slen2)
228           ;;return () immediately if lengths aren't equal.
229           (string-not-equal-loop 1 t nil)))))
230
231 (defun string-not-equal (string1 string2 &key (start1 0) end1 (start2 0) end2)
232   #!+sb-doc
233   "Given two strings, if the first string is not lexicographically equal
234   to the second string, returns the longest common prefix (using char-equal)
235   of the two strings. Otherwise, returns ()."
236   (with-two-strings string1 string2 start1 end1 offset1 start2 end2
237     (let ((slen1 (- end1 start1))
238           (slen2 (- end2 start2)))
239       (declare (fixnum slen1 slen2))
240       (if (or (minusp slen1) (minusp slen2))
241           ;; Prevent endless looping later.
242           (error "Improper bounds for string comparison."))
243       (cond ((or (minusp slen1) (or (minusp slen2)))
244              (error "Improper substring for comparison."))
245             ((= slen1 slen2)
246              (string-not-equal-loop 1 nil (- index1 offset1)))
247             ((< slen1 slen2)
248              (string-not-equal-loop 1 (- index1 offset1)))
249             (t
250              (string-not-equal-loop 2 (- index1 offset1)))))))
251
252 (eval-when (:compile-toplevel :execute)
253
254 ;;; STRING-LESS-GREATER-EQUAL-TESTS returns a test on the lengths of string1
255 ;;; and string2 and a test on the current characters from string1 and string2
256 ;;; for the following macro.
257 (defun string-less-greater-equal-tests (lessp equalp)
258   (if lessp
259       (if equalp
260           ;; STRING-NOT-GREATERP
261           (values '<= `(not (char-greaterp char1 char2)))
262           ;; STRING-LESSP
263           (values '< `(char-lessp char1 char2)))
264       (if equalp
265           ;; STRING-NOT-LESSP
266           (values '>= `(not (char-lessp char1 char2)))
267           ;; STRING-GREATERP
268           (values '> `(char-greaterp char1 char2)))))
269
270 (sb!xc:defmacro string-less-greater-equal (lessp equalp)
271   (multiple-value-bind (length-test character-test)
272       (string-less-greater-equal-tests lessp equalp)
273     `(with-two-strings string1 string2 start1 end1 offset1 start2 end2
274        (let ((slen1 (- (the fixnum end1) start1))
275              (slen2 (- (the fixnum end2) start2)))
276          (declare (fixnum slen1 slen2))
277          (if (or (minusp slen1) (minusp slen2))
278              ;;prevent endless looping later.
279              (error "Improper bounds for string comparison."))
280          (do ((index1 start1 (1+ index1))
281               (index2 start2 (1+ index2))
282               (char1)
283               (char2))
284              ((or (= index1 (the fixnum end1)) (= index2 (the fixnum end2)))
285               (if (,length-test slen1 slen2) (- index1 offset1)))
286            (declare (fixnum index1 index2))
287            (setq char1 (schar string1 index1))
288            (setq char2 (schar string2 index2))
289            (if (not (char-equal char1 char2))
290                (if ,character-test
291                    (return (- index1 offset1))
292                    (return ()))))))))
293
294 ) ; EVAL-WHEN
295
296 (defun string-lessp* (string1 string2 start1 end1 start2 end2)
297   (declare (fixnum start1 start2))
298   (string-less-greater-equal t nil))
299
300 (defun string-greaterp* (string1 string2 start1 end1 start2 end2)
301   (declare (fixnum start1 start2))
302   (string-less-greater-equal nil nil))
303
304 (defun string-not-lessp* (string1 string2 start1 end1 start2 end2)
305   (declare (fixnum start1 start2))
306   (string-less-greater-equal nil t))
307
308 (defun string-not-greaterp* (string1 string2 start1 end1 start2 end2)
309   (declare (fixnum start1 start2))
310   (string-less-greater-equal t t))
311
312 (defun string-lessp (string1 string2 &key (start1 0) end1 (start2 0) end2)
313   #!+sb-doc
314   "Given two strings, if the first string is lexicographically less than
315   the second string, returns the longest common prefix (using char-equal)
316   of the two strings. Otherwise, returns ()."
317   (string-lessp* string1 string2 start1 end1 start2 end2))
318
319 (defun string-greaterp (string1 string2 &key (start1 0) end1 (start2 0) end2)
320   #!+sb-doc
321   "Given two strings, if the first string is lexicographically greater than
322   the second string, returns the longest common prefix (using char-equal)
323   of the two strings. Otherwise, returns ()."
324   (string-greaterp* string1 string2 start1 end1 start2 end2))
325
326 (defun string-not-lessp (string1 string2 &key (start1 0) end1 (start2 0) end2)
327   #!+sb-doc
328   "Given two strings, if the first string is lexicographically greater
329   than or equal to the second string, returns the longest common prefix
330   (using char-equal) of the two strings. Otherwise, returns ()."
331   (string-not-lessp* string1 string2 start1 end1 start2 end2))
332
333 (defun string-not-greaterp (string1 string2 &key (start1 0) end1 (start2 0)
334                                     end2)
335   #!+sb-doc
336   "Given two strings, if the first string is lexicographically less than
337   or equal to the second string, returns the longest common prefix
338   (using char-equal) of the two strings. Otherwise, returns ()."
339   (string-not-greaterp* string1 string2 start1 end1 start2 end2))
340
341 (defun make-string (count &key element-type ((:initial-element fill-char)))
342   #!+sb-doc
343   "Given a character count and an optional fill character, makes and returns
344    a new string Count long filled with the fill character."
345   (declare (fixnum count)
346            (ignore element-type))
347   (if fill-char
348       (do ((i 0 (1+ i))
349            (string (make-string count)))
350           ((= i count) string)
351         (declare (fixnum i))
352         (setf (schar string i) fill-char))
353       (make-string count)))
354
355 (flet ((%upcase (string start end)
356          (declare (string string) (index start) (type sequence-end end))
357          (let ((saved-header string))
358            (with-one-string (string start end)
359              (do ((index start (1+ index)))
360                  ((= index (the fixnum end)))
361                (declare (fixnum index))
362                (setf (schar string index) (char-upcase (schar string index)))))
363            saved-header)))
364 (defun string-upcase (string &key (start 0) end)
365   (%upcase (copy-seq (string string)) start end))
366 (defun nstring-upcase (string &key (start 0) end)
367   (%upcase string start end))
368 ) ; FLET
369
370 (flet ((%downcase (string start end)
371          (declare (string string) (index start) (type sequence-end end))
372          (let ((saved-header string))
373            (with-one-string (string start end)
374              (do ((index start (1+ index)))
375                  ((= index (the fixnum end)))
376                (declare (fixnum index))
377                (setf (schar string index)
378                      (char-downcase (schar string index)))))
379            saved-header)))
380 (defun string-downcase (string &key (start 0) end)
381   (%downcase (copy-seq (string string)) start end))
382 (defun nstring-downcase (string &key (start 0) end)
383   (%downcase string start end))
384 ) ; FLET
385
386 (flet ((%capitalize (string start end)
387          (declare (string string) (index start) (type sequence-end end))
388          (let ((saved-header string))
389            (with-one-string (string start end)
390              (do ((index start (1+ index))
391                   (new-word? t)
392                   (char nil))
393                  ((= index (the fixnum end)))
394                (declare (fixnum index))
395                (setq char (schar string index))
396                (cond ((not (alphanumericp char))
397                       (setq new-word? t))
398                      (new-word?
399                       ;; CHAR is the first case-modifiable character after
400                       ;; a sequence of non-case-modifiable characters.
401                       (setf (schar string index) (char-upcase char))
402                       (setq new-word? nil))
403                      (t
404                       (setf (schar string index) (char-downcase char))))))
405            saved-header)))
406 (defun string-capitalize (string &key (start 0) end)
407   (%capitalize (copy-seq (string string)) start end))
408 (defun nstring-capitalize (string &key (start 0) end)
409   (%capitalize string start end))
410 ) ; FLET
411
412 (defun string-left-trim (char-bag string)
413   (with-string string
414     (do ((index start (1+ index)))
415         ((or (= index (the fixnum end))
416              (not (find (schar string index) char-bag :test #'char=)))
417          (subseq (the simple-string string) index end))
418       (declare (fixnum index)))))
419
420 (defun string-right-trim (char-bag string)
421   (with-string string
422     (do ((index (1- (the fixnum end)) (1- index)))
423         ((or (< index start)
424              (not (find (schar string index) char-bag :test #'char=)))
425          (subseq (the simple-string string) start (1+ index)))
426       (declare (fixnum index)))))
427
428 (defun string-trim (char-bag string)
429   (with-string string
430     (let* ((left-end (do ((index start (1+ index)))
431                          ((or (= index (the fixnum end))
432                               (not (find (schar string index)
433                                          char-bag
434                                          :test #'char=)))
435                           index)
436                        (declare (fixnum index))))
437            (right-end (do ((index (1- (the fixnum end)) (1- index)))
438                           ((or (< index left-end)
439                                (not (find (schar string index)
440                                           char-bag
441                                           :test #'char=)))
442                            (1+ index))
443                         (declare (fixnum index)))))
444       (subseq (the simple-string string) left-end right-end))))