0.8.8.30:
[sbcl.git] / src / code / seq.lisp
1 ;;;; generic SEQUENCEs
2 ;;;;
3 ;;;; KLUDGE: comment from original CMU CL source:
4 ;;;;   Be careful when modifying code. A lot of the structure of the
5 ;;;;   code is affected by the fact that compiler transforms use the
6 ;;;;   lower level support functions. If transforms are written for
7 ;;;;   some sequence operation, note how the END argument is handled
8 ;;;;   in other operations with transforms.
9
10 ;;;; This software is part of the SBCL system. See the README file for
11 ;;;; more information.
12 ;;;;
13 ;;;; This software is derived from the CMU CL system, which was
14 ;;;; written at Carnegie Mellon University and released into the
15 ;;;; public domain. The software is in the public domain and is
16 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
17 ;;;; files for more information.
18
19 (in-package "SB!IMPL")
20 \f
21 ;;;; utilities
22
23 (eval-when (:compile-toplevel)
24
25 (defparameter *sequence-keyword-info*
26   ;; (name default supplied-p adjustment new-type)
27   `((count nil
28            nil
29            (etypecase count
30              (null (1- most-positive-fixnum))
31              (fixnum (max 0 count))
32              (integer (if (minusp count)
33                           0
34                           (1- most-positive-fixnum))))
35            (mod #.sb!xc:most-positive-fixnum))
36     ,@(mapcan (lambda (names)
37                 (destructuring-bind (start end length sequence) names
38                   (list
39                    `(,start
40                      0
41                      nil
42                      (if (<= 0 ,start ,length)
43                          ,start
44                          (signal-bounding-indices-bad-error ,sequence
45                                                             ,start ,end))
46                      index)
47                   `(,end
48                     nil
49                     nil
50                     (if (or (null ,end) (<= ,start ,end ,length))
51                         ;; Defaulting of NIL is done inside the
52                         ;; bodies, for ease of sharing with compiler
53                         ;; transforms.
54                         ;;
55                         ;; FIXME: defend against non-number non-NIL
56                         ;; stuff?
57                         ,end
58                         (signal-bounding-indices-bad-error ,sequence
59                                                            ,start ,end))
60                     (or null index)))))
61               '((start end length sequence)
62                 (start1 end1 length1 sequence1)
63                 (start2 end2 length2 sequence2)))
64     (key nil
65          nil
66          (and key (%coerce-callable-to-fun key))
67          (or null function))
68     (test #'eql
69           nil
70           (%coerce-callable-to-fun test)
71           function)
72     (test-not nil
73               nil
74               (and test-not (%coerce-callable-to-fun test-not))
75               (or null function))
76     ))
77
78 (sb!xc:defmacro define-sequence-traverser (name args &body body)
79   (multiple-value-bind (body declarations docstring)
80       (parse-body body :doc-string-allowed t)
81     (collect ((new-args) (new-declarations) (adjustments))
82       (dolist (arg args)
83         (case arg
84           ;; FIXME: make this robust.  And clean.
85           ((sequence)
86            (new-args arg)
87            (adjustments '(length (etypecase sequence
88                                    (list (length sequence))
89                                    (vector (length sequence)))))
90            (new-declarations '(type index length)))
91           ((sequence1)
92            (new-args arg)
93            (adjustments '(length1 (etypecase sequence1
94                                     (list (length sequence1))
95                                     (vector (length sequence1)))))
96            (new-declarations '(type index length1)))
97           ((sequence2)
98            (new-args arg)
99            (adjustments '(length2 (etypecase sequence2
100                                     (list (length sequence2))
101                                     (vector (length sequence2)))))
102            (new-declarations '(type index length2)))
103           (t (let ((info (cdr (assoc arg *sequence-keyword-info*))))
104                (cond (info
105                       (destructuring-bind (default supplied-p adjuster type) info
106                         (new-args `(,arg ,default ,@(when supplied-p (list supplied-p))))
107                         (adjustments `(,arg ,adjuster))
108                         (new-declarations `(type ,type ,arg))))
109                      (t (new-args arg)))))))
110       `(defun ,name ,(new-args)
111          ,@(when docstring (list docstring))
112          ,@declarations
113          (let* (,@(adjustments))
114            (declare ,@(new-declarations))
115            ,@body)))))
116
117 ;;; SEQ-DISPATCH does an efficient type-dispatch on the given SEQUENCE.
118 ;;;
119 ;;; FIXME: It might be worth making three cases here, LIST,
120 ;;; SIMPLE-VECTOR, and VECTOR, instead of the current LIST and VECTOR.
121 ;;; It tends to make code run faster but be bigger; some benchmarking
122 ;;; is needed to decide.
123 (sb!xc:defmacro seq-dispatch (sequence list-form array-form)
124   `(if (listp ,sequence)
125        ,list-form
126        ,array-form))
127
128 (sb!xc:defmacro make-sequence-like (sequence length)
129   #!+sb-doc
130   "Return a sequence of the same type as SEQUENCE and the given LENGTH."
131   `(if (typep ,sequence 'list)
132        (make-list ,length)
133        (progn
134          ;; This is only called from places which have already deduced
135          ;; that the SEQUENCE argument is actually a sequence.  So
136          ;; this would be a candidate place for (AVER (TYPEP ,SEQUENCE
137          ;; 'VECTOR)), except that this seems to be a performance
138          ;; hotspot.
139          (make-array ,length
140                      :element-type (array-element-type ,sequence)))))
141
142 (sb!xc:defmacro bad-sequence-type-error (type-spec)
143   `(error 'simple-type-error
144           :datum ,type-spec
145           ;; FIXME: This is actually wrong, and should be something
146           ;; like (SATISFIES IS-A-VALID-SEQUENCE-TYPE-SPECIFIER-P).
147           :expected-type 'sequence
148           :format-control "~S is a bad type specifier for sequences."
149           :format-arguments (list ,type-spec)))
150
151 (sb!xc:defmacro sequence-type-length-mismatch-error (type length)
152   `(error 'simple-type-error
153           :datum ,length
154           :expected-type (cond ((array-type-p ,type)
155                                 `(eql ,(car (array-type-dimensions ,type))))
156                                ((type= ,type (specifier-type 'null))
157                                 '(eql 0))
158                                ((cons-type-p ,type)
159                                 '(integer 1))
160                                (t (bug "weird type in S-T-L-M-ERROR")))
161           ;; FIXME: this format control causes ugly printing.  There's
162           ;; probably some ~<~@:_~> incantation that would make it
163           ;; nicer. -- CSR, 2002-10-18
164           :format-control "The length requested (~S) does not match the type restriction in ~S."
165           :format-arguments (list ,length (type-specifier ,type))))
166
167 (sb!xc:defmacro sequence-type-too-hairy (type-spec)
168   ;; FIXME: Should this be a BUG? I'm inclined to think not; there are
169   ;; words that give some but not total support to this position in
170   ;; ANSI.  Essentially, we are justified in throwing this on
171   ;; e.g. '(OR SIMPLE-VECTOR (VECTOR FIXNUM)), but maybe not (by ANSI)
172   ;; on '(CONS * (CONS * NULL)) -- CSR, 2002-10-18
173   `(error 'simple-type-error
174           :datum ,type-spec
175           ;; FIXME: as in BAD-SEQUENCE-TYPE-ERROR, this is wrong.
176           :expected-type 'sequence
177           :format-control "~S is too hairy for sequence functions."
178           :format-arguments (list ,type-spec)))
179 ) ; EVAL-WHEN
180
181 ;;; It's possible with some sequence operations to declare the length
182 ;;; of a result vector, and to be safe, we really ought to verify that
183 ;;; the actual result has the declared length.
184 (defun vector-of-checked-length-given-length (vector declared-length)
185   (declare (type vector vector))
186   (declare (type index declared-length))
187   (let ((actual-length (length vector)))
188     (unless (= actual-length declared-length)
189       (error 'simple-type-error
190              :datum vector
191              :expected-type `(vector ,declared-length)
192              :format-control
193              "Vector length (~W) doesn't match declared length (~W)."
194              :format-arguments (list actual-length declared-length))))
195   vector)
196 (defun sequence-of-checked-length-given-type (sequence result-type)
197   (let ((ctype (specifier-type result-type)))
198     (if (not (array-type-p ctype))
199         sequence
200         (let ((declared-length (first (array-type-dimensions ctype))))
201           (if (eq declared-length '*)
202               sequence
203               (vector-of-checked-length-given-length sequence
204                                                      declared-length))))))
205
206 (declaim (ftype (function (sequence index) nil) signal-index-too-large-error))
207 (defun signal-index-too-large-error (sequence index)
208   (let* ((length (length sequence))
209          (max-index (and (plusp length)
210                          (1- length))))
211     (error 'index-too-large-error
212            :datum index
213            :expected-type (if max-index
214                               `(integer 0 ,max-index)
215                               ;; This seems silly, is there something better?
216                               '(integer 0 (0))))))
217
218 (defun signal-bounding-indices-bad-error (sequence start end)
219   (let ((length (length sequence)))
220     (error 'bounding-indices-bad-error
221            :datum (cons start end)
222            :expected-type `(cons (integer 0 ,length)
223                                  (or null (integer ,start ,length)))
224            :object sequence)))
225 \f
226 (defun elt (sequence index)
227   #!+sb-doc "Return the element of SEQUENCE specified by INDEX."
228   (etypecase sequence
229     (list
230      (do ((count index (1- count))
231           (list sequence (cdr list)))
232          ((= count 0)
233           (if (endp list)
234               (signal-index-too-large-error sequence index)
235               (car list)))
236        (declare (type (integer 0) count))))
237     (vector
238      (when (>= index (length sequence))
239        (signal-index-too-large-error sequence index))
240      (aref sequence index))))
241
242 (defun %setelt (sequence index newval)
243   #!+sb-doc "Store NEWVAL as the component of SEQUENCE specified by INDEX."
244   (etypecase sequence
245     (list
246      (do ((count index (1- count))
247           (seq sequence))
248          ((= count 0) (rplaca seq newval) newval)
249        (declare (fixnum count))
250        (if (atom (cdr seq))
251            (signal-index-too-large-error sequence index)
252            (setq seq (cdr seq)))))
253     (vector
254      (when (>= index (length sequence))
255        (signal-index-too-large-error sequence index))
256      (setf (aref sequence index) newval))))
257
258 (defun length (sequence)
259   #!+sb-doc "Return an integer that is the length of SEQUENCE."
260   (etypecase sequence
261     (vector (length (truly-the vector sequence)))
262     (list (length (truly-the list sequence)))))
263
264 (defun make-sequence (type length &key (initial-element nil iep))
265   #!+sb-doc
266   "Return a sequence of the given TYPE and LENGTH, with elements initialized
267   to INITIAL-ELEMENT."
268   (declare (fixnum length))
269   (let* ((adjusted-type
270           (typecase type
271             (atom (cond
272                     ((eq type 'string) '(vector character))
273                     ((eq type 'simple-string) '(simple-array character (*)))
274                     (t type)))
275             (cons (cond
276                     ((eq (car type) 'string) `(vector character ,@(cdr type)))
277                     ((eq (car type) 'simple-string)
278                      `(simple-array character ,@(when (cdr type)
279                                                       (list (cdr type)))))
280                     (t type)))
281             (t type)))
282          (type (specifier-type adjusted-type)))
283     (cond ((csubtypep type (specifier-type 'list))
284            (cond
285              ((type= type (specifier-type 'list))
286               (make-list length :initial-element initial-element))
287              ((eq type *empty-type*)
288               (bad-sequence-type-error nil))
289              ((type= type (specifier-type 'null))
290               (if (= length 0)
291                   'nil
292                   (sequence-type-length-mismatch-error type length)))
293              ((cons-type-p type)
294               (multiple-value-bind (min exactp)
295                   (sb!kernel::cons-type-length-info type)
296                 (if exactp
297                     (unless (= length min)
298                       (sequence-type-length-mismatch-error type length))
299                     (unless (>= length min)
300                       (sequence-type-length-mismatch-error type length)))
301                 (make-list length :initial-element initial-element)))
302              ;; We'll get here for e.g. (OR NULL (CONS INTEGER *)),
303              ;; which may seem strange and non-ideal, but then I'd say
304              ;; it was stranger to feed that type in to MAKE-SEQUENCE.
305              (t (sequence-type-too-hairy (type-specifier type)))))
306           ((csubtypep type (specifier-type 'vector))
307            (cond
308              (;; is it immediately obvious what the result type is?
309               (typep type 'array-type)
310               (progn
311                 (aver (= (length (array-type-dimensions type)) 1))
312                 (let* ((etype (type-specifier
313                                (array-type-specialized-element-type type)))
314                        (etype (if (eq etype '*) t etype))
315                        (type-length (car (array-type-dimensions type))))
316                   (unless (or (eq type-length '*)
317                               (= type-length length))
318                     (sequence-type-length-mismatch-error type length))
319                   ;; FIXME: These calls to MAKE-ARRAY can't be
320                   ;; open-coded, as the :ELEMENT-TYPE argument isn't
321                   ;; constant.  Probably we ought to write a
322                   ;; DEFTRANSFORM for MAKE-SEQUENCE.  -- CSR,
323                   ;; 2002-07-22
324                   (if iep
325                       (make-array length :element-type etype
326                                   :initial-element initial-element)
327                       (make-array length :element-type etype)))))
328              (t (sequence-type-too-hairy (type-specifier type)))))
329           (t (bad-sequence-type-error (type-specifier type))))))
330 \f
331 ;;;; SUBSEQ
332 ;;;;
333 ;;;; The support routines for SUBSEQ are used by compiler transforms,
334 ;;;; so we worry about dealing with END being supplied or defaulting
335 ;;;; to NIL at this level.
336
337 (defun vector-subseq* (sequence start &optional end)
338   (declare (type vector sequence))
339   (declare (type index start))
340   (declare (type (or null index) end))
341   (when (null end)
342     (setf end (length sequence)))
343   (unless (<= 0 start end (length sequence))
344     (signal-bounding-indices-bad-error sequence start end))
345   (do ((old-index start (1+ old-index))
346        (new-index 0 (1+ new-index))
347        (copy (make-sequence-like sequence (- end start))))
348       ((= old-index end) copy)
349     (declare (fixnum old-index new-index))
350     (setf (aref copy new-index)
351           (aref sequence old-index))))
352
353 (defun list-subseq* (sequence start &optional end)
354   (declare (type list sequence))
355   ;; the INDEX declaration isn't actually mandatory, but it's true for
356   ;; all practical purposes.
357   (declare (type index start))
358   (declare (type (or null index) end))
359   (do ((list sequence (cdr list))
360        (index 0 (1+ index))
361        (result nil))
362       (nil)
363     (cond
364       ((null list) (if (or (and end (> end index))
365                            (< index start))
366                        (signal-bounding-indices-bad-error sequence start end)
367                        (return (nreverse result))))
368       ((< index start) nil)
369       ((and end (= index end)) (return (nreverse result)))
370       (t (push (car list) result)))))
371
372 (defun subseq (sequence start &optional end)
373   #!+sb-doc
374   "Return a copy of a subsequence of SEQUENCE starting with element number
375    START and continuing to the end of SEQUENCE or the optional END."
376   (seq-dispatch sequence
377                 (list-subseq* sequence start end)
378                 (vector-subseq* sequence start end)))
379 \f
380 ;;;; COPY-SEQ
381
382 (eval-when (:compile-toplevel :execute)
383
384 (sb!xc:defmacro vector-copy-seq (sequence)
385   `(let ((length (length (the vector ,sequence))))
386      (declare (fixnum length))
387      (do ((index 0 (1+ index))
388           (copy (make-sequence-like ,sequence length)))
389          ((= index length) copy)
390        (declare (fixnum index))
391        (setf (aref copy index) (aref ,sequence index)))))
392
393 (sb!xc:defmacro list-copy-seq (list)
394   `(if (atom ,list) '()
395        (let ((result (cons (car ,list) '()) ))
396          (do ((x (cdr ,list) (cdr x))
397               (splice result
398                       (cdr (rplacd splice (cons (car x) '() ))) ))
399              ((atom x) (unless (null x)
400                                (rplacd splice x))
401                        result)))))
402
403 ) ; EVAL-WHEN
404
405 (defun copy-seq (sequence)
406   #!+sb-doc "Return a copy of SEQUENCE which is EQUAL to SEQUENCE but not EQ."
407   (seq-dispatch sequence
408                 (list-copy-seq* sequence)
409                 (vector-copy-seq* sequence)))
410
411 ;;; internal frobs
412
413 (defun list-copy-seq* (sequence)
414   (list-copy-seq sequence))
415
416 (defun vector-copy-seq* (sequence)
417   (declare (type vector sequence))
418   (vector-copy-seq sequence))
419 \f
420 ;;;; FILL
421
422 (eval-when (:compile-toplevel :execute)
423
424 (sb!xc:defmacro vector-fill (sequence item start end)
425   `(do ((index ,start (1+ index)))
426        ((= index (the fixnum ,end)) ,sequence)
427      (declare (fixnum index))
428      (setf (aref ,sequence index) ,item)))
429
430 (sb!xc:defmacro list-fill (sequence item start end)
431   `(do ((current (nthcdr ,start ,sequence) (cdr current))
432         (index ,start (1+ index)))
433        ((or (atom current) (and end (= index (the fixnum ,end))))
434         sequence)
435      (declare (fixnum index))
436      (rplaca current ,item)))
437
438 ) ; EVAL-WHEN
439
440 ;;; The support routines for FILL are used by compiler transforms, so we
441 ;;; worry about dealing with END being supplied or defaulting to NIL
442 ;;; at this level.
443
444 (defun list-fill* (sequence item start end)
445   (declare (list sequence))
446   (list-fill sequence item start end))
447
448 (defun vector-fill* (sequence item start end)
449   (declare (vector sequence))
450   (when (null end) (setq end (length sequence)))
451   (vector-fill sequence item start end))
452
453 (define-sequence-traverser fill (sequence item &key start end)
454   #!+sb-doc "Replace the specified elements of SEQUENCE with ITEM."
455   (seq-dispatch sequence
456                 (list-fill* sequence item start end)
457                 (vector-fill* sequence item start end)))
458 \f
459 ;;;; REPLACE
460
461 (eval-when (:compile-toplevel :execute)
462
463 ;;; If we are copying around in the same vector, be careful not to copy the
464 ;;; same elements over repeatedly. We do this by copying backwards.
465 (sb!xc:defmacro mumble-replace-from-mumble ()
466   `(if (and (eq target-sequence source-sequence) (> target-start source-start))
467        (let ((nelts (min (- target-end target-start)
468                          (- source-end source-start))))
469          (do ((target-index (+ (the fixnum target-start) (the fixnum nelts) -1)
470                             (1- target-index))
471               (source-index (+ (the fixnum source-start) (the fixnum nelts) -1)
472                             (1- source-index)))
473              ((= target-index (the fixnum (1- target-start))) target-sequence)
474            (declare (fixnum target-index source-index))
475            ;; disable bounds checking
476            (declare (optimize (safety 0)))
477            (setf (aref target-sequence target-index)
478                  (aref source-sequence source-index))))
479        (do ((target-index target-start (1+ target-index))
480             (source-index source-start (1+ source-index)))
481            ((or (= target-index (the fixnum target-end))
482                 (= source-index (the fixnum source-end)))
483             target-sequence)
484          (declare (fixnum target-index source-index))
485          ;; disable bounds checking
486          (declare (optimize (safety 0)))
487          (setf (aref target-sequence target-index)
488                (aref source-sequence source-index)))))
489
490 (sb!xc:defmacro list-replace-from-list ()
491   `(if (and (eq target-sequence source-sequence) (> target-start source-start))
492        (let ((new-elts (subseq source-sequence source-start
493                                (+ (the fixnum source-start)
494                                   (the fixnum
495                                        (min (- (the fixnum target-end)
496                                                (the fixnum target-start))
497                                             (- (the fixnum source-end)
498                                                (the fixnum source-start))))))))
499          (do ((n new-elts (cdr n))
500               (o (nthcdr target-start target-sequence) (cdr o)))
501              ((null n) target-sequence)
502            (rplaca o (car n))))
503        (do ((target-index target-start (1+ target-index))
504             (source-index source-start (1+ source-index))
505             (target-sequence-ref (nthcdr target-start target-sequence)
506                                  (cdr target-sequence-ref))
507             (source-sequence-ref (nthcdr source-start source-sequence)
508                                  (cdr source-sequence-ref)))
509            ((or (= target-index (the fixnum target-end))
510                 (= source-index (the fixnum source-end))
511                 (null target-sequence-ref) (null source-sequence-ref))
512             target-sequence)
513          (declare (fixnum target-index source-index))
514          (rplaca target-sequence-ref (car source-sequence-ref)))))
515
516 (sb!xc:defmacro list-replace-from-mumble ()
517   `(do ((target-index target-start (1+ target-index))
518         (source-index source-start (1+ source-index))
519         (target-sequence-ref (nthcdr target-start target-sequence)
520                              (cdr target-sequence-ref)))
521        ((or (= target-index (the fixnum target-end))
522             (= source-index (the fixnum source-end))
523             (null target-sequence-ref))
524         target-sequence)
525      (declare (fixnum source-index target-index))
526      (rplaca target-sequence-ref (aref source-sequence source-index))))
527
528 (sb!xc:defmacro mumble-replace-from-list ()
529   `(do ((target-index target-start (1+ target-index))
530         (source-index source-start (1+ source-index))
531         (source-sequence (nthcdr source-start source-sequence)
532                          (cdr source-sequence)))
533        ((or (= target-index (the fixnum target-end))
534             (= source-index (the fixnum source-end))
535             (null source-sequence))
536         target-sequence)
537      (declare (fixnum target-index source-index))
538      (setf (aref target-sequence target-index) (car source-sequence))))
539
540 ) ; EVAL-WHEN
541
542 ;;;; The support routines for REPLACE are used by compiler transforms, so we
543 ;;;; worry about dealing with END being supplied or defaulting to NIL
544 ;;;; at this level.
545
546 (defun list-replace-from-list* (target-sequence source-sequence target-start
547                                 target-end source-start source-end)
548   (when (null target-end) (setq target-end (length target-sequence)))
549   (when (null source-end) (setq source-end (length source-sequence)))
550   (list-replace-from-list))
551
552 (defun list-replace-from-vector* (target-sequence source-sequence target-start
553                                   target-end source-start source-end)
554   (when (null target-end) (setq target-end (length target-sequence)))
555   (when (null source-end) (setq source-end (length source-sequence)))
556   (list-replace-from-mumble))
557
558 (defun vector-replace-from-list* (target-sequence source-sequence target-start
559                                   target-end source-start source-end)
560   (when (null target-end) (setq target-end (length target-sequence)))
561   (when (null source-end) (setq source-end (length source-sequence)))
562   (mumble-replace-from-list))
563
564 (defun vector-replace-from-vector* (target-sequence source-sequence
565                                     target-start target-end source-start
566                                     source-end)
567   (when (null target-end) (setq target-end (length target-sequence)))
568   (when (null source-end) (setq source-end (length source-sequence)))
569   (mumble-replace-from-mumble))
570
571 (define-sequence-traverser replace
572     (sequence1 sequence2 &key start1 end1 start2 end2)
573   #!+sb-doc
574   "The target sequence is destructively modified by copying successive
575    elements into it from the source sequence."
576   (let* (;; KLUDGE: absent either rewriting FOO-REPLACE-FROM-BAR, or
577          ;; excessively polluting DEFINE-SEQUENCE-TRAVERSER, we rebind
578          ;; these things here so that legacy code gets the names it's
579          ;; expecting.  We could use &AUX instead :-/.
580          (target-sequence sequence1)
581          (source-sequence sequence2)
582          (target-start start1)
583          (source-start start2)
584          (target-end (or end1 length1))
585          (source-end (or end2 length2)))
586     (seq-dispatch target-sequence
587                   (seq-dispatch source-sequence
588                                 (list-replace-from-list)
589                                 (list-replace-from-mumble))
590                   (seq-dispatch source-sequence
591                                 (mumble-replace-from-list)
592                                 (mumble-replace-from-mumble)))))
593 \f
594 ;;;; REVERSE
595
596 (eval-when (:compile-toplevel :execute)
597
598 (sb!xc:defmacro vector-reverse (sequence)
599   `(let ((length (length ,sequence)))
600      (declare (fixnum length))
601      (do ((forward-index 0 (1+ forward-index))
602           (backward-index (1- length) (1- backward-index))
603           (new-sequence (make-sequence-like sequence length)))
604          ((= forward-index length) new-sequence)
605        (declare (fixnum forward-index backward-index))
606        (setf (aref new-sequence forward-index)
607              (aref ,sequence backward-index)))))
608
609 (sb!xc:defmacro list-reverse-macro (sequence)
610   `(do ((new-list ()))
611        ((endp ,sequence) new-list)
612      (push (pop ,sequence) new-list)))
613
614 ) ; EVAL-WHEN
615
616 (defun reverse (sequence)
617   #!+sb-doc
618   "Return a new sequence containing the same elements but in reverse order."
619   (seq-dispatch sequence
620                 (list-reverse* sequence)
621                 (vector-reverse* sequence)))
622
623 ;;; internal frobs
624
625 (defun list-reverse* (sequence)
626   (list-reverse-macro sequence))
627
628 (defun vector-reverse* (sequence)
629   (vector-reverse sequence))
630 \f
631 ;;;; NREVERSE
632
633 (eval-when (:compile-toplevel :execute)
634
635 (sb!xc:defmacro vector-nreverse (sequence)
636   `(let ((length (length (the vector ,sequence))))
637      (when (>= length 2)
638        (do ((left-index 0 (1+ left-index))
639             (right-index (1- length) (1- right-index)))
640            ((<= right-index left-index))
641          (declare (type index left-index right-index))
642          (rotatef (aref ,sequence left-index)
643                   (aref ,sequence right-index))))
644      ,sequence))
645
646 (sb!xc:defmacro list-nreverse-macro (list)
647   `(do ((1st (cdr ,list) (if (endp 1st) 1st (cdr 1st)))
648         (2nd ,list 1st)
649         (3rd '() 2nd))
650        ((atom 2nd) 3rd)
651      (rplacd 2nd 3rd)))
652
653 ) ; EVAL-WHEN
654
655 (defun list-nreverse* (sequence)
656   (list-nreverse-macro sequence))
657
658 (defun vector-nreverse* (sequence)
659   (vector-nreverse sequence))
660
661 (defun nreverse (sequence)
662   #!+sb-doc
663   "Return a sequence of the same elements in reverse order; the argument
664    is destroyed."
665   (seq-dispatch sequence
666                 (list-nreverse* sequence)
667                 (vector-nreverse* sequence)))
668 \f
669 ;;;; CONCATENATE
670
671 (eval-when (:compile-toplevel :execute)
672
673 (sb!xc:defmacro concatenate-to-list (sequences)
674   `(let ((result (list nil)))
675      (do ((sequences ,sequences (cdr sequences))
676           (splice result))
677          ((null sequences) (cdr result))
678        (let ((sequence (car sequences)))
679          ;; FIXME: It appears to me that this and CONCATENATE-TO-MUMBLE
680          ;; could benefit from a DO-SEQUENCE macro.
681          (seq-dispatch sequence
682                        (do ((sequence sequence (cdr sequence)))
683                            ((atom sequence))
684                          (setq splice
685                                (cdr (rplacd splice (list (car sequence))))))
686                        (do ((index 0 (1+ index))
687                             (length (length sequence)))
688                            ((= index length))
689                          (declare (fixnum index length))
690                          (setq splice
691                                (cdr (rplacd splice
692                                             (list (aref sequence index)))))))))))
693
694 (sb!xc:defmacro concatenate-to-mumble (output-type-spec sequences)
695   `(do ((seqs ,sequences (cdr seqs))
696         (total-length 0)
697         (lengths ()))
698        ((null seqs)
699         (do ((sequences ,sequences (cdr sequences))
700              (lengths lengths (cdr lengths))
701              (index 0)
702              (result (make-sequence ,output-type-spec total-length)))
703             ((= index total-length) result)
704           (declare (fixnum index))
705           (let ((sequence (car sequences)))
706             (seq-dispatch sequence
707                           (do ((sequence sequence (cdr sequence)))
708                               ((atom sequence))
709                             (setf (aref result index) (car sequence))
710                             (setq index (1+ index)))
711                           (do ((jndex 0 (1+ jndex))
712                                (this-length (car lengths)))
713                               ((= jndex this-length))
714                             (declare (fixnum jndex this-length))
715                             (setf (aref result index)
716                                   (aref sequence jndex))
717                             (setq index (1+ index)))))))
718      (let ((length (length (car seqs))))
719        (declare (fixnum length))
720        (setq lengths (nconc lengths (list length)))
721        (setq total-length (+ total-length length)))))
722
723 ) ; EVAL-WHEN
724 \f
725 (defun concatenate (output-type-spec &rest sequences)
726   #!+sb-doc
727   "Return a new sequence of all the argument sequences concatenated together
728   which shares no structure with the original argument sequences of the
729   specified OUTPUT-TYPE-SPEC."
730   (let ((type (specifier-type output-type-spec)))
731   (cond
732     ((csubtypep type (specifier-type 'list))
733      (cond
734        ((type= type (specifier-type 'list))
735         (apply #'concat-to-list* sequences))
736        ((eq type *empty-type*)
737         (bad-sequence-type-error nil))
738        ((type= type (specifier-type 'null))
739         (if (every (lambda (x) (or (null x)
740                                    (and (vectorp x) (= (length x) 0))))
741                    sequences)
742             'nil
743             (sequence-type-length-mismatch-error
744              type
745              ;; FIXME: circular list issues.
746              (reduce #'+ sequences :key #'length))))
747        ((cons-type-p type)
748         (multiple-value-bind (min exactp)
749             (sb!kernel::cons-type-length-info type)
750           (let ((length (reduce #'+ sequences :key #'length)))
751             (if exactp
752                 (unless (= length min)
753                   (sequence-type-length-mismatch-error type length))
754                 (unless (>= length min)
755                   (sequence-type-length-mismatch-error type length)))
756             (apply #'concat-to-list* sequences))))
757        (t (sequence-type-too-hairy (type-specifier type)))))
758     ((csubtypep type (specifier-type 'vector))
759      (apply #'concat-to-simple* output-type-spec sequences))
760     (t
761      (bad-sequence-type-error output-type-spec)))))
762
763 ;;; internal frobs
764 ;;; FIXME: These are weird. They're never called anywhere except in
765 ;;; CONCATENATE. It seems to me that the macros ought to just
766 ;;; be expanded directly in CONCATENATE, or in CONCATENATE-STRING
767 ;;; and CONCATENATE-LIST variants. Failing that, these ought to be local
768 ;;; functions (FLET).
769 (defun concat-to-list* (&rest sequences)
770   (concatenate-to-list sequences))
771 (defun concat-to-simple* (type &rest sequences)
772   (concatenate-to-mumble type sequences))
773 \f
774 ;;;; MAP and MAP-INTO
775
776 ;;; helper functions to handle arity-1 subcases of MAP
777 (declaim (ftype (function (function sequence) list) %map-list-arity-1))
778 (declaim (ftype (function (function sequence) simple-vector)
779                 %map-simple-vector-arity-1))
780 (macrolet ((dosequence ((i sequence) &body body)
781              (once-only ((sequence sequence))
782                `(etypecase ,sequence
783                   (list (dolist (,i ,sequence) ,@body))
784                   (simple-vector (dovector (,i sequence) ,@body))
785                   (vector (dovector (,i sequence) ,@body))))))
786   (defun %map-to-list-arity-1 (fun sequence)
787     (let ((reversed-result nil)
788           (really-fun (%coerce-callable-to-fun fun)))
789       (dosequence (element sequence)
790         (push (funcall really-fun element)
791               reversed-result))
792       (nreverse reversed-result)))
793   (defun %map-to-simple-vector-arity-1 (fun sequence)
794     (let ((result (make-array (length sequence)))
795           (index 0)
796           (really-fun (%coerce-callable-to-fun fun)))
797       (declare (type index index))
798       (dosequence (element sequence)
799         (setf (aref result index)
800               (funcall really-fun element))
801         (incf index))
802       result))
803   (defun %map-for-effect-arity-1 (fun sequence)
804     (let ((really-fun (%coerce-callable-to-fun fun)))
805       (dosequence (element sequence)
806         (funcall really-fun element)))
807     nil))
808
809 ;;; helper functions to handle arity-N subcases of MAP
810 ;;;
811 ;;; KLUDGE: This is hairier, and larger, than need be, because we
812 ;;; don't have DYNAMIC-EXTENT. With DYNAMIC-EXTENT, we could define
813 ;;; %MAP-FOR-EFFECT, and then implement the
814 ;;; other %MAP-TO-FOO functions reasonably efficiently by passing closures to
815 ;;; %MAP-FOR-EFFECT. (DYNAMIC-EXTENT would help a little by avoiding
816 ;;; consing each closure, and would help a lot by allowing us to define
817 ;;; a closure (LAMBDA (&REST REST) <do something with (APPLY FUN REST)>)
818 ;;; with the REST list allocated with DYNAMIC-EXTENT. -- WHN 20000920
819 (macrolet (;; Execute BODY in a context where the machinery for
820            ;; UPDATED-MAP-APPLY-ARGS has been set up.
821            (with-map-state (sequences &body body)
822              `(let* ((%sequences ,sequences)
823                      (%iters (mapcar (lambda (sequence)
824                                        (etypecase sequence
825                                          (list sequence)
826                                          (vector 0)))
827                                      %sequences))
828                      (%apply-args (make-list (length %sequences))))
829                 (declare (type list %sequences %iters %apply-args))
830                 ,@body))
831            ;; Return a list of args to pass to APPLY for the next
832            ;; function call in the mapping, or NIL if no more function
833            ;; calls should be made (because we've reached the end of a
834            ;; sequence arg).
835            (updated-map-apply-args ()
836              '(do ((in-sequences  %sequences  (cdr in-sequences))
837                    (in-iters      %iters      (cdr in-iters))
838                    (in-apply-args %apply-args (cdr in-apply-args)))
839                   ((null in-sequences)
840                    %apply-args)
841                 (declare (type list in-sequences in-iters in-apply-args))
842                 (let ((i (car in-iters)))
843                   (declare (type (or list index) i))
844                   (if (listp i)
845                       (if (null i)      ; if end of this sequence
846                           (return nil)
847                           (setf (car in-apply-args) (car i)
848                                 (car in-iters) (cdr i)))
849                       (let ((v (the vector (car in-sequences))))
850                         (if (>= i (length v)) ; if end of this sequence
851                             (return nil)
852                             (setf (car in-apply-args) (aref v i)
853                                   (car in-iters) (1+ i)))))))))
854   (defun %map-to-list (func sequences)
855     (declare (type function func))
856     (declare (type list sequences))
857     (with-map-state sequences
858       (loop with updated-map-apply-args 
859             while (setf updated-map-apply-args (updated-map-apply-args))
860             collect (apply func updated-map-apply-args))))
861   (defun %map-to-vector (output-type-spec func sequences)
862     (declare (type function func))
863     (declare (type list sequences))
864     (let ((min-len (with-map-state sequences
865                      (do ((counter 0 (1+ counter)))
866                          ;; Note: Doing everything in
867                          ;; UPDATED-MAP-APPLY-ARGS here is somewhat
868                          ;; wasteful; we even do some extra consing.
869                          ;; And stepping over every element of
870                          ;; VECTORs, instead of just grabbing their
871                          ;; LENGTH, is also wasteful. But it's easy
872                          ;; and safe. (If you do rewrite it, please
873                          ;; try to make sure that
874                          ;;   (MAP NIL #'F SOME-CIRCULAR-LIST #(1))
875                          ;; does the right thing.)
876                          ((not (updated-map-apply-args))
877                           counter)
878                        (declare (type index counter))))))
879       (declare (type index min-len))
880       (with-map-state sequences
881         (let ((result (make-sequence output-type-spec min-len))
882               (index 0))
883           (declare (type index index))
884           (loop with updated-map-apply-args
885                 while (setf updated-map-apply-args (updated-map-apply-args))
886                 do
887                 (setf (aref result index)
888                       (apply func updated-map-apply-args))
889                 (incf index))
890           result))))
891   (defun %map-for-effect (func sequences)
892     (declare (type function func))
893     (declare (type list sequences))
894     (with-map-state sequences
895       (loop with updated-map-apply-args
896             while (setf updated-map-apply-args (updated-map-apply-args))
897             do
898             (apply func updated-map-apply-args))
899       nil)))
900
901   "FUNCTION must take as many arguments as there are sequences provided.  
902   The result is a sequence of type OUTPUT-TYPE-SPEC such that element I 
903   is the result of applying FUNCTION to element I of each of the argument
904   sequences."
905
906 ;;; %MAP is just MAP without the final just-to-be-sure check that
907 ;;; length of the output sequence matches any length specified
908 ;;; in RESULT-TYPE.
909 (defun %map (result-type function first-sequence &rest more-sequences)
910   (let ((really-fun (%coerce-callable-to-fun function))
911         (type (specifier-type result-type)))
912     ;; Handle one-argument MAP NIL specially, using ETYPECASE to turn
913     ;; it into something which can be DEFTRANSFORMed away. (It's
914     ;; fairly important to handle this case efficiently, since
915     ;; quantifiers like SOME are transformed into this case, and since
916     ;; there's no consing overhead to dwarf our inefficiency.)
917     (if (and (null more-sequences)
918              (null result-type))
919         (%map-for-effect-arity-1 really-fun first-sequence)
920         ;; Otherwise, use the industrial-strength full-generality
921         ;; approach, consing O(N-ARGS) temporary storage (which can have
922         ;; DYNAMIC-EXTENT), then using O(N-ARGS * RESULT-LENGTH) time.
923         (let ((sequences (cons first-sequence more-sequences)))
924           (cond
925             ((eq type *empty-type*) (%map-for-effect really-fun sequences))
926             ((csubtypep type (specifier-type 'list))
927              (%map-to-list really-fun sequences))
928             ((csubtypep type (specifier-type 'vector))
929              (%map-to-vector result-type really-fun sequences))
930             (t
931              (bad-sequence-type-error result-type)))))))
932
933 (defun map (result-type function first-sequence &rest more-sequences)
934   (apply #'%map
935          result-type
936          function
937          first-sequence
938          more-sequences))
939
940 ;;; KLUDGE: MAP has been rewritten substantially since the fork from
941 ;;; CMU CL in order to give reasonable performance, but this
942 ;;; implementation of MAP-INTO still has the same problems as the old
943 ;;; MAP code. Ideally, MAP-INTO should be rewritten to be efficient in
944 ;;; the same way that the corresponding cases of MAP have been
945 ;;; rewritten. Instead of doing it now, though, it's easier to wait
946 ;;; until we have DYNAMIC-EXTENT, at which time it should become
947 ;;; extremely easy to define a reasonably efficient MAP-INTO in terms
948 ;;; of (MAP NIL ..). -- WHN 20000920
949 (defun map-into (result-sequence function &rest sequences)
950   (let* ((fp-result
951           (and (arrayp result-sequence)
952                (array-has-fill-pointer-p result-sequence)))
953          (len (apply #'min
954                      (if fp-result
955                          (array-dimension result-sequence 0)
956                          (length result-sequence))
957                      (mapcar #'length sequences))))
958
959     (when fp-result
960       (setf (fill-pointer result-sequence) len))
961
962     (let ((really-fun (%coerce-callable-to-fun function)))
963       (dotimes (index len)
964         (setf (elt result-sequence index)
965               (apply really-fun
966                      (mapcar (lambda (seq) (elt seq index))
967                              sequences))))))
968   result-sequence)
969 \f
970 ;;;; quantifiers
971
972 ;;; We borrow the logic from (MAP NIL ..) to handle iteration over
973 ;;; arbitrary sequence arguments, both in the full call case and in
974 ;;; the open code case.
975 (macrolet ((defquantifier (name found-test found-result
976                                 &key doc (unfound-result (not found-result)))
977              `(progn 
978                 ;; KLUDGE: It would be really nice if we could simply
979                 ;; do something like this
980                 ;;  (declaim (inline ,name))
981                 ;;  (defun ,name (pred first-seq &rest more-seqs)
982                 ;;    ,doc
983                 ;;    (flet ((map-me (&rest rest)
984                 ;;             (let ((pred-value (apply pred rest)))
985                 ;;               (,found-test pred-value
986                 ;;                 (return-from ,name
987                 ;;                   ,found-result)))))
988                 ;;      (declare (inline map-me))
989                 ;;      (apply #'map nil #'map-me first-seq more-seqs)
990                 ;;      ,unfound-result))
991                 ;; but Python doesn't seem to be smart enough about
992                 ;; inlining and APPLY to recognize that it can use
993                 ;; the DEFTRANSFORM for MAP in the resulting inline
994                 ;; expansion. I don't have any appetite for deep
995                 ;; compiler hacking right now, so I'll just work
996                 ;; around the apparent problem by using a compiler
997                 ;; macro instead. -- WHN 20000410
998                 (defun ,name (pred first-seq &rest more-seqs)
999                   #!+sb-doc ,doc
1000                   (flet ((map-me (&rest rest)
1001                            (let ((pred-value (apply pred rest)))
1002                              (,found-test pred-value
1003                                           (return-from ,name
1004                                             ,found-result)))))
1005                     (declare (inline map-me))
1006                     (apply #'map nil #'map-me first-seq more-seqs)
1007                     ,unfound-result))
1008                 ;; KLUDGE: It would be more obviously correct -- but
1009                 ;; also significantly messier -- for PRED-VALUE to be
1010                 ;; a gensym. However, a private symbol really does
1011                 ;; seem to be good enough; and anyway the really
1012                 ;; obviously correct solution is to make Python smart
1013                 ;; enough that we can use an inline function instead
1014                 ;; of a compiler macro (as above). -- WHN 20000410
1015                 ;;
1016                 ;; FIXME: The DEFINE-COMPILER-MACRO here can be
1017                 ;; important for performance, and it'd be good to have
1018                 ;; it be visible throughout the compilation of all the
1019                 ;; target SBCL code. That could be done by defining
1020                 ;; SB-XC:DEFINE-COMPILER-MACRO and using it here,
1021                 ;; moving this DEFQUANTIFIER stuff (and perhaps other
1022                 ;; inline definitions in seq.lisp as well) into a new
1023                 ;; seq.lisp, and moving remaining target-only stuff
1024                 ;; from the old seq.lisp into target-seq.lisp.
1025                 (define-compiler-macro ,name (pred first-seq &rest more-seqs)
1026                   (let ((elements (make-gensym-list (1+ (length more-seqs))))
1027                         (blockname (gensym "BLOCK")))
1028                     (once-only ((pred pred))
1029                       `(block ,blockname
1030                          (map nil
1031                               (lambda (,@elements)
1032                                 (let ((pred-value (funcall ,pred ,@elements)))
1033                                   (,',found-test pred-value
1034                                     (return-from ,blockname
1035                                       ,',found-result))))
1036                               ,first-seq
1037                               ,@more-seqs)
1038                          ,',unfound-result)))))))
1039   (defquantifier some when pred-value :unfound-result nil :doc
1040   "Apply PREDICATE to the 0-indexed elements of the sequences, then 
1041    possibly to those with index 1, and so on. Return the first 
1042    non-NIL value encountered, or NIL if the end of any sequence is reached.")
1043   (defquantifier every unless nil :doc
1044   "Apply PREDICATE to the 0-indexed elements of the sequences, then
1045    possibly to those with index 1, and so on. Return NIL as soon
1046    as any invocation of PREDICATE returns NIL, or T if every invocation
1047    is non-NIL.")
1048   (defquantifier notany when nil :doc
1049   "Apply PREDICATE to the 0-indexed elements of the sequences, then 
1050    possibly to those with index 1, and so on. Return NIL as soon
1051    as any invocation of PREDICATE returns a non-NIL value, or T if the end
1052    of any sequence is reached.")
1053   (defquantifier notevery unless t :doc
1054   "Apply PREDICATE to 0-indexed elements of the sequences, then
1055    possibly to those with index 1, and so on. Return T as soon
1056    as any invocation of PREDICATE returns NIL, or NIL if every invocation
1057    is non-NIL."))
1058 \f
1059 ;;;; REDUCE
1060
1061 (eval-when (:compile-toplevel :execute)
1062
1063 (sb!xc:defmacro mumble-reduce (function
1064                                sequence
1065                                key
1066                                start
1067                                end
1068                                initial-value
1069                                ref)
1070   `(do ((index ,start (1+ index))
1071         (value ,initial-value))
1072        ((= index (the fixnum ,end)) value)
1073      (declare (fixnum index))
1074      (setq value (funcall ,function value
1075                           (apply-key ,key (,ref ,sequence index))))))
1076
1077 (sb!xc:defmacro mumble-reduce-from-end (function
1078                                         sequence
1079                                         key
1080                                         start
1081                                         end
1082                                         initial-value
1083                                         ref)
1084   `(do ((index (1- ,end) (1- index))
1085         (value ,initial-value)
1086         (terminus (1- ,start)))
1087        ((= index terminus) value)
1088      (declare (fixnum index terminus))
1089      (setq value (funcall ,function
1090                           (apply-key ,key (,ref ,sequence index))
1091                           value))))
1092
1093 (sb!xc:defmacro list-reduce (function
1094                              sequence
1095                              key
1096                              start
1097                              end
1098                              initial-value
1099                              ivp)
1100   `(let ((sequence (nthcdr ,start ,sequence)))
1101      (do ((count (if ,ivp ,start (1+ (the fixnum ,start)))
1102                  (1+ count))
1103           (sequence (if ,ivp sequence (cdr sequence))
1104                     (cdr sequence))
1105           (value (if ,ivp ,initial-value (apply-key ,key (car sequence)))
1106                  (funcall ,function value (apply-key ,key (car sequence)))))
1107          ((= count (the fixnum ,end)) value)
1108        (declare (fixnum count)))))
1109
1110 (sb!xc:defmacro list-reduce-from-end (function
1111                                       sequence
1112                                       key
1113                                       start
1114                                       end
1115                                       initial-value
1116                                       ivp)
1117   `(let ((sequence (nthcdr (- (the fixnum (length ,sequence))
1118                               (the fixnum ,end))
1119                            (reverse ,sequence))))
1120      (do ((count (if ,ivp ,start (1+ (the fixnum ,start)))
1121                  (1+ count))
1122           (sequence (if ,ivp sequence (cdr sequence))
1123                     (cdr sequence))
1124           (value (if ,ivp ,initial-value (apply-key ,key (car sequence)))
1125                  (funcall ,function (apply-key ,key (car sequence)) value)))
1126          ((= count (the fixnum ,end)) value)
1127        (declare (fixnum count)))))
1128
1129 ) ; EVAL-WHEN
1130
1131 (define-sequence-traverser reduce
1132     (function sequence &key key from-end start end (initial-value nil ivp))
1133   (declare (type index start))
1134   (let ((start start)
1135         (end (or end length)))
1136     (declare (type index start end))
1137     (cond ((= end start)
1138            (if ivp initial-value (funcall function)))
1139           ((listp sequence)
1140            (if from-end
1141                (list-reduce-from-end function sequence key start end
1142                                      initial-value ivp)
1143                (list-reduce function sequence key start end
1144                             initial-value ivp)))
1145           (from-end
1146            (when (not ivp)
1147              (setq end (1- (the fixnum end)))
1148              (setq initial-value (apply-key key (aref sequence end))))
1149            (mumble-reduce-from-end function sequence key start end
1150                                    initial-value aref))
1151           (t
1152            (when (not ivp)
1153              (setq initial-value (apply-key key (aref sequence start)))
1154              (setq start (1+ start)))
1155            (mumble-reduce function sequence key start end
1156                           initial-value aref)))))
1157 \f
1158 ;;;; DELETE
1159
1160 (eval-when (:compile-toplevel :execute)
1161
1162 (sb!xc:defmacro mumble-delete (pred)
1163   `(do ((index start (1+ index))
1164         (jndex start)
1165         (number-zapped 0))
1166        ((or (= index (the fixnum end)) (= number-zapped count))
1167         (do ((index index (1+ index))           ; Copy the rest of the vector.
1168              (jndex jndex (1+ jndex)))
1169             ((= index (the fixnum length))
1170              (shrink-vector sequence jndex))
1171           (declare (fixnum index jndex))
1172           (setf (aref sequence jndex) (aref sequence index))))
1173      (declare (fixnum index jndex number-zapped))
1174      (setf (aref sequence jndex) (aref sequence index))
1175      (if ,pred
1176          (incf number-zapped)
1177          (incf jndex))))
1178
1179 (sb!xc:defmacro mumble-delete-from-end (pred)
1180   `(do ((index (1- (the fixnum end)) (1- index)) ; Find the losers.
1181         (number-zapped 0)
1182         (losers ())
1183         this-element
1184         (terminus (1- start)))
1185        ((or (= index terminus) (= number-zapped count))
1186         (do ((losers losers)                     ; Delete the losers.
1187              (index start (1+ index))
1188              (jndex start))
1189             ((or (null losers) (= index (the fixnum end)))
1190              (do ((index index (1+ index))       ; Copy the rest of the vector.
1191                   (jndex jndex (1+ jndex)))
1192                  ((= index (the fixnum length))
1193                   (shrink-vector sequence jndex))
1194                (declare (fixnum index jndex))
1195                (setf (aref sequence jndex) (aref sequence index))))
1196           (declare (fixnum index jndex))
1197           (setf (aref sequence jndex) (aref sequence index))
1198           (if (= index (the fixnum (car losers)))
1199               (pop losers)
1200               (incf jndex))))
1201      (declare (fixnum index number-zapped terminus))
1202      (setq this-element (aref sequence index))
1203      (when ,pred
1204        (incf number-zapped)
1205        (push index losers))))
1206
1207 (sb!xc:defmacro normal-mumble-delete ()
1208   `(mumble-delete
1209     (if test-not
1210         (not (funcall test-not item (apply-key key (aref sequence index))))
1211         (funcall test item (apply-key key (aref sequence index))))))
1212
1213 (sb!xc:defmacro normal-mumble-delete-from-end ()
1214   `(mumble-delete-from-end
1215     (if test-not
1216         (not (funcall test-not item (apply-key key this-element)))
1217         (funcall test item (apply-key key this-element)))))
1218
1219 (sb!xc:defmacro list-delete (pred)
1220   `(let ((handle (cons nil sequence)))
1221      (do ((current (nthcdr start sequence) (cdr current))
1222           (previous (nthcdr start handle))
1223           (index start (1+ index))
1224           (number-zapped 0))
1225          ((or (= index (the fixnum end)) (= number-zapped count))
1226           (cdr handle))
1227        (declare (fixnum index number-zapped))
1228        (cond (,pred
1229               (rplacd previous (cdr current))
1230               (incf number-zapped))
1231              (t
1232               (setq previous (cdr previous)))))))
1233
1234 (sb!xc:defmacro list-delete-from-end (pred)
1235   `(let* ((reverse (nreverse (the list sequence)))
1236           (handle (cons nil reverse)))
1237      (do ((current (nthcdr (- (the fixnum length) (the fixnum end)) reverse)
1238                    (cdr current))
1239           (previous (nthcdr (- (the fixnum length) (the fixnum end)) handle))
1240           (index start (1+ index))
1241           (number-zapped 0))
1242          ((or (= index (the fixnum end)) (= number-zapped count))
1243           (nreverse (cdr handle)))
1244        (declare (fixnum index number-zapped))
1245        (cond (,pred
1246               (rplacd previous (cdr current))
1247               (incf number-zapped))
1248              (t
1249               (setq previous (cdr previous)))))))
1250
1251 (sb!xc:defmacro normal-list-delete ()
1252   '(list-delete
1253     (if test-not
1254         (not (funcall test-not item (apply-key key (car current))))
1255         (funcall test item (apply-key key (car current))))))
1256
1257 (sb!xc:defmacro normal-list-delete-from-end ()
1258   '(list-delete-from-end
1259     (if test-not
1260         (not (funcall test-not item (apply-key key (car current))))
1261         (funcall test item (apply-key key (car current))))))
1262
1263 ) ; EVAL-WHEN
1264
1265 (define-sequence-traverser delete
1266     (item sequence &key from-end test test-not start
1267           end count key)
1268   #!+sb-doc
1269   "Return a sequence formed by destructively removing the specified ITEM from
1270   the given SEQUENCE."
1271   (declare (fixnum start))
1272   (let ((end (or end length)))
1273     (declare (type index end))
1274     (seq-dispatch sequence
1275                   (if from-end
1276                       (normal-list-delete-from-end)
1277                       (normal-list-delete))
1278                   (if from-end
1279                       (normal-mumble-delete-from-end)
1280                       (normal-mumble-delete)))))
1281
1282 (eval-when (:compile-toplevel :execute)
1283
1284 (sb!xc:defmacro if-mumble-delete ()
1285   `(mumble-delete
1286     (funcall predicate (apply-key key (aref sequence index)))))
1287
1288 (sb!xc:defmacro if-mumble-delete-from-end ()
1289   `(mumble-delete-from-end
1290     (funcall predicate (apply-key key this-element))))
1291
1292 (sb!xc:defmacro if-list-delete ()
1293   '(list-delete
1294     (funcall predicate (apply-key key (car current)))))
1295
1296 (sb!xc:defmacro if-list-delete-from-end ()
1297   '(list-delete-from-end
1298     (funcall predicate (apply-key key (car current)))))
1299
1300 ) ; EVAL-WHEN
1301
1302 (define-sequence-traverser delete-if
1303     (predicate sequence &key from-end start key end count)
1304   #!+sb-doc
1305   "Return a sequence formed by destructively removing the elements satisfying
1306   the specified PREDICATE from the given SEQUENCE."
1307   (declare (fixnum start))
1308   (let ((end (or end length)))
1309     (declare (type index end))
1310     (seq-dispatch sequence
1311                   (if from-end
1312                       (if-list-delete-from-end)
1313                       (if-list-delete))
1314                   (if from-end
1315                       (if-mumble-delete-from-end)
1316                       (if-mumble-delete)))))
1317
1318 (eval-when (:compile-toplevel :execute)
1319
1320 (sb!xc:defmacro if-not-mumble-delete ()
1321   `(mumble-delete
1322     (not (funcall predicate (apply-key key (aref sequence index))))))
1323
1324 (sb!xc:defmacro if-not-mumble-delete-from-end ()
1325   `(mumble-delete-from-end
1326     (not (funcall predicate (apply-key key this-element)))))
1327
1328 (sb!xc:defmacro if-not-list-delete ()
1329   '(list-delete
1330     (not (funcall predicate (apply-key key (car current))))))
1331
1332 (sb!xc:defmacro if-not-list-delete-from-end ()
1333   '(list-delete-from-end
1334     (not (funcall predicate (apply-key key (car current))))))
1335
1336 ) ; EVAL-WHEN
1337
1338 (define-sequence-traverser delete-if-not
1339     (predicate sequence &key from-end start end key count)
1340   #!+sb-doc
1341   "Return a sequence formed by destructively removing the elements not
1342   satisfying the specified PREDICATE from the given SEQUENCE."
1343   (declare (fixnum start))
1344   (let ((end (or end length)))
1345     (declare (type index end))
1346     (seq-dispatch sequence
1347                   (if from-end
1348                       (if-not-list-delete-from-end)
1349                       (if-not-list-delete))
1350                   (if from-end
1351                       (if-not-mumble-delete-from-end)
1352                       (if-not-mumble-delete)))))
1353 \f
1354 ;;;; REMOVE
1355
1356 (eval-when (:compile-toplevel :execute)
1357
1358 ;;; MUMBLE-REMOVE-MACRO does not include (removes) each element that
1359 ;;; satisfies the predicate.
1360 (sb!xc:defmacro mumble-remove-macro (bump left begin finish right pred)
1361   `(do ((index ,begin (,bump index))
1362         (result
1363          (do ((index ,left (,bump index))
1364               (result (make-sequence-like sequence length)))
1365              ((= index (the fixnum ,begin)) result)
1366            (declare (fixnum index))
1367            (setf (aref result index) (aref sequence index))))
1368         (new-index ,begin)
1369         (number-zapped 0)
1370         (this-element))
1371        ((or (= index (the fixnum ,finish))
1372             (= number-zapped count))
1373         (do ((index index (,bump index))
1374              (new-index new-index (,bump new-index)))
1375             ((= index (the fixnum ,right)) (shrink-vector result new-index))
1376           (declare (fixnum index new-index))
1377           (setf (aref result new-index) (aref sequence index))))
1378      (declare (fixnum index new-index number-zapped))
1379      (setq this-element (aref sequence index))
1380      (cond (,pred (incf number-zapped))
1381            (t (setf (aref result new-index) this-element)
1382               (setq new-index (,bump new-index))))))
1383
1384 (sb!xc:defmacro mumble-remove (pred)
1385   `(mumble-remove-macro 1+ 0 start end length ,pred))
1386
1387 (sb!xc:defmacro mumble-remove-from-end (pred)
1388   `(let ((sequence (copy-seq sequence)))
1389      (mumble-delete-from-end ,pred)))
1390
1391 (sb!xc:defmacro normal-mumble-remove ()
1392   `(mumble-remove
1393     (if test-not
1394         (not (funcall test-not item (apply-key key this-element)))
1395         (funcall test item (apply-key key this-element)))))
1396
1397 (sb!xc:defmacro normal-mumble-remove-from-end ()
1398   `(mumble-remove-from-end
1399     (if test-not
1400         (not (funcall test-not item (apply-key key this-element)))
1401         (funcall test item (apply-key key this-element)))))
1402
1403 (sb!xc:defmacro if-mumble-remove ()
1404   `(mumble-remove (funcall predicate (apply-key key this-element))))
1405
1406 (sb!xc:defmacro if-mumble-remove-from-end ()
1407   `(mumble-remove-from-end (funcall predicate (apply-key key this-element))))
1408
1409 (sb!xc:defmacro if-not-mumble-remove ()
1410   `(mumble-remove (not (funcall predicate (apply-key key this-element)))))
1411
1412 (sb!xc:defmacro if-not-mumble-remove-from-end ()
1413   `(mumble-remove-from-end
1414     (not (funcall predicate (apply-key key this-element)))))
1415
1416 ;;; LIST-REMOVE-MACRO does not include (removes) each element that satisfies
1417 ;;; the predicate.
1418 (sb!xc:defmacro list-remove-macro (pred reverse?)
1419   `(let* ((sequence ,(if reverse?
1420                          '(reverse (the list sequence))
1421                          'sequence))
1422           (%start ,(if reverse? '(- length end) 'start))
1423           (%end ,(if reverse? '(- length start) 'end))
1424           (splice (list nil))
1425           (results (do ((index 0 (1+ index))
1426                         (before-start splice))
1427                        ((= index (the fixnum %start)) before-start)
1428                      (declare (fixnum index))
1429                      (setq splice
1430                            (cdr (rplacd splice (list (pop sequence))))))))
1431      (do ((index %start (1+ index))
1432           (this-element)
1433           (number-zapped 0))
1434          ((or (= index (the fixnum %end)) (= number-zapped count))
1435           (do ((index index (1+ index)))
1436               ((null sequence)
1437                ,(if reverse?
1438                     '(nreverse (the list (cdr results)))
1439                     '(cdr results)))
1440             (declare (fixnum index))
1441             (setq splice (cdr (rplacd splice (list (pop sequence)))))))
1442        (declare (fixnum index number-zapped))
1443        (setq this-element (pop sequence))
1444        (if ,pred
1445            (setq number-zapped (1+ number-zapped))
1446            (setq splice (cdr (rplacd splice (list this-element))))))))
1447
1448 (sb!xc:defmacro list-remove (pred)
1449   `(list-remove-macro ,pred nil))
1450
1451 (sb!xc:defmacro list-remove-from-end (pred)
1452   `(list-remove-macro ,pred t))
1453
1454 (sb!xc:defmacro normal-list-remove ()
1455   `(list-remove
1456     (if test-not
1457         (not (funcall test-not item (apply-key key this-element)))
1458         (funcall test item (apply-key key this-element)))))
1459
1460 (sb!xc:defmacro normal-list-remove-from-end ()
1461   `(list-remove-from-end
1462     (if test-not
1463         (not (funcall test-not item (apply-key key this-element)))
1464         (funcall test item (apply-key key this-element)))))
1465
1466 (sb!xc:defmacro if-list-remove ()
1467   `(list-remove
1468     (funcall predicate (apply-key key this-element))))
1469
1470 (sb!xc:defmacro if-list-remove-from-end ()
1471   `(list-remove-from-end
1472     (funcall predicate (apply-key key this-element))))
1473
1474 (sb!xc:defmacro if-not-list-remove ()
1475   `(list-remove
1476     (not (funcall predicate (apply-key key this-element)))))
1477
1478 (sb!xc:defmacro if-not-list-remove-from-end ()
1479   `(list-remove-from-end
1480     (not (funcall predicate (apply-key key this-element)))))
1481
1482 ) ; EVAL-WHEN
1483
1484 (define-sequence-traverser remove
1485     (item sequence &key from-end test test-not start
1486           end count key)
1487   #!+sb-doc
1488   "Return a copy of SEQUENCE with elements satisfying the test (default is
1489    EQL) with ITEM removed."
1490   (declare (fixnum start))
1491   (let ((end (or end length)))
1492     (declare (type index end))
1493     (seq-dispatch sequence
1494                   (if from-end
1495                       (normal-list-remove-from-end)
1496                       (normal-list-remove))
1497                   (if from-end
1498                       (normal-mumble-remove-from-end)
1499                       (normal-mumble-remove)))))
1500
1501 (define-sequence-traverser remove-if
1502     (predicate sequence &key from-end start end count key)
1503   #!+sb-doc
1504   "Return a copy of sequence with elements such that predicate(element)
1505    is non-null removed"
1506   (declare (fixnum start))
1507   (let ((end (or end length)))
1508     (declare (type index end))
1509     (seq-dispatch sequence
1510                   (if from-end
1511                       (if-list-remove-from-end)
1512                       (if-list-remove))
1513                   (if from-end
1514                       (if-mumble-remove-from-end)
1515                       (if-mumble-remove)))))
1516
1517 (define-sequence-traverser remove-if-not
1518     (predicate sequence &key from-end start end count key)
1519   #!+sb-doc
1520   "Return a copy of sequence with elements such that predicate(element)
1521    is null removed"
1522   (declare (fixnum start))
1523   (let ((end (or end length)))
1524     (declare (type index end))
1525     (seq-dispatch sequence
1526                   (if from-end
1527                       (if-not-list-remove-from-end)
1528                       (if-not-list-remove))
1529                   (if from-end
1530                       (if-not-mumble-remove-from-end)
1531                       (if-not-mumble-remove)))))
1532 \f
1533 ;;;; REMOVE-DUPLICATES
1534
1535 ;;; Remove duplicates from a list. If from-end, remove the later duplicates,
1536 ;;; not the earlier ones. Thus if we check from-end we don't copy an item
1537 ;;; if we look into the already copied structure (from after :start) and see
1538 ;;; the item. If we check from beginning we check into the rest of the
1539 ;;; original list up to the :end marker (this we have to do by running a
1540 ;;; do loop down the list that far and using our test.
1541 (defun list-remove-duplicates* (list test test-not start end key from-end)
1542   (declare (fixnum start))
1543   (let* ((result (list ())) ; Put a marker on the beginning to splice with.
1544          (splice result)
1545          (current list))
1546     (do ((index 0 (1+ index)))
1547         ((= index start))
1548       (declare (fixnum index))
1549       (setq splice (cdr (rplacd splice (list (car current)))))
1550       (setq current (cdr current)))
1551     (do ((index 0 (1+ index)))
1552         ((or (and end (= index (the fixnum end)))
1553              (atom current)))
1554       (declare (fixnum index))
1555       (if (or (and from-end
1556                    (not (if test-not
1557                             (member (apply-key key (car current))
1558                                     (nthcdr (1+ start) result)
1559                                     :test-not test-not
1560                                     :key key)
1561                             (member (apply-key key (car current))
1562                                     (nthcdr (1+ start) result)
1563                                     :test test
1564                                     :key key))))
1565               (and (not from-end)
1566                    (not (do ((it (apply-key key (car current)))
1567                              (l (cdr current) (cdr l))
1568                              (i (1+ index) (1+ i)))
1569                             ((or (atom l) (and end (= i (the fixnum end))))
1570                              ())
1571                           (declare (fixnum i))
1572                           (if (if test-not
1573                                   (not (funcall test-not
1574                                                 it
1575                                                 (apply-key key (car l))))
1576                                   (funcall test it (apply-key key (car l))))
1577                               (return t))))))
1578           (setq splice (cdr (rplacd splice (list (car current))))))
1579       (setq current (cdr current)))
1580     (do ()
1581         ((atom current))
1582       (setq splice (cdr (rplacd splice (list (car current)))))
1583       (setq current (cdr current)))
1584     (cdr result)))
1585
1586 (defun vector-remove-duplicates* (vector test test-not start end key from-end
1587                                          &optional (length (length vector)))
1588   (declare (vector vector) (fixnum start length))
1589   (when (null end) (setf end (length vector)))
1590   (let ((result (make-sequence-like vector length))
1591         (index 0)
1592         (jndex start))
1593     (declare (fixnum index jndex))
1594     (do ()
1595         ((= index start))
1596       (setf (aref result index) (aref vector index))
1597       (setq index (1+ index)))
1598     (do ((elt))
1599         ((= index end))
1600       (setq elt (aref vector index))
1601       ;; FIXME: Relying on POSITION allowing both :TEST and :TEST-NOT
1602       ;; arguments simultaneously is a little fragile, since ANSI says
1603       ;; we can't depend on it, so we need to remember to keep that
1604       ;; extension in our implementation. It'd probably be better to
1605       ;; rewrite this to avoid passing both (as
1606       ;; LIST-REMOVE-DUPLICATES* was rewritten ca. sbcl-0.7.12.18).
1607       (unless (or (and from-end
1608                        (position (apply-key key elt) result
1609                                  :start start :end jndex
1610                                  :test test :test-not test-not :key key))
1611                   (and (not from-end)
1612                        (position (apply-key key elt) vector
1613                                  :start (1+ index) :end end
1614                                  :test test :test-not test-not :key key)))
1615         (setf (aref result jndex) elt)
1616         (setq jndex (1+ jndex)))
1617       (setq index (1+ index)))
1618     (do ()
1619         ((= index length))
1620       (setf (aref result jndex) (aref vector index))
1621       (setq index (1+ index))
1622       (setq jndex (1+ jndex)))
1623     (shrink-vector result jndex)))
1624
1625 (define-sequence-traverser remove-duplicates
1626     (sequence &key test test-not start end from-end key)
1627   #!+sb-doc
1628   "The elements of SEQUENCE are compared pairwise, and if any two match,
1629    the one occurring earlier is discarded, unless FROM-END is true, in
1630    which case the one later in the sequence is discarded. The resulting
1631    sequence is returned.
1632
1633    The :TEST-NOT argument is deprecated."
1634   (declare (fixnum start))
1635   (seq-dispatch sequence
1636                 (if sequence
1637                     (list-remove-duplicates* sequence test test-not
1638                                               start end key from-end))
1639                 (vector-remove-duplicates* sequence test test-not
1640                                             start end key from-end)))
1641 \f
1642 ;;;; DELETE-DUPLICATES
1643
1644 (defun list-delete-duplicates* (list test test-not key from-end start end)
1645   (declare (fixnum start))
1646   (let ((handle (cons nil list)))
1647     (do ((current (nthcdr start list) (cdr current))
1648          (previous (nthcdr start handle))
1649          (index start (1+ index)))
1650         ((or (and end (= index (the fixnum end))) (null current))
1651          (cdr handle))
1652       (declare (fixnum index))
1653       (if (do ((x (if from-end
1654                       (nthcdr (1+ start) handle)
1655                       (cdr current))
1656                   (cdr x))
1657                (i (1+ index) (1+ i)))
1658               ((or (null x)
1659                    (and (not from-end) end (= i (the fixnum end)))
1660                    (eq x current))
1661                nil)
1662             (declare (fixnum i))
1663             (if (if test-not
1664                     (not (funcall test-not
1665                                   (apply-key key (car current))
1666                                   (apply-key key (car x))))
1667                     (funcall test
1668                              (apply-key key (car current))
1669                              (apply-key key (car x))))
1670                 (return t)))
1671           (rplacd previous (cdr current))
1672           (setq previous (cdr previous))))))
1673
1674 (defun vector-delete-duplicates* (vector test test-not key from-end start end
1675                                          &optional (length (length vector)))
1676   (declare (vector vector) (fixnum start length))
1677   (when (null end) (setf end (length vector)))
1678   (do ((index start (1+ index))
1679        (jndex start))
1680       ((= index end)
1681        (do ((index index (1+ index))            ; copy the rest of the vector
1682             (jndex jndex (1+ jndex)))
1683            ((= index length)
1684             (shrink-vector vector jndex)
1685             vector)
1686          (setf (aref vector jndex) (aref vector index))))
1687     (declare (fixnum index jndex))
1688     (setf (aref vector jndex) (aref vector index))
1689     (unless (position (apply-key key (aref vector index)) vector :key key
1690                       :start (if from-end start (1+ index)) :test test
1691                       :end (if from-end jndex end) :test-not test-not)
1692       (setq jndex (1+ jndex)))))
1693
1694 (define-sequence-traverser delete-duplicates
1695     (sequence &key test test-not start end from-end key)
1696   #!+sb-doc
1697   "The elements of SEQUENCE are examined, and if any two match, one is
1698    discarded. The resulting sequence, which may be formed by destroying the
1699    given sequence, is returned.
1700
1701    The :TEST-NOT argument is deprecated."
1702   (seq-dispatch sequence
1703     (if sequence
1704         (list-delete-duplicates* sequence test test-not key from-end start end))
1705     (vector-delete-duplicates* sequence test test-not key from-end start end)))
1706 \f
1707 ;;;; SUBSTITUTE
1708
1709 (defun list-substitute* (pred new list start end count key test test-not old)
1710   (declare (fixnum start end count))
1711   (let* ((result (list nil))
1712          elt
1713          (splice result)
1714          (list list))      ; Get a local list for a stepper.
1715     (do ((index 0 (1+ index)))
1716         ((= index start))
1717       (declare (fixnum index))
1718       (setq splice (cdr (rplacd splice (list (car list)))))
1719       (setq list (cdr list)))
1720     (do ((index start (1+ index)))
1721         ((or (= index end) (null list) (= count 0)))
1722       (declare (fixnum index))
1723       (setq elt (car list))
1724       (setq splice
1725             (cdr (rplacd splice
1726                          (list
1727                           (cond
1728                            ((case pred
1729                                    (normal
1730                                     (if test-not
1731                                         (not
1732                                          (funcall test-not old (apply-key key elt)))
1733                                         (funcall test old (apply-key key elt))))
1734                                    (if (funcall test (apply-key key elt)))
1735                                    (if-not (not (funcall test (apply-key key elt)))))
1736                             (decf count)
1737                             new)
1738                                 (t elt))))))
1739       (setq list (cdr list)))
1740     (do ()
1741         ((null list))
1742       (setq splice (cdr (rplacd splice (list (car list)))))
1743       (setq list (cdr list)))
1744     (cdr result)))
1745
1746 ;;; Replace old with new in sequence moving from left to right by incrementer
1747 ;;; on each pass through the loop. Called by all three substitute functions.
1748 (defun vector-substitute* (pred new sequence incrementer left right length
1749                            start end count key test test-not old)
1750   (declare (fixnum start count end incrementer right))
1751   (let ((result (make-sequence-like sequence length))
1752         (index left))
1753     (declare (fixnum index))
1754     (do ()
1755         ((= index start))
1756       (setf (aref result index) (aref sequence index))
1757       (setq index (+ index incrementer)))
1758     (do ((elt))
1759         ((or (= index end) (= count 0)))
1760       (setq elt (aref sequence index))
1761       (setf (aref result index)
1762             (cond ((case pred
1763                           (normal
1764                             (if test-not
1765                                 (not (funcall test-not old (apply-key key elt)))
1766                                 (funcall test old (apply-key key elt))))
1767                           (if (funcall test (apply-key key elt)))
1768                           (if-not (not (funcall test (apply-key key elt)))))
1769                    (setq count (1- count))
1770                    new)
1771                   (t elt)))
1772       (setq index (+ index incrementer)))
1773     (do ()
1774         ((= index right))
1775       (setf (aref result index) (aref sequence index))
1776       (setq index (+ index incrementer)))
1777     result))
1778
1779 (eval-when (:compile-toplevel :execute)
1780
1781 (sb!xc:defmacro subst-dispatch (pred)
1782   `(if (listp sequence)
1783        (if from-end
1784            (nreverse (list-substitute* ,pred
1785                                        new
1786                                        (reverse sequence)
1787                                        (- (the fixnum length)
1788                                           (the fixnum end))
1789                                        (- (the fixnum length)
1790                                           (the fixnum start))
1791                                        count key test test-not old))
1792            (list-substitute* ,pred
1793                              new sequence start end count key test test-not
1794                              old))
1795       (if from-end
1796           (vector-substitute* ,pred new sequence -1 (1- (the fixnum length))
1797                               -1 length (1- (the fixnum end))
1798                               (1- (the fixnum start))
1799                               count key test test-not old)
1800           (vector-substitute* ,pred new sequence 1 0 length length
1801            start end count key test test-not old))))
1802
1803 ) ; EVAL-WHEN
1804
1805 (define-sequence-traverser substitute
1806     (new old sequence &key from-end test test-not
1807          start count end key)
1808   #!+sb-doc
1809   "Return a sequence of the same kind as SEQUENCE with the same elements,
1810   except that all elements equal to OLD are replaced with NEW. See manual
1811   for details."
1812   (declare (fixnum start))
1813   (let ((end (or end length)))
1814     (declare (type index end))
1815     (subst-dispatch 'normal)))
1816 \f
1817 ;;;; SUBSTITUTE-IF, SUBSTITUTE-IF-NOT
1818
1819 (define-sequence-traverser substitute-if
1820     (new pred sequence &key from-end start end count key)
1821   #!+sb-doc
1822   "Return a sequence of the same kind as SEQUENCE with the same elements
1823   except that all elements satisfying the PRED are replaced with NEW. See
1824   manual for details."
1825   (declare (fixnum start))
1826   (let ((end (or end length))
1827         (test pred)
1828         test-not
1829         old)
1830     (declare (type index length end))
1831     (subst-dispatch 'if)))
1832
1833 (define-sequence-traverser substitute-if-not
1834     (new pred sequence &key from-end start end count key)
1835   #!+sb-doc
1836   "Return a sequence of the same kind as SEQUENCE with the same elements
1837   except that all elements not satisfying the PRED are replaced with NEW.
1838   See manual for details."
1839   (declare (fixnum start))
1840   (let ((end (or end length))
1841         (test pred)
1842         test-not
1843         old)
1844     (declare (type index length end))
1845     (subst-dispatch 'if-not)))
1846 \f
1847 ;;;; NSUBSTITUTE
1848
1849 (define-sequence-traverser nsubstitute
1850     (new old sequence &key from-end test test-not
1851          end count key start)
1852   #!+sb-doc
1853   "Return a sequence of the same kind as SEQUENCE with the same elements
1854   except that all elements equal to OLD are replaced with NEW. The SEQUENCE
1855   may be destructively modified. See manual for details."
1856   (declare (fixnum start))
1857   (let ((end (or end length)))
1858     (if (listp sequence)
1859         (if from-end
1860             (let ((length (length sequence)))
1861               (nreverse (nlist-substitute*
1862                          new old (nreverse (the list sequence))
1863                          test test-not (- length end) (- length start)
1864                          count key)))
1865             (nlist-substitute* new old sequence
1866                                test test-not start end count key))
1867         (if from-end
1868             (nvector-substitute* new old sequence -1
1869                                  test test-not (1- end) (1- start) count key)
1870             (nvector-substitute* new old sequence 1
1871                                  test test-not start end count key)))))
1872
1873 (defun nlist-substitute* (new old sequence test test-not start end count key)
1874   (declare (fixnum start count end))
1875   (do ((list (nthcdr start sequence) (cdr list))
1876        (index start (1+ index)))
1877       ((or (= index end) (null list) (= count 0)) sequence)
1878     (declare (fixnum index))
1879     (when (if test-not
1880               (not (funcall test-not old (apply-key key (car list))))
1881               (funcall test old (apply-key key (car list))))
1882       (rplaca list new)
1883       (setq count (1- count)))))
1884
1885 (defun nvector-substitute* (new old sequence incrementer
1886                             test test-not start end count key)
1887   (declare (fixnum start incrementer count end))
1888   (do ((index start (+ index incrementer)))
1889       ((or (= index end) (= count 0)) sequence)
1890     (declare (fixnum index))
1891     (when (if test-not
1892               (not (funcall test-not
1893                             old
1894                             (apply-key key (aref sequence index))))
1895               (funcall test old (apply-key key (aref sequence index))))
1896       (setf (aref sequence index) new)
1897       (setq count (1- count)))))
1898 \f
1899 ;;;; NSUBSTITUTE-IF, NSUBSTITUTE-IF-NOT
1900
1901 (define-sequence-traverser nsubstitute-if
1902     (new pred sequence &key from-end start end count key)
1903   #!+sb-doc
1904   "Return a sequence of the same kind as SEQUENCE with the same elements
1905    except that all elements satisfying the PRED are replaced with NEW. 
1906    SEQUENCE may be destructively modified. See manual for details."
1907   (declare (fixnum start))
1908   (let ((end (or end length)))
1909     (declare (fixnum end))
1910     (if (listp sequence)
1911         (if from-end
1912             (let ((length (length sequence)))
1913               (nreverse (nlist-substitute-if*
1914                          new pred (nreverse (the list sequence))
1915                          (- length end) (- length start) count key)))
1916             (nlist-substitute-if* new pred sequence
1917                                   start end count key))
1918         (if from-end
1919             (nvector-substitute-if* new pred sequence -1
1920                                     (1- end) (1- start) count key)
1921             (nvector-substitute-if* new pred sequence 1
1922                                     start end count key)))))
1923
1924 (defun nlist-substitute-if* (new test sequence start end count key)
1925   (declare (fixnum end))
1926   (do ((list (nthcdr start sequence) (cdr list))
1927        (index start (1+ index)))
1928       ((or (= index end) (null list) (= count 0)) sequence)
1929     (when (funcall test (apply-key key (car list)))
1930       (rplaca list new)
1931       (setq count (1- count)))))
1932
1933 (defun nvector-substitute-if* (new test sequence incrementer
1934                                start end count key)
1935   (do ((index start (+ index incrementer)))
1936       ((or (= index end) (= count 0)) sequence)
1937     (when (funcall test (apply-key key (aref sequence index)))
1938       (setf (aref sequence index) new)
1939       (setq count (1- count)))))
1940
1941 (define-sequence-traverser nsubstitute-if-not
1942     (new pred sequence &key from-end start end count key)
1943   #!+sb-doc
1944   "Return a sequence of the same kind as SEQUENCE with the same elements
1945    except that all elements not satisfying the TEST are replaced with NEW.
1946    SEQUENCE may be destructively modified. See manual for details."
1947   (declare (fixnum start))
1948   (let ((end (or end length)))
1949     (declare (fixnum end))
1950     (if (listp sequence)
1951         (if from-end
1952             (let ((length (length sequence)))
1953               (nreverse (nlist-substitute-if-not*
1954                          new pred (nreverse (the list sequence))
1955                          (- length end) (- length start) count key)))
1956             (nlist-substitute-if-not* new pred sequence
1957                                       start end count key))
1958         (if from-end
1959             (nvector-substitute-if-not* new pred sequence -1
1960                                         (1- end) (1- start) count key)
1961             (nvector-substitute-if-not* new pred sequence 1
1962                                         start end count key)))))
1963
1964 (defun nlist-substitute-if-not* (new test sequence start end count key)
1965   (declare (fixnum end))
1966   (do ((list (nthcdr start sequence) (cdr list))
1967        (index start (1+ index)))
1968       ((or (= index end) (null list) (= count 0)) sequence)
1969     (when (not (funcall test (apply-key key (car list))))
1970       (rplaca list new)
1971       (decf count))))
1972
1973 (defun nvector-substitute-if-not* (new test sequence incrementer
1974                                    start end count key)
1975   (do ((index start (+ index incrementer)))
1976       ((or (= index end) (= count 0)) sequence)
1977     (when (not (funcall test (apply-key key (aref sequence index))))
1978       (setf (aref sequence index) new)
1979       (decf count))))
1980 \f
1981 ;;;; FIND, POSITION, and their -IF and -IF-NOT variants
1982
1983 (defun effective-find-position-test (test test-not)
1984   (effective-find-position-test test test-not))
1985 (defun effective-find-position-key (key)
1986   (effective-find-position-key key))
1987
1988 ;;; shared guts of out-of-line FIND, POSITION, FIND-IF, and POSITION-IF
1989 (macrolet (;; shared logic for defining %FIND-POSITION and
1990            ;; %FIND-POSITION-IF in terms of various inlineable cases
1991            ;; of the expression defined in FROB and VECTOR*-FROB
1992            (frobs ()
1993              `(etypecase sequence-arg
1994                 (list (frob sequence-arg from-end))
1995                 (vector
1996                  (with-array-data ((sequence sequence-arg :offset-var offset)
1997                                    (start start)
1998                                    (end (%check-vector-sequence-bounds
1999                                          sequence-arg start end)))
2000                    (multiple-value-bind (f p)
2001                        (macrolet ((frob2 () '(if from-end
2002                                                  (frob sequence t)
2003                                                  (frob sequence nil))))
2004                          (typecase sequence
2005                            (simple-vector (frob2))
2006                            (simple-base-string (frob2))
2007                            (t (vector*-frob sequence))))
2008                      (declare (type (or index null) p))
2009                      (values f (and p (the index (+ p offset))))))))))
2010   (defun %find-position (item sequence-arg from-end start end key test)
2011     (macrolet ((frob (sequence from-end)
2012                  `(%find-position item ,sequence
2013                                   ,from-end start end key test))
2014                (vector*-frob (sequence)
2015                  `(%find-position-vector-macro item ,sequence
2016                                                from-end start end key test)))
2017       (frobs)))
2018   (defun %find-position-if (predicate sequence-arg from-end start end key)
2019     (macrolet ((frob (sequence from-end)
2020                  `(%find-position-if predicate ,sequence
2021                                      ,from-end start end key))
2022                (vector*-frob (sequence)
2023                  `(%find-position-if-vector-macro predicate ,sequence
2024                                                   from-end start end key)))
2025       (frobs)))
2026   (defun %find-position-if-not (predicate sequence-arg from-end start end key)
2027     (macrolet ((frob (sequence from-end)
2028                  `(%find-position-if-not predicate ,sequence
2029                                          ,from-end start end key))
2030                (vector*-frob (sequence)
2031                  `(%find-position-if-not-vector-macro predicate ,sequence
2032                                                   from-end start end key)))
2033       (frobs))))
2034
2035 ;;; the user interface to FIND and POSITION: just interpreter stubs,
2036 ;;; nowadays.
2037 (defun find (item sequence &key from-end (start 0) end key test test-not)
2038   ;; FIXME: this can't be the way to go, surely?
2039   (find item sequence :from-end from-end :start start :end end :key key
2040         :test test :test-not test-not))
2041 (defun position (item sequence &key from-end (start 0) end key test test-not)
2042   (position item sequence :from-end from-end :start start :end end :key key
2043             :test test :test-not test-not))
2044
2045 ;;; the user interface to FIND-IF and POSITION-IF, entirely analogous
2046 ;;; to the interface to FIND and POSITION
2047 (defun find-if (predicate sequence &key from-end (start 0) end key)
2048   (find-if predicate sequence :from-end from-end :start start
2049            :end end :key key))
2050 (defun position-if (predicate sequence &key from-end (start 0) end key)
2051   (position-if predicate sequence :from-end from-end :start start
2052                :end end :key key))
2053
2054 (defun find-if-not (predicate sequence &key from-end (start 0) end key)
2055   (find-if-not predicate sequence :from-end from-end :start start
2056            :end end :key key))
2057 (defun position-if-not (predicate sequence &key from-end (start 0) end key)
2058   (position-if-not predicate sequence :from-end from-end :start start
2059                :end end :key key))
2060 \f
2061 ;;;; COUNT-IF, COUNT-IF-NOT, and COUNT
2062
2063 (eval-when (:compile-toplevel :execute)
2064
2065 (sb!xc:defmacro vector-count-if (notp from-end-p predicate sequence)
2066   (let ((next-index (if from-end-p '(1- index) '(1+ index)))
2067         (pred `(funcall ,predicate (apply-key key (aref ,sequence index)))))
2068     `(let ((%start ,(if from-end-p '(1- end) 'start))
2069            (%end ,(if from-end-p '(1- start) 'end)))
2070       (do ((index %start ,next-index)
2071            (count 0))
2072           ((= index (the fixnum %end)) count)
2073         (declare (fixnum index count))
2074         (,(if notp 'unless 'when) ,pred
2075           (setq count (1+ count)))))))
2076
2077 (sb!xc:defmacro list-count-if (notp from-end-p predicate sequence)
2078   (let ((pred `(funcall ,predicate (apply-key key (pop sequence)))))
2079     `(let ((%start ,(if from-end-p '(- length end) 'start))
2080            (%end ,(if from-end-p '(- length start) 'end))
2081            (sequence ,(if from-end-p '(reverse sequence) 'sequence)))
2082       (do ((sequence (nthcdr %start ,sequence))
2083            (index %start (1+ index))
2084            (count 0))
2085           ((or (= index (the fixnum %end)) (null sequence)) count)
2086         (declare (fixnum index count))
2087         (,(if notp 'unless 'when) ,pred
2088           (setq count (1+ count)))))))
2089
2090
2091 ) ; EVAL-WHEN
2092
2093 (define-sequence-traverser count-if (pred sequence &key from-end start end key)
2094   #!+sb-doc
2095   "Return the number of elements in SEQUENCE satisfying PRED(el)."
2096   (declare (fixnum start))
2097   (let ((end (or end length)))
2098     (declare (type index end))
2099     (seq-dispatch sequence
2100                   (if from-end
2101                       (list-count-if nil t pred sequence)
2102                       (list-count-if nil nil pred sequence))
2103                   (if from-end
2104                       (vector-count-if nil t pred sequence)
2105                       (vector-count-if nil nil pred sequence)))))
2106
2107 (define-sequence-traverser count-if-not
2108     (pred sequence &key from-end start end key)
2109   #!+sb-doc
2110   "Return the number of elements in SEQUENCE not satisfying TEST(el)."
2111   (declare (fixnum start))
2112   (let ((end (or end length)))
2113     (declare (type index end))
2114     (seq-dispatch sequence
2115                   (if from-end
2116                       (list-count-if t t pred sequence)
2117                       (list-count-if t nil pred sequence))
2118                   (if from-end
2119                       (vector-count-if t t pred sequence)
2120                       (vector-count-if t nil pred sequence)))))
2121
2122 (define-sequence-traverser count
2123     (item sequence &key from-end start end
2124           key (test #'eql test-p) (test-not nil test-not-p))
2125   #!+sb-doc
2126   "Return the number of elements in SEQUENCE satisfying a test with ITEM,
2127    which defaults to EQL."
2128   (declare (fixnum start))
2129   (when (and test-p test-not-p)
2130     ;; ANSI Common Lisp has left the behavior in this situation unspecified.
2131     ;; (CLHS 17.2.1)
2132     (error ":TEST and :TEST-NOT are both present."))
2133   (let ((end (or end length)))
2134     (declare (type index end))
2135     (let ((%test (if test-not-p
2136                      (lambda (x)
2137                        (not (funcall test-not item x)))
2138                      (lambda (x)
2139                        (funcall test item x)))))
2140       (seq-dispatch sequence
2141                     (if from-end
2142                         (list-count-if nil t %test sequence)
2143                         (list-count-if nil nil %test sequence))
2144                     (if from-end
2145                         (vector-count-if nil t %test sequence)
2146                         (vector-count-if nil nil %test sequence))))))
2147
2148
2149 \f
2150 ;;;; MISMATCH
2151
2152 (eval-when (:compile-toplevel :execute)
2153
2154 (sb!xc:defmacro match-vars (&rest body)
2155   `(let ((inc (if from-end -1 1))
2156          (start1 (if from-end (1- (the fixnum end1)) start1))
2157          (start2 (if from-end (1- (the fixnum end2)) start2))
2158          (end1 (if from-end (1- (the fixnum start1)) end1))
2159          (end2 (if from-end (1- (the fixnum start2)) end2)))
2160      (declare (fixnum inc start1 start2 end1 end2))
2161      ,@body))
2162
2163 (sb!xc:defmacro matchify-list ((sequence start length end) &body body)
2164   (declare (ignore end)) ;; ### Should END be used below?
2165   `(let ((,sequence (if from-end
2166                         (nthcdr (- (the fixnum ,length) (the fixnum ,start) 1)
2167                                 (reverse (the list ,sequence)))
2168                         (nthcdr ,start ,sequence))))
2169      (declare (type list ,sequence))
2170      ,@body))
2171
2172 ) ; EVAL-WHEN
2173
2174 (eval-when (:compile-toplevel :execute)
2175
2176 (sb!xc:defmacro if-mismatch (elt1 elt2)
2177   `(cond ((= (the fixnum index1) (the fixnum end1))
2178           (return (if (= (the fixnum index2) (the fixnum end2))
2179                       nil
2180                       (if from-end
2181                           (1+ (the fixnum index1))
2182                           (the fixnum index1)))))
2183          ((= (the fixnum index2) (the fixnum end2))
2184           (return (if from-end (1+ (the fixnum index1)) index1)))
2185          (test-not
2186           (if (funcall test-not (apply-key key ,elt1) (apply-key key ,elt2))
2187               (return (if from-end (1+ (the fixnum index1)) index1))))
2188          (t (if (not (funcall test (apply-key key ,elt1)
2189                               (apply-key key ,elt2)))
2190                 (return (if from-end (1+ (the fixnum index1)) index1))))))
2191
2192 (sb!xc:defmacro mumble-mumble-mismatch ()
2193   `(do ((index1 start1 (+ index1 (the fixnum inc)))
2194         (index2 start2 (+ index2 (the fixnum inc))))
2195        (())
2196      (declare (fixnum index1 index2))
2197      (if-mismatch (aref sequence1 index1) (aref sequence2 index2))))
2198
2199 (sb!xc:defmacro mumble-list-mismatch ()
2200   `(do ((index1 start1 (+ index1 (the fixnum inc)))
2201         (index2 start2 (+ index2 (the fixnum inc))))
2202        (())
2203      (declare (fixnum index1 index2))
2204      (if-mismatch (aref sequence1 index1) (pop sequence2))))
2205 \f
2206 (sb!xc:defmacro list-mumble-mismatch ()
2207   `(do ((index1 start1 (+ index1 (the fixnum inc)))
2208         (index2 start2 (+ index2 (the fixnum inc))))
2209        (())
2210      (declare (fixnum index1 index2))
2211      (if-mismatch (pop sequence1) (aref sequence2 index2))))
2212
2213 (sb!xc:defmacro list-list-mismatch ()
2214   `(do ((sequence1 sequence1)
2215         (sequence2 sequence2)
2216         (index1 start1 (+ index1 (the fixnum inc)))
2217         (index2 start2 (+ index2 (the fixnum inc))))
2218        (())
2219      (declare (fixnum index1 index2))
2220      (if-mismatch (pop sequence1) (pop sequence2))))
2221
2222 ) ; EVAL-WHEN
2223
2224 (define-sequence-traverser mismatch
2225     (sequence1 sequence2
2226                &key from-end test test-not
2227                start1 end1 start2 end2 key)
2228   #!+sb-doc
2229   "The specified subsequences of SEQUENCE1 and SEQUENCE2 are compared
2230    element-wise. If they are of equal length and match in every element, the
2231    result is NIL. Otherwise, the result is a non-negative integer, the index
2232    within SEQUENCE1 of the leftmost position at which they fail to match; or,
2233    if one is shorter than and a matching prefix of the other, the index within
2234    SEQUENCE1 beyond the last position tested is returned. If a non-NIL
2235    :FROM-END argument is given, then one plus the index of the rightmost
2236    position in which the sequences differ is returned."
2237   (declare (fixnum start1 start2))
2238   (let* ((end1 (or end1 length1))
2239          (end2 (or end2 length2)))
2240     (declare (type index end1 end2))
2241     (match-vars
2242      (seq-dispatch sequence1
2243        (matchify-list (sequence1 start1 length1 end1)
2244          (seq-dispatch sequence2
2245            (matchify-list (sequence2 start2 length2 end2)
2246              (list-list-mismatch))
2247            (list-mumble-mismatch)))
2248        (seq-dispatch sequence2
2249          (matchify-list (sequence2 start2 length2 end2)
2250            (mumble-list-mismatch))
2251          (mumble-mumble-mismatch))))))
2252 \f
2253 ;;; search comparison functions
2254
2255 (eval-when (:compile-toplevel :execute)
2256
2257 ;;; Compare two elements and return if they don't match.
2258 (sb!xc:defmacro compare-elements (elt1 elt2)
2259   `(if test-not
2260        (if (funcall test-not (apply-key key ,elt1) (apply-key key ,elt2))
2261            (return nil)
2262            t)
2263        (if (not (funcall test (apply-key key ,elt1) (apply-key key ,elt2)))
2264            (return nil)
2265            t)))
2266
2267 (sb!xc:defmacro search-compare-list-list (main sub)
2268   `(do ((main ,main (cdr main))
2269         (jndex start1 (1+ jndex))
2270         (sub (nthcdr start1 ,sub) (cdr sub)))
2271        ((or (endp main) (endp sub) (<= end1 jndex))
2272         t)
2273      (declare (type (integer 0) jndex))
2274      (compare-elements (car sub) (car main))))
2275
2276 (sb!xc:defmacro search-compare-list-vector (main sub)
2277   `(do ((main ,main (cdr main))
2278         (index start1 (1+ index)))
2279        ((or (endp main) (= index end1)) t)
2280      (compare-elements (aref ,sub index) (car main))))
2281
2282 (sb!xc:defmacro search-compare-vector-list (main sub index)
2283   `(do ((sub (nthcdr start1 ,sub) (cdr sub))
2284         (jndex start1 (1+ jndex))
2285         (index ,index (1+ index)))
2286        ((or (<= end1 jndex) (endp sub)) t)
2287      (declare (type (integer 0) jndex))
2288      (compare-elements (car sub) (aref ,main index))))
2289
2290 (sb!xc:defmacro search-compare-vector-vector (main sub index)
2291   `(do ((index ,index (1+ index))
2292         (sub-index start1 (1+ sub-index)))
2293        ((= sub-index end1) t)
2294      (compare-elements (aref ,sub sub-index) (aref ,main index))))
2295
2296 (sb!xc:defmacro search-compare (main-type main sub index)
2297   (if (eq main-type 'list)
2298       `(seq-dispatch ,sub
2299                      (search-compare-list-list ,main ,sub)
2300                      (search-compare-list-vector ,main ,sub))
2301       `(seq-dispatch ,sub
2302                      (search-compare-vector-list ,main ,sub ,index)
2303                      (search-compare-vector-vector ,main ,sub ,index))))
2304
2305 ) ; EVAL-WHEN
2306 \f
2307 ;;;; SEARCH
2308
2309 (eval-when (:compile-toplevel :execute)
2310
2311 (sb!xc:defmacro list-search (main sub)
2312   `(do ((main (nthcdr start2 ,main) (cdr main))
2313         (index2 start2 (1+ index2))
2314         (terminus (- end2 (the (integer 0) (- end1 start1))))
2315         (last-match ()))
2316        ((> index2 terminus) last-match)
2317      (declare (type (integer 0) index2))
2318      (if (search-compare list main ,sub index2)
2319          (if from-end
2320              (setq last-match index2)
2321              (return index2)))))
2322
2323 (sb!xc:defmacro vector-search (main sub)
2324   `(do ((index2 start2 (1+ index2))
2325         (terminus (- end2 (the (integer 0) (- end1 start1))))
2326         (last-match ()))
2327        ((> index2 terminus) last-match)
2328      (declare (type (integer 0) index2))
2329      (if (search-compare vector ,main ,sub index2)
2330          (if from-end
2331              (setq last-match index2)
2332              (return index2)))))
2333
2334 ) ; EVAL-WHEN
2335
2336 (define-sequence-traverser search
2337     (sequence1 sequence2
2338                &key from-end test test-not
2339                start1 end1 start2 end2 key)
2340   (declare (fixnum start1 start2))
2341   (let ((end1 (or end1 length1))
2342         (end2 (or end2 length2)))
2343     (seq-dispatch sequence2
2344                   (list-search sequence2 sequence1)
2345                   (vector-search sequence2 sequence1))))