9616cde3c85421f8af76bb9863671c6dcc9e9988
[sbcl.git] / tests / seq.impure.lisp
1 ;;;; tests related to sequences
2
3 ;;;; This file is impure because we want to be able to use DEFUN.
4
5 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; more information.
7 ;;;;
8 ;;;; While most of SBCL is derived from the CMU CL system, the test
9 ;;;; files (like this one) were written from scratch after the fork
10 ;;;; from CMU CL.
11 ;;;;
12 ;;;; This software is in the public domain and is provided with
13 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
14 ;;;; more information.
15
16 (load "test-util.lisp")
17 (load "assertoid.lisp")
18
19 (defpackage :seq-test
20   (:use :cl :assertoid :test-util))
21
22 (in-package :seq-test)
23
24 ;;; user-defined mock sequence class for testing generic versions of
25 ;;; sequence functions.
26 (defclass list-backed-sequence (standard-object
27                                 sequence)
28   ((elements :initarg :elements :type list :accessor %elements)))
29
30 (defmethod sequence:make-sequence-like ((sequence list-backed-sequence) length
31                                         &rest args &key
32                                         initial-element initial-contents)
33   (declare (ignore initial-element initial-contents))
34   (make-instance 'list-backed-sequence
35                  :elements (apply #'sequence:make-sequence-like
36                                   '() length args)))
37
38 (defmethod sequence:length ((sequence list-backed-sequence))
39   (length (%elements sequence)))
40
41 (defmethod sequence:elt
42     ((sequence list-backed-sequence) index)
43   (nth index (%elements sequence)))
44
45 (defmethod (setf sequence:elt)
46     (new-value (sequence list-backed-sequence) index)
47   (setf (nth index (%elements sequence)) new-value))
48
49 ;;; helper functions for exercising SEQUENCE code on data of many
50 ;;; specialized types, and in many different optimization scenarios
51 (defun for-every-seq-1 (base-seq snippet)
52   (labels
53       ((entirely (eltype)
54          (every (lambda (el) (typep el eltype)) base-seq))
55        (make-sequence-for-type (type)
56          (etypecase type
57            ((member list list-backed-sequence)
58             (coerce base-seq type))
59            ((cons (eql simple-array) (cons * (cons (eql 1) null)))
60             (destructuring-bind (eltype one) (rest type)
61               (when (entirely eltype)
62                 (coerce base-seq type))))
63            ((cons (eql vector))
64             (destructuring-bind (eltype) (rest type)
65               (when (entirely eltype)
66                 (let ((initial-element
67                         (cond ((subtypep eltype 'character)
68                                #\!)
69                               ((subtypep eltype 'number)
70                                0)
71                                 (t #'error))))
72                   (replace (make-array
73                             (+ (length base-seq)
74                                (random 3))
75                             :element-type eltype
76                             :fill-pointer
77                             (length base-seq)
78                             :initial-element
79                             initial-element)
80                            base-seq))))))))
81     (dolist (seq-type '(list
82                         (simple-array t 1)
83                         (vector t)
84                         (simple-array character 1)
85                         (vector character)
86                         (simple-array (signed-byte 4) 1)
87                         (vector (signed-byte 4))
88                         list-backed-sequence))
89       (dolist (declaredness '(nil t))
90         (dolist (optimization '(((speed 3) (space 0))
91                                 ((speed 2) (space 2))
92                                 ((speed 1) (space 2))
93                                 ((speed 0) (space 1))))
94           (let ((seq (make-sequence-for-type seq-type))
95                 (lambda-expr `(lambda (seq)
96                                 ,@(when declaredness
97                                     `((declare (type ,seq-type seq))))
98                                 (declare (optimize ,@optimization))
99                                 ,snippet)))
100             (when (not seq)
101               (return))
102             (format t "~&~S~%" lambda-expr)
103             (multiple-value-bind (fun warnings-p failure-p)
104                 (compile nil lambda-expr)
105               (when (or warnings-p failure-p)
106                 (error "~@<failed compilation:~2I ~_LAMBDA-EXPR=~S ~_WARNINGS-P=~S ~_FAILURE-P=~S~:@>"
107                        lambda-expr warnings-p failure-p))
108               (format t "~&~S ~S~%~S~%~S ~S~%"
109                       base-seq snippet seq-type declaredness optimization)
110               (format t "~&(TYPEP SEQ 'SIMPLE-ARRAY)=~S~%"
111                       (typep seq 'simple-array))
112               (unless (funcall fun seq)
113                 (error "~@<failed test:~2I ~_BASE-SEQ=~S ~_SNIPPET=~S ~_SEQ-TYPE=~S ~_DECLAREDNESS=~S ~_OPTIMIZATION=~S~:@>"
114                        base-seq
115                        snippet
116                        seq-type
117                        declaredness
118                        optimization)))))))))
119 (defun for-every-seq (base-seq snippets)
120   (dolist (snippet snippets)
121     (for-every-seq-1 base-seq snippet)))
122
123 ;;; a wrapper to hide declared type information from the compiler, so
124 ;;; we don't get stopped by compiler warnings about e.g. compiling
125 ;;; (POSITION 1 #() :KEY #'ABS) when #() has been coerced to a string.
126 (defun indiscriminate (fun)
127   (lambda (&rest rest) (apply fun rest)))
128
129 ;;; asymmetric test arg order example from ANSI FIND definition page
130 (assert (eql #\space ; original example, depends on ASCII character ordering
131              (find #\d "here are some letters that can be looked at"
132                    :test #'char>)))
133 (assert (eql #\e ; modified example, depends only on standard a-z ordering
134              (find #\f "herearesomeletters" :test #'char>)))
135 (assert (eql 4 ; modified more, avoids charset technicalities completely
136              (find 5 '(6 4) :test '>)))
137
138 (with-test (:name sequence:emptyp)
139   (for-every-seq #()
140     '((eq t (sequence:emptyp seq))))
141   (for-every-seq #(1)
142     '((eq nil (sequence:emptyp seq)))))
143
144 ;;; tests of FIND, POSITION, FIND-IF, and POSITION-IF (and a few for
145 ;;; deprecated FIND-IF-NOT and POSITION-IF-NOT too)
146 (for-every-seq #()
147   '((null (find 1 seq))
148     (null (find 1 seq :from-end t))
149     (null (position 1 seq :key (indiscriminate #'abs)))
150     (null (position nil seq :test (constantly t)))
151     (null (position nil seq :test nil))
152     (null (position nil seq :test-not nil))
153     (null (find-if #'1+ seq :key (indiscriminate #'log)))
154     (null (position-if #'identity seq :from-end t))
155     (null (find-if-not #'packagep seq))
156     (null (position-if-not #'packagep seq :key nil))))
157 (for-every-seq #(1)
158   '((null (find 2 seq))
159     ;; Get the argument ordering for asymmetric tests like #'> right.
160     ;; (bug reported and fixed by Alexey Dejneka sbcl-devel 2001-10-17)
161     (eql 1 (find 2 seq :test #'>))
162     (find 2 seq :key #'1+)
163     (find 1 seq :from-end t)
164     (null (find 1 seq :from-end t :start 1))
165     (null (find 0 seq :from-end t))
166     (eql 0 (position 1 seq :key #'abs))
167     (null (position nil seq :test 'equal))
168     (eql 1 (find-if #'1- seq :key #'log))
169     (eql 0 (position-if #'identity seq :from-end t))
170     (null (find-if-not #'sin seq))
171     (eql 0 (position-if-not #'packagep seq :key 'identity))))
172 (for-every-seq #(1 2 3 2 1)
173   '((find 3 seq)
174     (find 3 seq :from-end 'yes)
175     (eql 1 (position 1.5 seq :test #'<))
176     (eql 0 (position 0 seq :key '1-))
177     (eql 4 (position 0 seq :key '1- :from-end t))
178     (eql 2 (position 4 seq :key '1+))
179     (eql 2 (position 4 seq :key '1+ :from-end t))
180     (eql 1 (position 2 seq))
181     (eql 1 (position 2 seq :start 1))
182     (null (find 2 seq :start 1 :end 1))
183     (eql 3 (position 2 seq :start 2))
184     (eql 3 (position 2 seq :key nil :from-end t))
185     (eql 2 (position 3 seq :test '=))
186     (eql 0 (position 3 seq :test-not 'equalp))
187     (eql 2 (position 3 seq :test 'equal :from-end t))
188     (null (position 4 seq :test #'eql))
189     (null (find-if #'packagep seq))
190     (eql 1 (find-if #'plusp seq))
191     (eql 3 (position-if #'plusp seq :key #'1- :from-end t))
192     (eql 1 (position-if #'evenp seq))
193     (eql 3 (position-if #'evenp seq :from-end t))
194     (eql 2 (position-if #'plusp seq :from-end nil :key '1- :start 2))
195     (eql 3 (position-if #'plusp seq :from-end t :key '1- :start 2))
196     (null (position-if #'plusp seq :from-end t :key '1- :start 2 :end 2))
197     (null (find-if-not #'plusp seq))
198     (eql 0 (position-if-not #'evenp seq))
199     (eql 0 (search #(1) seq))
200     (eql 1 (search #(4 5) seq :key 'oddp))
201     (eql 1 (search #(-2) seq :test (lambda (a b) (= (- a) b))))
202     (eql 4 (search #(1) seq :start2 1))
203     (null (search #(3) seq :start2 3))
204     (eql 2 (search #(3) seq :start2 2))
205     (eql 0 (search #(1 2) seq))
206     (null (search #(2 1 3) seq))
207     (eql 0 (search #(0 1 2 4) seq :start1 1 :end1 3))
208     (eql 3 (search #(0 2 1 4) seq :start1 1 :end1 3))
209     (eql 4 (search #(1) seq :from-end t))
210     (eql 0 (search #(1 2) seq :from-end t))
211     (null (search #(1 2) seq :from-end t :start2 1))
212     (eql 0 (search #(0 1 2 4) seq :from-end t :start1 1 :end1 3))
213     (eql 3 (search #(0 2 1 4) seq :from-end t :start1 1 :end1 3))
214     (null (search #(2 1 3) seq :from-end t))))
215 (for-every-seq "string test"
216   '((null (find 0 seq))
217     (null (find #\D seq :key #'char-upcase))
218     (find #\E seq :key #'char-upcase)
219     (null (find #\e seq :key #'char-upcase))
220     (eql 3 (position #\i seq))
221     (eql 0 (position #\s seq :key #'char-downcase))
222     (eql 1 (position #\s seq :key #'char-downcase :test #'char/=))
223     (eql 9 (position #\s seq :from-end t :test #'char=))
224     (eql 10 (position #\s seq :from-end t :test #'char/=))
225     (eql 4 (position #\N seq :from-end t :key 'char-upcase :test #'char-equal))
226     (eql 5 (position-if (lambda (c) (equal #\g c)) seq))
227     (eql 5 (position-if (lambda (c) (equal #\g c)) seq :from-end t))
228     (find-if #'characterp seq)
229     (find-if (lambda (c) (typep c 'base-char)) seq :from-end t)
230     (null (find-if 'upper-case-p seq))))
231
232 ;;; SUBSEQ
233 (let ((avec (make-array 10
234                         :fill-pointer 4
235                         :initial-contents '(0 1 2 3 iv v vi vii iix ix))))
236   ;; These first five always worked AFAIK.
237   (assert (equalp (subseq avec 0 3) #(0 1 2)))
238   (assert (equalp (subseq avec 3 3) #()))
239   (assert (equalp (subseq avec 1 3) #(1 2)))
240   (assert (equalp (subseq avec 1) #(1 2 3)))
241   (assert (equalp (subseq avec 1 4) #(1 2 3)))
242   ;; SBCL bug found ca. 2002-05-01 by OpenMCL's correct handling of
243   ;; SUBSEQ, CSR's driving portable cross-compilation far enough to
244   ;; reach the SUBSEQ calls in assem.lisp, and WHN's sleazy
245   ;; translation of old CMU CL new-assem.lisp into sufficiently grotty
246   ;; portable Lisp that it passed suitable illegal values to SUBSEQ to
247   ;; exercise the bug:-|
248   ;;
249   ;; SUBSEQ should check its END value against logical LENGTH, not
250   ;; physical ARRAY-DIMENSION 0.
251   ;;
252   ;; fixed in sbcl-0.7.4.22 by WHN
253   (assert (null (ignore-errors (aref (subseq avec 1 5) 0)))))
254
255 ;;; FILL
256 (defun test-fill-typecheck (x)
257   (declare (optimize (safety 3) (space 2) (speed 1)))
258   (fill (make-string 10) x))
259
260 (assert (string= (test-fill-typecheck #\@) "@@@@@@@@@@"))
261 ;;; BUG 186, fixed in sbcl-0.7.5.5
262 (assert (null (ignore-errors (test-fill-typecheck 4097))))
263
264 ;;; MAKE-SEQUENCE, COERCE, CONCATENATE, MERGE, MAP and requested
265 ;;; result type (BUGs 46a, 46b, 66)
266 (macrolet ((assert-type-error (form)
267              `(assert (typep (nth-value 1 (ignore-errors ,form))
268                              'type-error))))
269   (dolist (type-stub '((simple-vector)
270                        (vector *)
271                        (vector (signed-byte 8))
272                        (vector (unsigned-byte 16))
273                        (vector (signed-byte 32))
274                        (simple-bit-vector)))
275     (declare (optimize safety))
276     (format t "~&~S~%" type-stub)
277     ;; MAKE-SEQUENCE
278     (assert (= (length (make-sequence `(,@type-stub) 10)) 10))
279     (assert (= (length (make-sequence `(,@type-stub 10) 10)) 10))
280     (assert-type-error (make-sequence `(,@type-stub 10) 11))
281     ;; COERCE
282     (assert (= (length (coerce '(0 0 0) `(,@type-stub))) 3))
283     (assert (= (length (coerce #(0 0 0) `(,@type-stub 3))) 3))
284     (assert-type-error (coerce #*111 `(,@type-stub 4)))
285     ;; CONCATENATE
286     (assert (= (length (concatenate `(,@type-stub) #(0 0 0) #*111)) 6))
287     (assert (equalp (concatenate `(,@type-stub) #(0 0 0) #*111)
288                    (coerce #(0 0 0 1 1 1) `(,@type-stub))))
289     (assert (= (length (concatenate `(,@type-stub 6) #(0 0 0) #*111)) 6))
290     (assert (equalp (concatenate `(,@type-stub 6) #(0 0 0) #*111)
291                    (coerce #(0 0 0 1 1 1) `(,@type-stub 6))))
292     (assert-type-error (concatenate `(,@type-stub 5) #(0 0 0) #*111))
293     ;; MERGE
294     (macrolet ((test (type)
295                  `(merge ,type (copy-seq #(0 1 0)) (copy-seq #*111) #'>)))
296       (assert (= (length (test `(,@type-stub))) 6))
297       (assert (equalp (test `(,@type-stub))
298                       (coerce #(1 1 1 0 1 0) `(,@type-stub))))
299       (assert (= (length (test `(,@type-stub 6))) 6))
300       (assert (equalp (test `(,@type-stub 6))
301                       (coerce #(1 1 1 0 1 0) `(,@type-stub 6))))
302       (assert-type-error (test `(,@type-stub 4))))
303     ;; MAP
304     (assert (= (length (map `(,@type-stub) #'logxor #(0 0 1 1) '(0 1 0 1))) 4))
305     (assert (equalp (map `(,@type-stub) #'logxor #(0 0 1 1) '(0 1 0 1))
306                    (coerce #(0 1 1 0) `(,@type-stub))))
307     (assert (= (length (map `(,@type-stub 4) #'logxor #(0 0 1 1) '(0 1 0 1)))
308                4))
309     (assert (equalp (map `(,@type-stub 4) #'logxor #(0 0 1 1) '(0 1 0 1))
310                    (coerce #(0 1 1 0) `(,@type-stub 4))))
311     (assert-type-error (map `(,@type-stub 5) #'logxor #(0 0 1 1) '(0 1 0 1))))
312   ;; some more CONCATENATE tests for strings
313   (locally
314       (declare (optimize safety))
315     (assert (string= (concatenate 'string "foo" " " "bar") "foo bar"))
316     (assert (string= (concatenate '(string 7) "foo" " " "bar") "foo bar"))
317     (assert-type-error (concatenate '(string 6) "foo" " " "bar"))
318     (assert (string= (concatenate '(string 6) "foo" #(#\b #\a #\r)) "foobar"))
319     (assert-type-error (concatenate '(string 7) "foo" #(#\b #\a #\r))))
320   ;; Non-VECTOR ARRAY types aren't allowed as vector type specifiers.
321   (locally
322     (declare (optimize safety))
323     (assert-type-error (concatenate 'simple-array "foo" "bar"))
324     (assert-type-error (map 'simple-array #'identity '(1 2 3)))
325     (assert (equalp #(11 13)
326                     (map '(simple-array fixnum (*)) #'+ '(1 2 3) '(10 11))))
327     (assert-type-error (coerce '(1 2 3) 'simple-array))
328     (assert-type-error (merge 'simple-array (list 1 3) (list 2 4) '<))
329     (assert (equalp #(3 2 1) (coerce '(3 2 1) '(vector fixnum))))
330     (assert-type-error (map 'array #'identity '(1 2 3)))
331     (assert-type-error (map '(array fixnum) #'identity '(1 2 3)))
332     (assert (equalp #(1 2 3) (coerce '(1 2 3) '(vector fixnum))))
333     ;; but COERCE has an exemption clause:
334     (assert (string= "foo" (coerce "foo" 'simple-array)))
335     ;; ... though not in all cases.
336     (assert-type-error (coerce '(#\f #\o #\o) 'simple-array))))
337
338 ;; CONCATENATE used to fail for generic sequences for result-type NULL.
339 (with-test (:name (concatenate :result-type-null :bug-1162301))
340   (assert (sequence:emptyp (concatenate 'null)))
341
342   (for-every-seq #()
343     '((sequence:emptyp (concatenate 'null seq))
344       (sequence:emptyp (concatenate 'null seq seq))
345       (sequence:emptyp (concatenate 'null seq #()))
346       (sequence:emptyp (concatenate 'null seq ""))))
347
348   (for-every-seq #(1)
349     (mapcar (lambda (form)
350               `(typep (nth-value 1 (ignore-errors ,form)) 'type-error))
351             '((concatenate 'null seq)
352               (concatenate 'null seq seq)
353               (concatenate 'null seq #())
354               (concatenate 'null seq "2")))))
355
356 ;;; As pointed out by Raymond Toy on #lisp IRC, MERGE had some issues
357 ;;; with user-defined types until sbcl-0.7.8.11
358 (deftype list-typeoid () 'list)
359 (assert (equal '(1 2 3 4) (merge 'list-typeoid (list 1 3) (list 2 4) '<)))
360 ;;; and also with types that weren't precicely LIST
361 (assert (equal '(1 2 3 4) (merge 'cons (list 1 3) (list 2 4) '<)))
362
363 ;;; but wait, there's more! The NULL and CONS types also have implicit
364 ;;; length requirements:
365 (macrolet ((assert-type-error (form)
366              `(assert (typep (nth-value 1 (ignore-errors ,form))
367                              'type-error))))
368   (locally
369       (declare (optimize safety))
370     ;; MAKE-SEQUENCE
371     (assert-type-error (make-sequence 'cons 0))
372     (assert-type-error (make-sequence 'null 1))
373     (assert-type-error (make-sequence '(cons t null) 0))
374     (assert-type-error (make-sequence '(cons t null) 2))
375     ;; KLUDGE: I'm not certain that this test actually tests for what
376     ;; it should test, in that the type deriver and optimizers might
377     ;; be too smart for the good of an exhaustive test system.
378     ;; However, it makes me feel good.  -- CSR, 2002-10-18
379     (assert (null (make-sequence 'null 0)))
380     (assert (= (length (make-sequence 'cons 3)) 3))
381     (assert (= (length (make-sequence '(cons t null) 1)) 1))
382     ;; and NIL is not a valid type for MAKE-SEQUENCE
383     (assert-type-error (make-sequence 'nil 0))
384     ;; COERCE
385     (assert-type-error (coerce #(1) 'null))
386     (assert-type-error (coerce #() 'cons))
387     (assert-type-error (coerce #() '(cons t null)))
388     (assert-type-error (coerce #(1 2) '(cons t null)))
389     (assert (null (coerce #() 'null)))
390     (assert (= (length (coerce #(1) 'cons)) 1))
391     (assert (= (length (coerce #(1) '(cons t null))) 1))
392     (assert-type-error (coerce #() 'nil))
393     ;; MERGE
394     (assert-type-error (merge 'null (list 1 3) (list 2 4) '<))
395     (assert-type-error (merge 'cons () () '<))
396     (assert (null (merge 'null () () '<)))
397     (assert (= (length (merge 'cons (list 1 3) (list 2 4) '<)) 4))
398     (assert (= (length (merge '(cons t (cons t (cons t (cons t null))))
399                               (list 1 3) (list 2 4)
400                               '<))
401                4))
402     (assert-type-error (merge 'nil () () '<))
403     ;; CONCATENATE
404     (assert-type-error (concatenate 'cons #() ()))
405     (assert-type-error (concatenate '(cons t null) #(1 2 3) #(4 5 6)))
406     (assert (= (length (concatenate 'cons #() '(1) "2 3")) 4))
407     (assert (= (length (concatenate '(cons t cons) '(1) "34")) 3))
408     (assert-type-error (concatenate 'nil '(3)))
409     ;; FIXME: tests for MAP to come when some brave soul implements
410     ;; the analogous type checking for MAP/%MAP.
411     ))
412 \f
413 ;;; ELT should signal an error of type TYPE-ERROR if its index
414 ;;; argument isn't a valid sequence index for sequence:
415 (defun test-elt-signal (x)
416   (elt x 3))
417 (assert (raises-error? (test-elt-signal "foo") type-error))
418 (assert (eql (test-elt-signal "foob") #\b))
419 (locally
420   (declare (optimize (safety 3)))
421   (assert (raises-error? (elt (list 1 2 3) 3) type-error)))
422 \f
423 ;;; confusion in the refactoring led to this signalling an unbound
424 ;;; variable, not a type error.
425 (defun svrefalike (x)
426   (svref x 0))
427 (assert (raises-error? (svrefalike #*0) type-error))
428 \f
429 ;;; checks for uniform bounding index handling.
430 ;;;
431 ;;; This used to be SAFETY 3 only, but bypassing these checks with
432 ;;; above-zero speed when SPEED > SAFETY is not The SBCL Way.
433 ;;;
434 ;;; KLUDGE: not all in one big form because that causes SBCL to spend
435 ;;; an absolute age trying to compile it.
436 (defmacro sequence-bounding-indices-test (&body body)
437   `(progn
438      (locally
439     ;; See Issues 332 [and 333(!)] in the CLHS
440     (declare (optimize (speed 3) (safety 1)))
441     (let ((string (make-array 10
442                               :fill-pointer 5
443                               :initial-element #\a
444                               :element-type 'base-char)))
445         ,(car body)
446         (format t "... BASE-CHAR")
447         (finish-output)
448         (flet ((reset ()
449                  (setf (fill-pointer string) 10)
450                  (fill string #\a)
451                  (setf (fill-pointer string) 5)))
452           (declare (ignorable #'reset))
453           ,@(cdr body))))
454     (locally
455       ;; See Issues 332 [and 333(!)] in the CLHS
456       (declare (optimize (speed 3) (safety 1)))
457       (let ((string (make-array 10
458                                 :fill-pointer 5
459                                 :initial-element #\a
460                                 :element-type 'character)))
461         ,(car body)
462         (format t "... CHARACTER")
463         (finish-output)
464       (flet ((reset ()
465                (setf (fill-pointer string) 10)
466                (fill string #\a)
467                (setf (fill-pointer string) 5)))
468         (declare (ignorable #'reset))
469           ,@(cdr body))))))
470
471 (declaim (notinline opaque-identity))
472 (defun opaque-identity (x) x)
473 ;;; Accessor SUBSEQ
474 (sequence-bounding-indices-test
475  (format t "~&/Accessor SUBSEQ")
476  (assert (string= (subseq string 0 5) "aaaaa"))
477  (assert (raises-error? (subseq string 0 6)))
478  (assert (raises-error? (subseq string (opaque-identity -1) 5)))
479  (assert (raises-error? (subseq string 4 2)))
480  (assert (raises-error? (subseq string 6)))
481  (assert (string= (setf (subseq string 0 5) "abcde") "abcde"))
482  (assert (string= (subseq string 0 5) "abcde"))
483  (reset)
484  (assert (raises-error? (setf (subseq string 0 6) "abcdef")))
485  (assert (raises-error? (setf (subseq string (opaque-identity -1) 5) "abcdef")))
486  (assert (raises-error? (setf (subseq string 4 2) "")))
487  (assert (raises-error? (setf (subseq string 6) "ghij"))))
488
489 ;;; Function COUNT, COUNT-IF, COUNT-IF-NOT
490 (sequence-bounding-indices-test
491  (format t "~&/Function COUNT, COUNT-IF, COUNT-IF-NOT")
492  (assert (= (count #\a string :start 0 :end nil) 5))
493  (assert (= (count #\a string :start 0 :end 5) 5))
494  (assert (raises-error? (count #\a string :start 0 :end 6)))
495  (assert (raises-error? (count #\a string :start (opaque-identity -1) :end 5)))
496  (assert (raises-error? (count #\a string :start 4 :end 2)))
497  (assert (raises-error? (count #\a string :start 6 :end 9)))
498  (assert (= (count-if #'alpha-char-p string :start 0 :end nil) 5))
499  (assert (= (count-if #'alpha-char-p string :start 0 :end 5) 5))
500  (assert (raises-error?
501           (count-if #'alpha-char-p string :start 0 :end 6)))
502  (assert (raises-error?
503           (count-if #'alpha-char-p string :start (opaque-identity -1) :end 5)))
504  (assert (raises-error?
505           (count-if #'alpha-char-p string :start 4 :end 2)))
506  (assert (raises-error?
507           (count-if #'alpha-char-p string :start 6 :end 9)))
508  (assert (= (count-if-not #'alpha-char-p string :start 0 :end nil) 0))
509  (assert (= (count-if-not #'alpha-char-p string :start 0 :end 5) 0))
510  (assert (raises-error?
511           (count-if-not #'alpha-char-p string :start 0 :end 6)))
512  (assert (raises-error?
513           (count-if-not #'alpha-char-p string :start (opaque-identity -1) :end 5)))
514  (assert (raises-error?
515           (count-if-not #'alpha-char-p string :start 4 :end 2)))
516  (assert (raises-error?
517           (count-if-not #'alpha-char-p string :start 6 :end 9))))
518
519 ;;; Function FILL
520 (sequence-bounding-indices-test
521  (format t "~&/Function FILL")
522  (assert (string= (fill string #\b :start 0 :end 5) "bbbbb"))
523  (assert (string= (fill string #\c :start 0 :end nil) "ccccc"))
524  (assert (raises-error? (fill string #\d :start 0 :end 6)))
525  (assert (raises-error? (fill string #\d :start (opaque-identity -1) :end 5)))
526  (assert (raises-error? (fill string #\d :start 4 :end 2)))
527  (assert (raises-error? (fill string #\d :start 6 :end 9))))
528
529 ;;; Function FIND, FIND-IF, FIND-IF-NOT
530 (sequence-bounding-indices-test
531  (format t "~&/Function FIND, FIND-IF, FIND-IF-NOT")
532  (assert (char= (find #\a string :start 0 :end nil) #\a))
533  (assert (char= (find #\a string :start 0 :end 5) #\a))
534  (assert (raises-error? (find #\a string :start 0 :end 6)))
535  (assert (raises-error? (find #\a string :start (opaque-identity -1) :end 5)))
536  (assert (raises-error? (find #\a string :start 4 :end 2)))
537  (assert (raises-error? (find #\a string :start 6 :end 9)))
538  (assert (char= (find-if #'alpha-char-p string :start 0 :end nil) #\a))
539  (assert (char= (find-if #'alpha-char-p string :start 0 :end 5) #\a))
540  (assert (raises-error?
541           (find-if #'alpha-char-p string :start 0 :end 6)))
542  (assert (raises-error?
543           (find-if #'alpha-char-p string :start (opaque-identity -1) :end 5)))
544  (assert (raises-error?
545           (find-if #'alpha-char-p string :start 4 :end 2)))
546  (assert (raises-error?
547           (find-if #'alpha-char-p string :start 6 :end 9)))
548  (assert (eq (find-if-not #'alpha-char-p string :start 0 :end nil) nil))
549  (assert (eq (find-if-not #'alpha-char-p string :start 0 :end 5) nil))
550  (assert (raises-error?
551           (find-if-not #'alpha-char-p string :start 0 :end 6)))
552  (assert (raises-error?
553           (find-if-not #'alpha-char-p string :start (opaque-identity -1) :end 5)))
554  (assert (raises-error?
555           (find-if-not #'alpha-char-p string :start 4 :end 2)))
556  (assert (raises-error?
557           (find-if-not #'alpha-char-p string :start 6 :end 9))))
558
559 ;;; Function MISMATCH
560 (sequence-bounding-indices-test
561  (format t "~&/Function MISMATCH")
562  (assert (null (mismatch string "aaaaa" :start1 0 :end1 nil)))
563  (assert (= (mismatch "aaab" string :start2 0 :end2 4) 3))
564  (assert (raises-error? (mismatch "aaaaaa" string :start2 0 :end2 6)))
565  (assert (raises-error? (mismatch string "aaaaaa" :start1 (opaque-identity -1) :end1 5)))
566  (assert (raises-error? (mismatch string "" :start1 4 :end1 2)))
567  (assert (raises-error? (mismatch "aaaa" string :start2 6 :end2 9))))
568
569 ;;; Function PARSE-INTEGER
570 (sequence-bounding-indices-test
571  (format t "~&/Function PARSE-INTEGER")
572  (setf (fill-pointer string) 10)
573  (setf (subseq string 0 10) "1234567890")
574  (setf (fill-pointer string) 5)
575  (assert (= (parse-integer string :start 0 :end 5) 12345))
576  (assert (= (parse-integer string :start 0 :end nil) 12345))
577  (assert (raises-error? (parse-integer string :start 0 :end 6)))
578  (assert (raises-error? (parse-integer string :start (opaque-identity -1) :end 5)))
579  (assert (raises-error? (parse-integer string :start 4 :end 2)))
580  (assert (raises-error? (parse-integer string :start 6 :end 9))))
581
582 ;;; Function PARSE-NAMESTRING
583 (sequence-bounding-indices-test
584  (format t "~&/Function PARSE-NAMESTRING")
585  (setf (fill-pointer string) 10)
586  (setf (subseq string 0 10)
587        #-win32 "/dev/ /tmp"
588        #+win32 "C:/   NUL")
589  (setf (fill-pointer string) 5)
590  (assert (truename (parse-namestring string nil *default-pathname-defaults*
591                                      :start 0 :end 5)))
592  (assert (truename (parse-namestring string nil *default-pathname-defaults*
593                                      :start 0 :end nil)))
594  (assert (raises-error? (parse-namestring string nil
595                                           *default-pathname-defaults*
596                                           :start 0 :end 6)))
597  (assert (raises-error? (parse-namestring string nil
598                                           *default-pathname-defaults*
599                                           :start (opaque-identity -1) :end 5)))
600  (assert (raises-error? (parse-namestring string nil
601                                           *default-pathname-defaults*
602                                           :start 4 :end 2)))
603  (assert (raises-error? (parse-namestring string nil
604                                           *default-pathname-defaults*
605                                           :start 6 :end 9))))
606
607 ;;; Function POSITION, POSITION-IF, POSITION-IF-NOT
608 (sequence-bounding-indices-test
609  (format t "~&/Function POSITION, POSITION-IF, POSITION-IF-NOT")
610
611  (assert (= (position #\a string :start 0 :end nil) 0))
612  (assert (= (position #\a string :start 0 :end 5) 0))
613  (assert (raises-error? (position #\a string :start 0 :end 6)))
614  (assert (raises-error? (position #\a string :start (opaque-identity -1) :end 5)))
615  (assert (raises-error? (position #\a string :start 4 :end 2)))
616  (assert (raises-error? (position #\a string :start 6 :end 9)))
617  (assert (= (position-if #'alpha-char-p string :start 0 :end nil) 0))
618  (assert (= (position-if #'alpha-char-p string :start 0 :end 5) 0))
619  (assert (raises-error?
620           (position-if #'alpha-char-p string :start 0 :end 6)))
621  (assert (raises-error?
622           (position-if #'alpha-char-p string :start (opaque-identity -1) :end 5)))
623  (assert (raises-error?
624           (position-if #'alpha-char-p string :start 4 :end 2)))
625  (assert (raises-error?
626           (position-if #'alpha-char-p string :start 6 :end 9)))
627  (assert (eq (position-if-not #'alpha-char-p string :start 0 :end nil) nil))
628  (assert (eq (position-if-not #'alpha-char-p string :start 0 :end 5) nil))
629  (assert (raises-error?
630           (position-if-not #'alpha-char-p string :start 0 :end 6)))
631  (assert (raises-error?
632           (position-if-not #'alpha-char-p string :start (opaque-identity -1) :end 5)))
633  (assert (raises-error?
634           (position-if-not #'alpha-char-p string :start 4 :end 2)))
635  (assert (raises-error?
636           (position-if-not #'alpha-char-p string :start 6 :end 9))))
637
638 ;;; Function READ-FROM-STRING
639 (sequence-bounding-indices-test
640  (format t "~&/Function READ-FROM-STRING")
641  (setf (subseq string 0 5) "(a b)")
642  (assert (equal (read-from-string string nil nil :start 0 :end 5) '(a b)))
643  (assert (equal (read-from-string string nil nil :start 0 :end nil) '(a b)))
644  (assert (raises-error? (read-from-string string nil nil :start 0 :end 6)))
645  (assert (raises-error? (read-from-string string nil nil :start (opaque-identity -1) :end 5)))
646  (assert (raises-error? (read-from-string string nil nil :start 4 :end 2)))
647  (assert (raises-error? (read-from-string string nil nil :start 6 :end 9))))
648
649 ;;; Function REDUCE
650 (sequence-bounding-indices-test
651  (format t "~&/Function REDUCE")
652  (setf (subseq string 0 5) "abcde")
653  (assert (equal (reduce #'list* string :from-end t :start 0 :end nil)
654                 '(#\a #\b #\c #\d . #\e)))
655  (assert (equal (reduce #'list* string :from-end t :start 0 :end 5)
656                 '(#\a #\b #\c #\d . #\e)))
657  (assert (raises-error? (reduce #'list* string :start 0 :end 6)))
658  (assert (raises-error? (reduce #'list* string :start (opaque-identity -1) :end 5)))
659  (assert (raises-error? (reduce #'list* string :start 4 :end 2)))
660  (assert (raises-error? (reduce #'list* string :start 6 :end 9))))
661
662 ;;; Function REMOVE, REMOVE-IF, REMOVE-IF-NOT, DELETE, DELETE-IF,
663 ;;; DELETE-IF-NOT
664 (sequence-bounding-indices-test
665  (format t "~&/Function REMOVE, REMOVE-IF, REMOVE-IF-NOT, ...")
666  (assert (equal (remove #\a string :start 0 :end nil) ""))
667  (assert (equal (remove #\a string :start 0 :end 5) ""))
668  (assert (raises-error? (remove #\a string :start 0 :end 6)))
669  (assert (raises-error? (remove #\a string :start (opaque-identity -1) :end 5)))
670  (assert (raises-error? (remove #\a string :start 4 :end 2)))
671  (assert (raises-error? (remove #\a string :start 6 :end 9)))
672  (assert (equal (remove-if #'alpha-char-p string :start 0 :end nil) ""))
673  (assert (equal (remove-if #'alpha-char-p string :start 0 :end 5) ""))
674  (assert (raises-error?
675           (remove-if #'alpha-char-p string :start 0 :end 6)))
676  (assert (raises-error?
677           (remove-if #'alpha-char-p string :start (opaque-identity -1) :end 5)))
678  (assert (raises-error?
679           (remove-if #'alpha-char-p string :start 4 :end 2)))
680  (assert (raises-error?
681           (remove-if #'alpha-char-p string :start 6 :end 9)))
682  (assert (equal (remove-if-not #'alpha-char-p string :start 0 :end nil)
683                 "aaaaa"))
684  (assert (equal (remove-if-not #'alpha-char-p string :start 0 :end 5)
685                 "aaaaa"))
686  (assert (raises-error?
687           (remove-if-not #'alpha-char-p string :start 0 :end 6)))
688  (assert (raises-error?
689           (remove-if-not #'alpha-char-p string :start (opaque-identity -1) :end 5)))
690  (assert (raises-error?
691           (remove-if-not #'alpha-char-p string :start 4 :end 2)))
692  (assert (raises-error?
693           (remove-if-not #'alpha-char-p string :start 6 :end 9))))
694 (sequence-bounding-indices-test
695  (format t "~&/... DELETE, DELETE-IF, DELETE-IF-NOT")
696  (assert (equal (delete #\a string :start 0 :end nil) ""))
697  (reset)
698  (assert (equal (delete #\a string :start 0 :end 5) ""))
699  (reset)
700  (assert (raises-error? (delete #\a string :start 0 :end 6)))
701  (reset)
702  (assert (raises-error? (delete #\a string :start (opaque-identity -1) :end 5)))
703  (reset)
704  (assert (raises-error? (delete #\a string :start 4 :end 2)))
705  (reset)
706  (assert (raises-error? (delete #\a string :start 6 :end 9)))
707  (reset)
708  (assert (equal (delete-if #'alpha-char-p string :start 0 :end nil) ""))
709  (reset)
710  (assert (equal (delete-if #'alpha-char-p string :start 0 :end 5) ""))
711  (reset)
712  (assert (raises-error?
713           (delete-if #'alpha-char-p string :start 0 :end 6)))
714  (reset)
715  (assert (raises-error?
716           (delete-if #'alpha-char-p string :start (opaque-identity -1) :end 5)))
717  (reset)
718  (assert (raises-error?
719           (delete-if #'alpha-char-p string :start 4 :end 2)))
720  (reset)
721  (assert (raises-error?
722           (delete-if #'alpha-char-p string :start 6 :end 9)))
723  (reset)
724  (assert (equal (delete-if-not #'alpha-char-p string :start 0 :end nil)
725                 "aaaaa"))
726  (reset)
727  (assert (equal (delete-if-not #'alpha-char-p string :start 0 :end 5)
728                 "aaaaa"))
729  (reset)
730  (assert (raises-error?
731           (delete-if-not #'alpha-char-p string :start 0 :end 6)))
732  (reset)
733  (assert (raises-error?
734           (delete-if-not #'alpha-char-p string :start (opaque-identity -1) :end 5)))
735  (reset)
736  (assert (raises-error?
737           (delete-if-not #'alpha-char-p string :start 4 :end 2)))
738  (reset)
739  (assert (raises-error?
740           (delete-if-not #'alpha-char-p string :start 6 :end 9))))
741
742 ;;; Function REMOVE-DUPLICATES, DELETE-DUPLICATES
743 (sequence-bounding-indices-test
744  (format t "~&/Function REMOVE-DUPLICATES, DELETE-DUPLICATES")
745  (assert (string= (remove-duplicates string :start 0 :end 5) "a"))
746  (assert (string= (remove-duplicates string :start 0 :end nil) "a"))
747  (assert (raises-error? (remove-duplicates string :start 0 :end 6)))
748  (assert (raises-error? (remove-duplicates string :start (opaque-identity -1) :end 5)))
749  (assert (raises-error? (remove-duplicates string :start 4 :end 2)))
750  (assert (raises-error? (remove-duplicates string :start 6 :end 9)))
751  (assert (string= (delete-duplicates string :start 0 :end 5) "a"))
752  (reset)
753  (assert (string= (delete-duplicates string :start 0 :end nil) "a"))
754  (reset)
755  (assert (raises-error? (delete-duplicates string :start 0 :end 6)))
756  (reset)
757  (assert (raises-error? (delete-duplicates string :start (opaque-identity -1) :end 5)))
758  (reset)
759  (assert (raises-error? (delete-duplicates string :start 4 :end 2)))
760  (reset)
761  (assert (raises-error? (delete-duplicates string :start 6 :end 9))))
762
763 ;;; Function REPLACE
764 (sequence-bounding-indices-test
765  (format t "~&/Function REPLACE")
766  (assert (string= (replace string "bbbbb" :start1 0 :end1 5) "bbbbb"))
767  (assert (string= (replace (copy-seq "ccccc")
768                            string
769                            :start2 0 :end2 nil) "bbbbb"))
770  (assert (raises-error? (replace string "ccccc" :start1 0 :end1 6)))
771  (assert (raises-error? (replace string "ccccc" :start2 (opaque-identity -1) :end2 5)))
772  (assert (raises-error? (replace string "ccccc" :start1 4 :end1 2)))
773  (assert (raises-error? (replace string "ccccc" :start1 6 :end1 9))))
774
775 ;;; Function SEARCH
776 (sequence-bounding-indices-test
777  (format t "~&/Function SEARCH")
778  (assert (= (search "aa" string :start2 0 :end2 5) 0))
779  (assert (null (search string "aa" :start1 0 :end2 nil)))
780  (assert (raises-error? (search "aa" string :start2 0 :end2 6)))
781  (assert (raises-error? (search "aa" string :start2 (opaque-identity -1) :end2 5)))
782  (assert (raises-error? (search "aa" string :start2 4 :end2 2)))
783  (assert (raises-error? (search "aa" string :start2 6 :end2 9))))
784
785 ;;; Function STRING-UPCASE, STRING-DOWNCASE, STRING-CAPITALIZE,
786 ;;; NSTRING-UPCASE, NSTRING-DOWNCASE, NSTRING-CAPITALIZE
787 (defmacro string-case-frob (fn)
788   `(progn
789     (assert (raises-error? (,fn string :start 0 :end 6)))
790     (assert (raises-error? (,fn string :start (opaque-identity -1) :end 5)))
791     (assert (raises-error? (,fn string :start 4 :end 2)))
792     (assert (raises-error? (,fn string :start 6 :end 9)))))
793
794 (sequence-bounding-indices-test
795  (format t "~&/Function STRING-UPCASE, STRING-DOWNCASE, STRING-CAPITALIZE, ...")
796  (string-case-frob string-upcase)
797  (string-case-frob string-downcase)
798  (string-case-frob string-capitalize)
799  (format t "~&/... NSTRING-UPCASE, NSTRING-DOWNCASE, NSTRING-CAPITALIZE")
800  (string-case-frob nstring-upcase)
801  (string-case-frob nstring-downcase)
802  (string-case-frob nstring-capitalize))
803
804 ;;; Function STRING=, STRING/=, STRING<, STRING>, STRING<=, STRING>=,
805 ;;; STRING-EQUAL, STRING-NOT-EQUAL, STRING-LESSP, STRING-GREATERP,
806 ;;; STRING-NOT-GREATERP, STRING-NOT-LESSP
807 (defmacro string-predicate-frob (fn)
808   `(progn
809     (,fn string "abcde" :start1 0 :end1 5)
810     (,fn "fghij" string :start2 0 :end2 nil)
811     (assert (raises-error? (,fn string "klmno"
812                                 :start1 0 :end1 6)))
813     (assert (raises-error? (,fn "pqrst" string
814                                 :start2 (opaque-identity -1) :end2 5)))
815     (assert (raises-error? (,fn "uvwxy" string
816                                 :start1 4 :end1 2)))
817     (assert (raises-error? (,fn string "z" :start2 6 :end2 9)))))
818 (sequence-bounding-indices-test
819  (format t "~&/Function STRING=, STRING/=, STRING<, STRING>, STRING<=, STRING>=, ...")
820  (string-predicate-frob string=)
821  (string-predicate-frob string/=)
822  (string-predicate-frob string<)
823  (string-predicate-frob string>)
824  (string-predicate-frob string<=)
825  (string-predicate-frob string>=))
826 (sequence-bounding-indices-test
827  (format t "~&/... STRING-EQUAL, STRING-NOT-EQUAL, STRING-LESSP, ...")
828  (string-predicate-frob string-equal)
829  (string-predicate-frob string-not-equal)
830  (string-predicate-frob string-lessp))
831 (sequence-bounding-indices-test
832  (format t "~&/... STRING-GREATERP, STRING-NOT-GREATERP, STRING-NOT-LESSP")
833  (string-predicate-frob string-greaterp)
834  (string-predicate-frob string-not-greaterp)
835  (string-predicate-frob string-not-lessp))
836
837 ;;; Function SUBSTITUTE, SUBSTITUTE-IF, SUBSTITUTE-IF-NOT,
838 ;;; NSUBSTITUTE, NSUBSTITUTE-IF, NSUBSTITUTE-IF-NOT
839 (sequence-bounding-indices-test
840  (format t "~&/Function SUBSTITUTE, SUBSTITUTE-IF, SUBSTITUTE-IF-NOT, ...")
841  (assert (string= (substitute #\b #\a string :start 0 :end 5) "bbbbb"))
842  (assert (string= (substitute #\c #\a string :start 0 :end nil)
843                   "ccccc"))
844  (assert (raises-error? (substitute #\b #\a string :start 0 :end 6)))
845  (assert (raises-error? (substitute #\b #\a string :start (opaque-identity -1) :end 5)))
846  (assert (raises-error? (substitute #\b #\a string :start 4 :end 2)))
847  (assert (raises-error? (substitute #\b #\a string :start 6 :end 9)))
848  (assert (string= (substitute-if #\b #'alpha-char-p string
849                                  :start 0 :end 5)
850                   "bbbbb"))
851  (assert (string= (substitute-if #\c #'alpha-char-p string
852                                  :start 0 :end nil)
853                   "ccccc"))
854  (assert (raises-error? (substitute-if #\b #'alpha-char-p string
855                                        :start 0 :end 6)))
856  (assert (raises-error? (substitute-if #\b #'alpha-char-p string
857                                        :start (opaque-identity -1) :end 5)))
858  (assert (raises-error? (substitute-if #\b #'alpha-char-p string
859                                        :start 4 :end 2)))
860  (assert (raises-error? (substitute-if #\b #'alpha-char-p string
861                                        :start 6 :end 9)))
862  (assert (string= (substitute-if-not #\b #'alpha-char-p string
863                                      :start 0 :end 5)
864                   "aaaaa"))
865  (assert (string= (substitute-if-not #\c #'alpha-char-p string
866                                      :start 0 :end nil)
867                   "aaaaa"))
868  (assert (raises-error? (substitute-if-not #\b #'alpha-char-p string
869                                            :start 0 :end 6)))
870  (assert (raises-error? (substitute-if-not #\b #'alpha-char-p string
871                                            :start (opaque-identity -1) :end 5)))
872  (assert (raises-error? (substitute-if-not #\b #'alpha-char-p string
873                                            :start 4 :end 2)))
874  (assert (raises-error? (substitute-if-not #\b #'alpha-char-p string
875                                            :start 6 :end 9))))
876 (sequence-bounding-indices-test
877  (format t "~&/... NSUBSTITUTE, NSUBSTITUTE-IF, NSUBSTITUTE-IF-NOT")
878  (assert (string= (nsubstitute #\b #\a string :start 0 :end 5) "bbbbb"))
879  (reset)
880  (assert (string= (nsubstitute #\c #\a string :start 0 :end nil)
881                   "ccccc"))
882  (reset)
883  (assert (raises-error? (nsubstitute #\b #\a string :start 0 :end 6)))
884  (reset)
885  (assert (raises-error? (nsubstitute #\b #\a string :start (opaque-identity -1) :end 5)))
886  (reset)
887  (assert (raises-error? (nsubstitute #\b #\a string :start 4 :end 2)))
888  (reset)
889  (assert (raises-error? (nsubstitute #\b #\a string :start 6 :end 9)))
890  (reset)
891  (assert (string= (nsubstitute-if #\b #'alpha-char-p string
892                                   :start 0 :end 5)
893                   "bbbbb"))
894  (reset)
895  (assert (string= (nsubstitute-if #\c #'alpha-char-p string
896                                   :start 0 :end nil)
897                   "ccccc"))
898  (reset)
899  (assert (raises-error? (nsubstitute-if #\b #'alpha-char-p string
900                                         :start 0 :end 6)))
901  (reset)
902  (assert (raises-error? (nsubstitute-if #\b #'alpha-char-p string
903                                         :start (opaque-identity -1) :end 5)))
904  (reset)
905  (assert (raises-error? (nsubstitute-if #\b #'alpha-char-p string
906                                         :start 4 :end 2)))
907  (reset)
908  (assert (raises-error? (nsubstitute-if #\b #'alpha-char-p string
909                                         :start 6 :end 9)))
910  (reset)
911  (assert (string= (nsubstitute-if-not #\b #'alpha-char-p string
912                                       :start 0 :end 5)
913                   "aaaaa"))
914  (reset)
915  (assert (string= (nsubstitute-if-not #\c #'alpha-char-p string
916                                       :start 0 :end nil)
917                   "aaaaa"))
918  (reset)
919  (assert (raises-error? (nsubstitute-if-not #\b #'alpha-char-p string
920                                             :start 0 :end 6)))
921  (reset)
922  (assert (raises-error? (nsubstitute-if-not #\b #'alpha-char-p string
923                                             :start (opaque-identity -1) :end 5)))
924  (reset)
925  (assert (raises-error? (nsubstitute-if-not #\b #'alpha-char-p string
926                                             :start 4 :end 2)))
927  (reset)
928  (assert (raises-error? (nsubstitute-if-not #\b #'alpha-char-p string
929                                             :start 6 :end 9))))
930 ;;; Function WRITE-STRING, WRITE-LINE
931 (sequence-bounding-indices-test
932  (format t "~&/Function WRITE-STRING, WRITE-LINE")
933  (write-string string *standard-output* :start 0 :end 5)
934  (write-string string *standard-output* :start 0 :end nil)
935  (assert (raises-error? (write-string string *standard-output*
936                                       :start 0 :end 6)))
937  (assert (raises-error? (write-string string *standard-output*
938                                       :start (opaque-identity -1) :end 5)))
939  (assert (raises-error? (write-string string *standard-output*
940                                       :start 4 :end 2)))
941  (assert (raises-error? (write-string string *standard-output*
942                                       :start 6 :end 9)))
943  (write-line string *standard-output* :start 0 :end 5)
944  (write-line string *standard-output* :start 0 :end nil)
945  (assert (raises-error? (write-line string *standard-output*
946                                       :start 0 :end 6)))
947  (assert (raises-error? (write-line string *standard-output*
948                                       :start (opaque-identity -1) :end 5)))
949  (assert (raises-error? (write-line string *standard-output*
950                                       :start 4 :end 2)))
951  (assert (raises-error? (write-line string *standard-output*
952                                       :start 6 :end 9))))
953
954 ;;; Macro WITH-INPUT-FROM-STRING
955 (sequence-bounding-indices-test
956  (format t "~&/Macro WITH-INPUT-FROM-STRING")
957  (with-input-from-string (s string :start 0 :end 5)
958    (assert (char= (read-char s) #\a)))
959  (with-input-from-string (s string :start 0 :end nil)
960    (assert (char= (read-char s) #\a)))
961  (assert (raises-error?
962           (with-input-from-string (s string :start 0 :end 6)
963             (read-char s))))
964  (assert (raises-error?
965           (with-input-from-string (s string :start (opaque-identity -1) :end 5)
966             (read-char s))))
967  (assert (raises-error?
968           (with-input-from-string (s string :start 4 :end 2)
969             (read-char s))))
970  (assert (raises-error?
971           (with-input-from-string (s string :start 6 :end 9)
972             (read-char s)))))
973 \f
974 ;;; testing bit-bashing according to _The Practice of Programming_
975 (defun fill-bytes-for-testing (bitsize)
976   "Return a list of 'bytes' of type (MOD BITSIZE)."
977   (remove-duplicates (list 0
978                            (1- (ash 1 (1- bitsize)))
979                            (ash 1 (1- bitsize))
980                            (1- (ash 1 bitsize)))))
981
982 (defun fill-with-known-value (value size &rest vectors)
983   (dolist (vec vectors)
984     (dotimes (i size)
985       (setf (aref vec i) value))))
986
987 (defun collect-fill-amounts (n-power)
988   (remove-duplicates
989    (loop for i from 0 upto n-power
990          collect (1- (expt 2 i))
991          collect (expt 2 i)
992          collect (1+ (expt 2 i)))))
993
994 (defun test-fill-bashing (bitsize padding-amount n-power)
995   (let* ((size (+ (* padding-amount 2) (expt 2 n-power) (* padding-amount 2)))
996          (standard (make-array size :element-type `(unsigned-byte ,bitsize)))
997          (bashed (make-array size :element-type `(unsigned-byte ,bitsize)))
998          (fill-amounts (collect-fill-amounts n-power))
999          (bash-function (intern (format nil "UB~A-BASH-FILL" bitsize)
1000                                 (find-package "SB-KERNEL"))))
1001     (format t "~&/Function ~A..." bash-function)
1002     (loop for offset from padding-amount below (* 2 padding-amount) do
1003           (dolist (c (fill-bytes-for-testing bitsize))
1004             (dolist (n fill-amounts)
1005               (fill-with-known-value (mod (lognot c) (ash 1 bitsize)) n
1006                                      standard bashed)
1007               ;; fill vectors
1008               ;; a) the standard slow way
1009               (locally (declare (notinline fill))
1010                 (fill standard c :start offset :end (+ offset n)))
1011               ;; b) the blazingly fast way
1012               (let ((value (loop for i from 0 by bitsize
1013                                  until (= i sb-vm:n-word-bits)
1014                                  sum (ash c i))))
1015                 (funcall bash-function value bashed offset n))
1016               ;; check for errors
1017               (when (mismatch standard bashed)
1018                 (format t "Test with offset ~A, fill ~A and length ~A failed.~%"
1019                         offset c n)
1020                 (format t "Mismatch: ~A ~A~%"
1021                         (subseq standard 0 (+ offset n 1))
1022                         (subseq bashed 0 (+ offset n 1)))
1023                 (return-from test-fill-bashing nil))))
1024           finally (return t))))
1025
1026 (defun test-copy-bashing (bitsize padding-amount n-power)
1027   (let* ((size (+ (* padding-amount 2) (expt 2 n-power) (* padding-amount 2)))
1028          (standard-dst (make-array size :element-type `(unsigned-byte ,bitsize)))
1029          (bashed-dst (make-array size :element-type `(unsigned-byte ,bitsize)))
1030          (source (make-array size :element-type `(unsigned-byte ,bitsize)))
1031          (fill-amounts (collect-fill-amounts n-power))
1032          (bash-function (intern (format nil "UB~A-BASH-COPY" bitsize)
1033                                 (find-package "SB-KERNEL"))))
1034     (format t "~&/Function ~A..." bash-function)
1035     (do ((source-offset padding-amount (1+ source-offset)))
1036         ((>= source-offset (* padding-amount 2))
1037          ;; success!
1038          t)
1039      (do ((target-offset padding-amount (1+ target-offset)))
1040          ((>= target-offset (* padding-amount 2)))
1041        (dolist (c (fill-bytes-for-testing bitsize))
1042          (dolist (n fill-amounts)
1043            (fill-with-known-value (mod (lognot c) (ash 1 bitsize)) size
1044                                   source standard-dst bashed-dst)
1045            ;; fill with test data
1046            (fill source c :start source-offset :end (+ source-offset n))
1047            ;; copy filled test data to test vectors
1048            ;; a) the slow way
1049            (replace standard-dst source
1050                     :start1 target-offset :end1 (+ target-offset n)
1051                     :start2 source-offset :end2 (+ source-offset n))
1052            ;; b) the blazingly fast way
1053            (funcall bash-function source source-offset
1054                     bashed-dst target-offset n)
1055            ;; check for errors
1056            (when (mismatch standard-dst bashed-dst)
1057              (format t "Test with target-offset ~A, source-offset ~A, fill ~A, and length ~A failed.~%"
1058                      target-offset source-offset c n)
1059              (format t "Mismatch:~% correct ~A~% actual  ~A~%"
1060                      standard-dst
1061                      bashed-dst)
1062              (return-from test-copy-bashing nil))))))))
1063
1064 ;; Too slow for the interpreter
1065 #+#.(cl:if (cl:eq sb-ext:*evaluator-mode* :compile) '(and) '(or))
1066 (loop for i = 1 then (* i 2) do
1067      ;; the bare '13' here is fairly arbitrary, except that it's been
1068      ;; reduced from '32', which made the tests take aeons; '8' provides
1069      ;; a good range of lengths over which to fill and copy, which
1070      ;; should tease out most errors in the code (if any exist).  (It
1071      ;; also makes this part of the test suite finish reasonably
1072      ;; quickly.)
1073      (assert (time (test-fill-bashing i 13 8)))
1074      (assert (time (test-copy-bashing i 13 8)))
1075      until (= i sb-vm:n-word-bits))
1076
1077 (defun test-inlined-bashing (bitsize)
1078   ;; We have to compile things separately for each bitsize so the
1079   ;; compiler will work out the array type and trigger the REPLACE
1080   ;; transform.
1081   (let ((lambda-form
1082          `(lambda ()
1083             (let* ((n-elements-per-word ,(truncate sb-vm:n-word-bits bitsize))
1084                    (size (* 3 n-elements-per-word))
1085                    (standard-dst (make-array size :element-type '(unsigned-byte ,bitsize)))
1086                    (bashed-dst (make-array size :element-type '(unsigned-byte ,bitsize)))
1087                    (source (make-array size :element-type '(unsigned-byte ,bitsize))))
1088               (declare (type (simple-array (unsigned-byte ,bitsize) (*))
1089                              source standard-dst bashed-dst))
1090               (do ((i 0 (1+ i))
1091                    (offset n-elements-per-word (1+ offset)))
1092                   ((>= offset (* 2 n-elements-per-word)) t)
1093                 (dolist (c (fill-bytes-for-testing ,bitsize))
1094                   (fill-with-known-value (mod (lognot c) (ash 1 ,bitsize)) size
1095                                          source standard-dst bashed-dst)
1096                   ;; fill with test-data
1097                   (fill source c :start offset :end (+ offset n-elements-per-word))
1098                   ;; copy filled data to test vectors
1099                   ;;
1100                   ;; a) the slow way (which is actually fast, since this
1101                   ;; should be transformed into UB*-BASH-COPY)
1102                   (replace standard-dst source
1103                            :start1 (- offset n-elements-per-word i)
1104                            :start2 (- offset n-elements-per-word i)
1105                            :end1 offset :end2 offset)
1106                   ;; b) the fast way--we fold the
1107                   ;; :START{1,2} arguments above ourselves
1108                   ;; to trigger the REPLACE transform
1109                   (replace bashed-dst source
1110                            :start1 0 :start2 0 :end1 offset :end2 offset)
1111                   ;; check for errors
1112                   (when (or (mismatch standard-dst bashed-dst)
1113                             ;; trigger COPY-SEQ transform
1114                             (mismatch (copy-seq standard-dst) bashed-dst)
1115                             ;; trigger SUBSEQ transform
1116                             (mismatch (subseq standard-dst (- offset n-elements-per-word i))
1117                                       bashed-dst))
1118                     (format t "Test with target-offset ~A, source-offset ~A, fill ~A, and length ~A failed.~%"
1119                             0 0 c offset)
1120                     (format t "Mismatch:~% correct ~A~% actual  ~A~%"
1121                             standard-dst
1122                             bashed-dst)
1123                     (return-from nil nil))))))))
1124     (funcall (compile nil lambda-form))))
1125
1126 #+#.(cl:if (cl:eq sb-ext:*evaluator-mode* :compile) '(and) '(or))
1127 (loop for i = 1 then (* i 2) do
1128       (assert (test-inlined-bashing i))
1129       until (= i sb-vm:n-word-bits))
1130 \f
1131 ;;; tests from the Sacla test suite via Eric Marsden, 2007-05-07
1132 (remove-duplicates (vector 1 2 2 1) :test-not (lambda (a b) (not (= a b))))
1133
1134 (delete-duplicates (vector #\a #\b #\c #\a)
1135                    :test-not (lambda (a b) (not (char-equal a b))))
1136
1137 ;;; FILL on lists
1138 (let ((l (list 1 2 3)))
1139   (assert (eq l (fill l 0 :start 1 :end 2)))
1140   (assert (equal l '(1 0 3)))
1141   (assert (eq l (fill l 'x :start 2 :end 3)))
1142   (assert (equal l '(1 0 x)))
1143   (assert (eq l (fill l 'y :start 1)))
1144   (assert (equal l '(1 y y)))
1145   (assert (eq l (fill l 'z :end 2)))
1146   (assert (equal l '(z z y)))
1147   (assert (eq l (fill l 1)))
1148   (assert (equal l '(1 1 1)))
1149   (assert (raises-error? (fill l 0 :start 4)))
1150   (assert (raises-error? (fill l 0 :end 4)))
1151   (assert (raises-error? (fill l 0 :start 2 :end 1))))
1152
1153 ;;; Both :TEST and :TEST-NOT provided
1154 (with-test (:name :test-and-test-not-to-adjoin)
1155   (let* ((wc 0)
1156          (fun
1157           (handler-bind (((and warning (not style-warning))
1158                           (lambda (w) (incf wc))))
1159             (compile nil `(lambda (item test test-not) (adjoin item '(1 2 3 :foo)
1160                                                                :test test
1161                                                                :test-not test-not))))))
1162     (assert (= 1 wc))
1163     (assert (eq :error
1164                 (handler-case
1165                     (funcall fun 1 #'eql (complement #'eql))
1166                   (error ()
1167                     :error))))))
1168 \f
1169 ;;; tests of deftype types equivalent to STRING or SIMPLE-STRING
1170 (deftype %string () 'string)
1171 (deftype %simple-string () 'simple-string)
1172 (deftype string-3 () '(string 3))
1173 (deftype simple-string-3 () '(simple-string 3))
1174
1175 (with-test (:name :user-defined-string-types-map-etc)
1176   (dolist (type '(%string %simple-string string-3 simple-string-3))
1177     (assert (string= "foo" (coerce '(#\f #\o #\o) type)))
1178     (assert (string= "foo" (map type 'identity #(#\f #\o #\o))))
1179     (assert (string= "foo" (merge type '(#\o) '(#\f #\o) 'char<)))
1180     (assert (string= "foo" (concatenate type '(#\f) "oo")))
1181     (assert (string= "ooo" (make-sequence type 3 :initial-element #\o)))))
1182 (with-test (:name :user-defined-string-types-map-etc-error)
1183   (dolist (type '(string-3 simple-string-3))
1184     (assert (raises-error? (coerce '(#\q #\u #\u #\x) type)))
1185     (assert (raises-error? (map type 'identity #(#\q #\u #\u #\x))))
1186     (assert (raises-error? (merge type '(#\q #\x) "uu" 'char<)))
1187     (assert (raises-error? (concatenate type "qu" '(#\u #\x))))
1188     (assert (raises-error? (make-sequence type 4 :initial-element #\u)))))
1189
1190 (defun test-bit-position (size set start end from-end res)
1191   (let ((v (make-array size :element-type 'bit :initial-element 0)))
1192     (dolist (i set)
1193       (setf (bit v i) 1))
1194     (dolist (f (list (compile nil
1195                               `(lambda (b v s e fe)
1196                                  (position b (the bit-vector v) :start s :end e :from-end fe)))
1197                      (compile nil
1198                               `(lambda (b v s e fe)
1199                                  (assert (eql b 1))
1200                                  (position 1 (the bit-vector v) :start s :end e :from-end fe)))
1201                      (compile nil
1202                               `(lambda (b v s e fe)
1203                                  (position b (the vector v) :start s :end e :from-end fe)))))
1204       (let ((got (funcall f 1 v start end from-end)))
1205         (unless (eql res got)
1206           (cerror "Continue" "POSITION 1, Wanted ~S, got ~S.~%  size = ~S, set = ~S, from-end = ~S"
1207                   res got
1208                   size set from-end)))))
1209   (let ((v (make-array size :element-type 'bit :initial-element 1)))
1210     (dolist (i set)
1211       (setf (bit v i) 0))
1212     (dolist (f (list (compile nil
1213                               `(lambda (b v s e fe)
1214                                  (position b (the bit-vector v) :start s :end e :from-end fe)))
1215                      (compile nil
1216                               `(lambda (b v s e fe)
1217                                  (assert (eql b 0))
1218                                  (position 0 (the bit-vector v) :start s :end e :from-end fe)))
1219                      (compile nil
1220                               `(lambda (b v s e fe)
1221                                  (position b (the vector v) :start s :end e :from-end fe)))))
1222       (let ((got (funcall f 0 v start end from-end)))
1223         (unless (eql res got)
1224           (cerror "Continue" "POSITION 0, Wanted ~S, got ~S.~%  size = ~S, set = ~S, from-end = ~S"
1225                   res got
1226                   size set from-end))))))
1227
1228 (defun random-test-bit-position (n)
1229   (loop repeat n
1230         do (let* ((vector (make-array (+ 2 (random 5000)) :element-type 'bit))
1231                   (offset (random (1- (length vector))))
1232                   (size (1+ (random (- (length vector) offset))))
1233                   (disp (make-array size :element-type 'bit :displaced-to vector
1234                                          :displaced-index-offset offset)))
1235              (assert (plusp size))
1236              (loop repeat 10
1237                    do (setf (bit vector (random (length vector))) 1))
1238              (flet ((test (orig)
1239                       (declare (bit-vector orig))
1240                       (let ((copy (coerce orig 'simple-vector))
1241                             (p0 (random (length orig)))
1242                             (p1 (1+ (random (length orig)))))
1243                         (multiple-value-bind (s e)
1244                             (if (> p1 p0)
1245                                 (values p0 p1)
1246                                 (values p1 p0))
1247                           (assert (eql (position 1 copy :start s :end e)
1248                                        (position 1 orig :start s :end e)))
1249                           (assert (eql (position 1 copy :start s :end e :from-end t)
1250                                        (position 1 orig :start s :end e :from-end t)))))))
1251                (test vector)
1252                (test disp)))))
1253
1254 (with-test (:name :bit-position)
1255   (test-bit-position 0 (list) 0 0 nil nil)
1256   (test-bit-position 0 (list) 0 0 t nil)
1257   (test-bit-position 1 (list 0) 0 0 nil nil)
1258   (test-bit-position 1 (list 0) 0 0 t nil)
1259   (test-bit-position 1 (list 0) 0 1 nil 0)
1260   (test-bit-position 1 (list 0) 0 1 t 0)
1261   (test-bit-position 10 (list 0 1) 0 1 nil 0)
1262   (test-bit-position 10 (list 0 1) 1 1 nil nil)
1263   (test-bit-position 10 (list 0 1) 0 1 t 0)
1264   (test-bit-position 10 (list 0 1) 1 1 t nil)
1265   (test-bit-position 10 (list 0 3) 1 4 nil 3)
1266   (test-bit-position 10 (list 0 3) 1 4 t 3)
1267   (test-bit-position 10 (list 0 3 6) 1 10 nil 3)
1268   (test-bit-position 10 (list 0 3 6) 1 10 t 6)
1269   (test-bit-position 1000 (list 128 700) 20 500 nil 128)
1270   (test-bit-position 1000 (list 128 700) 20 500 t 128)
1271   (test-bit-position 1000 (list 423 762) 200 800 nil 423)
1272   (test-bit-position 1000 (list 423 762) 200 800 t 762)
1273   (test-bit-position 1000 (list 298 299) 100 400 nil 298)
1274   (test-bit-position 1000 (list 298 299) 100 400 t 299))
1275
1276 (with-test (:name (:bit-position :random-test))
1277   (random-test-bit-position 10000))
1278
1279 ;;; success