0.8.0.78.vector-nil-string.7:
[sbcl.git] / src / code / array.lisp
1 ;;;; functions to implement arrays
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!IMPL")
13
14 #!-sb-fluid
15 (declaim (inline fill-pointer array-has-fill-pointer-p adjustable-array-p
16                  array-displacement))
17 \f
18 ;;;; miscellaneous accessor functions
19
20 ;;; These functions are only needed by the interpreter, 'cause the
21 ;;; compiler inlines them.
22 (macrolet ((def (name)
23              `(progn
24                 (defun ,name (array)
25                   (,name array))
26                 (defun (setf ,name) (value array)
27                   (setf (,name array) value)))))
28   (def %array-fill-pointer)
29   (def %array-fill-pointer-p)
30   (def %array-available-elements)
31   (def %array-data-vector)
32   (def %array-displacement)
33   (def %array-displaced-p))
34
35 (defun %array-rank (array)
36   (%array-rank array))
37
38 (defun %array-dimension (array axis)
39   (%array-dimension array axis))
40
41 (defun %set-array-dimension (array axis value)
42   (%set-array-dimension array axis value))
43
44 (defun %check-bound (array bound index)
45   (declare (type index bound)
46            (fixnum index))
47   (%check-bound array bound index))
48
49 (defun %with-array-data (array start end)
50   (%with-array-data-macro array start end :fail-inline? t))
51
52 (defun %data-vector-and-index (array index)
53   (if (array-header-p array)
54       (multiple-value-bind (vector index)
55           (%with-array-data array index nil)
56         (values vector index))
57       (values array index)))
58
59 ;;; It'd waste space to expand copies of error handling in every
60 ;;; inline %WITH-ARRAY-DATA, so we have them call this function
61 ;;; instead. This is just a wrapper which is known never to return.
62 (defun failed-%with-array-data (array start end)
63   (declare (notinline %with-array-data))
64   (%with-array-data array start end)
65   (bug "called FAILED-%WITH-ARRAY-DATA with valid array parameters?"))
66 \f
67 ;;;; MAKE-ARRAY
68 (defun upgraded-array-element-type (spec &optional environment)
69   #!+sb-doc
70   "Return the element type that will actually be used to implement an array
71    with the specifier :ELEMENT-TYPE Spec."
72   (declare (ignore environment))
73   (if (unknown-type-p (specifier-type spec))
74       (error "undefined type: ~S" spec)
75       (type-specifier (array-type-specialized-element-type
76                        (specifier-type `(array ,spec))))))
77 (eval-when (:compile-toplevel :execute)
78   (sb!xc:defmacro pick-vector-type (type &rest specs)
79     `(cond ,@(mapcar (lambda (spec)
80                        `(,(if (eq (car spec) t)
81                               t
82                               `(subtypep ,type ',(car spec)))
83                          ,@(cdr spec)))
84                      specs))))
85
86 ;;; These functions are used in the implementation of MAKE-ARRAY for
87 ;;; complex arrays. There are lots of transforms to simplify
88 ;;; MAKE-ARRAY for various easy cases, but not for all reasonable
89 ;;; cases, so e.g. as of sbcl-0.6.6 we still make full calls to
90 ;;; MAKE-ARRAY for any non-simple array. Thus, there's some value to
91 ;;; making this somewhat efficient, at least not doing full calls to
92 ;;; SUBTYPEP in the easy cases.
93 (defun %vector-widetag-and-n-bits (type)
94   (case type
95     ;; Pick off some easy common cases.
96     ;;
97     ;; (Perhaps we should make a much more exhaustive table of easy
98     ;; common cases here. Or perhaps the effort would be better spent
99     ;; on smarter compiler transforms which do the calculation once
100     ;; and for all in any reasonable user programs.)
101     ((t)
102      (values #.sb!vm:simple-vector-widetag #.sb!vm:n-word-bits))
103     ((base-char standard-char)
104      (values #.sb!vm:simple-base-string-widetag #.sb!vm:n-byte-bits))
105     ((bit)
106      (values #.sb!vm:simple-bit-vector-widetag 1))
107     ;; OK, we have to wade into SUBTYPEPing after all.
108     (t
109      ;; FIXME: The data here are redundant with
110      ;; *SPECIALIZED-ARRAY-ELEMENT-TYPE-PROPERTIES*.
111      (pick-vector-type type
112        (nil (values #.sb!vm:simple-array-nil-widetag 0))
113        (base-char (values #.sb!vm:simple-base-string-widetag #.sb!vm:n-byte-bits))
114        (bit (values #.sb!vm:simple-bit-vector-widetag 1))
115        ((unsigned-byte 2)
116         (values #.sb!vm:simple-array-unsigned-byte-2-widetag 2))
117        ((unsigned-byte 4)
118         (values #.sb!vm:simple-array-unsigned-byte-4-widetag 4))
119        ((unsigned-byte 8)
120         (values #.sb!vm:simple-array-unsigned-byte-8-widetag 8))
121        ((unsigned-byte 16)
122         (values #.sb!vm:simple-array-unsigned-byte-16-widetag 16))
123        ((unsigned-byte 32)
124         (values #.sb!vm:simple-array-unsigned-byte-32-widetag 32))
125        ((signed-byte 8)
126         (values #.sb!vm:simple-array-signed-byte-8-widetag 8))
127        ((signed-byte 16)
128         (values #.sb!vm:simple-array-signed-byte-16-widetag 16))
129        ((signed-byte 30)
130         (values #.sb!vm:simple-array-signed-byte-30-widetag 32))
131        ((signed-byte 32)
132         (values #.sb!vm:simple-array-signed-byte-32-widetag 32))
133        (single-float (values #.sb!vm:simple-array-single-float-widetag 32))
134        (double-float (values #.sb!vm:simple-array-double-float-widetag 64))
135        #!+long-float
136        (long-float
137         (values #.sb!vm:simple-array-long-float-widetag
138                 #!+x86 96 #!+sparc 128))
139        ((complex single-float)
140         (values #.sb!vm:simple-array-complex-single-float-widetag 64))
141        ((complex double-float)
142         (values #.sb!vm:simple-array-complex-double-float-widetag 128))
143        #!+long-float
144        ((complex long-float)
145         (values #.sb!vm:simple-array-complex-long-float-widetag
146                 #!+x86 192
147                 #!+sparc 256))
148        (t (values #.sb!vm:simple-vector-widetag #.sb!vm:n-word-bits))))))
149 (defun %complex-vector-widetag (type)
150   (case type
151     ;; Pick off some easy common cases.
152     ((t)
153      #.sb!vm:complex-vector-widetag)
154     ((base-char)
155      #.sb!vm:complex-base-string-widetag)
156     ((nil)
157      #.sb!vm:complex-vector-nil-widetag)
158     ((bit)
159      #.sb!vm:complex-bit-vector-widetag)
160     ;; OK, we have to wade into SUBTYPEPing after all.
161     (t
162      (pick-vector-type type
163        (nil #.sb!vm:complex-vector-nil-widetag)
164        (base-char #.sb!vm:complex-base-string-widetag)
165        (bit #.sb!vm:complex-bit-vector-widetag)
166        (t #.sb!vm:complex-vector-widetag)))))
167
168 (defun make-array (dimensions &key
169                               (element-type t)
170                               (initial-element nil initial-element-p)
171                               initial-contents adjustable fill-pointer
172                               displaced-to displaced-index-offset)
173   (let* ((dimensions (if (listp dimensions) dimensions (list dimensions)))
174          (array-rank (length (the list dimensions)))
175          (simple (and (null fill-pointer)
176                       (not adjustable)
177                       (null displaced-to))))
178     (declare (fixnum array-rank))
179     (when (and displaced-index-offset (null displaced-to))
180       (error "can't specify :DISPLACED-INDEX-OFFSET without :DISPLACED-TO"))
181     (if (and simple (= array-rank 1))
182         ;; it's a (SIMPLE-ARRAY * (*))
183         (multiple-value-bind (type n-bits)
184             (%vector-widetag-and-n-bits element-type)
185           (declare (type (unsigned-byte 8) type)
186                    (type (integer 0 256) n-bits))
187           (let* ((length (car dimensions))
188                  (array (allocate-vector
189                          type
190                          length
191                          (ceiling (* (if (= type sb!vm:simple-base-string-widetag)
192                                          (1+ length)
193                                          length)
194                                      n-bits)
195                                   sb!vm:n-word-bits))))
196             (declare (type index length))
197             (when initial-element-p
198               (fill array initial-element))
199             (when initial-contents
200               (when initial-element
201                 (error "can't specify both :INITIAL-ELEMENT and ~
202                 :INITIAL-CONTENTS"))
203               (unless (= length (length initial-contents))
204                 (error "There are ~W elements in the :INITIAL-CONTENTS, but ~
205                        the vector length is ~W."
206                        (length initial-contents)
207                        length))
208               (replace array initial-contents))
209             array))
210         ;; it's either a complex array or a multidimensional array.
211         (let* ((total-size (reduce #'* dimensions))
212                (data (or displaced-to
213                          (data-vector-from-inits
214                           dimensions total-size element-type
215                           initial-contents initial-element initial-element-p)))
216                (array (make-array-header
217                        (cond ((= array-rank 1)
218                               (%complex-vector-widetag element-type))
219                              (simple sb!vm:simple-array-widetag)
220                              (t sb!vm:complex-array-widetag))
221                        array-rank)))
222           (cond (fill-pointer
223                  (unless (= array-rank 1)
224                    (error "Only vectors can have fill pointers."))
225                  (let ((length (car dimensions)))
226                    (declare (fixnum length))
227                    (setf (%array-fill-pointer array)
228                      (cond ((eq fill-pointer t)
229                             length)
230                            (t
231                             (unless (and (fixnump fill-pointer)
232                                          (>= fill-pointer 0)
233                                          (<= fill-pointer length))
234                               ;; FIXME: should be TYPE-ERROR?
235                               (error "invalid fill-pointer ~W"
236                                      fill-pointer))
237                             fill-pointer))))
238                  (setf (%array-fill-pointer-p array) t))
239                 (t
240                  (setf (%array-fill-pointer array) total-size)
241                  (setf (%array-fill-pointer-p array) nil)))
242           (setf (%array-available-elements array) total-size)
243           (setf (%array-data-vector array) data)
244           (cond (displaced-to
245                  (when (or initial-element-p initial-contents)
246                    (error "Neither :INITIAL-ELEMENT nor :INITIAL-CONTENTS ~
247                    can be specified along with :DISPLACED-TO"))
248                  (let ((offset (or displaced-index-offset 0)))
249                    (when (> (+ offset total-size)
250                             (array-total-size displaced-to))
251                      (error "~S doesn't have enough elements." displaced-to))
252                    (setf (%array-displacement array) offset)
253                    (setf (%array-displaced-p array) t)))
254                 (t
255                  (setf (%array-displaced-p array) nil)))
256           (let ((axis 0))
257             (dolist (dim dimensions)
258               (setf (%array-dimension array axis) dim)
259               (incf axis)))
260           array))))
261
262 ;;; DATA-VECTOR-FROM-INITS returns a simple vector that has the
263 ;;; specified array characteristics. Dimensions is only used to pass
264 ;;; to FILL-DATA-VECTOR for error checking on the structure of
265 ;;; initial-contents.
266 (defun data-vector-from-inits (dimensions total-size element-type
267                                initial-contents initial-element
268                                initial-element-p)
269   (when (and initial-contents initial-element-p)
270     (error "cannot supply both :INITIAL-CONTENTS and :INITIAL-ELEMENT to
271             either MAKE-ARRAY or ADJUST-ARRAY."))
272   (let ((data (if initial-element-p
273                   (make-array total-size
274                               :element-type element-type
275                               :initial-element initial-element)
276                   (make-array total-size
277                               :element-type element-type))))
278     (cond (initial-element-p
279            (unless (simple-vector-p data)
280              (unless (typep initial-element element-type)
281                (error "~S cannot be used to initialize an array of type ~S."
282                       initial-element element-type))
283              (fill (the vector data) initial-element)))
284           (initial-contents
285            (fill-data-vector data dimensions initial-contents)))
286     data))
287
288 (defun fill-data-vector (vector dimensions initial-contents)
289   (let ((index 0))
290     (labels ((frob (axis dims contents)
291                (cond ((null dims)
292                       (setf (aref vector index) contents)
293                       (incf index))
294                      (t
295                       (unless (typep contents 'sequence)
296                         (error "malformed :INITIAL-CONTENTS: ~S is not a ~
297                                 sequence, but ~W more layer~:P needed."
298                                contents
299                                (- (length dimensions) axis)))
300                       (unless (= (length contents) (car dims))
301                         (error "malformed :INITIAL-CONTENTS: Dimension of ~
302                                 axis ~W is ~W, but ~S is ~W long."
303                                axis (car dims) contents (length contents)))
304                       (if (listp contents)
305                           (dolist (content contents)
306                             (frob (1+ axis) (cdr dims) content))
307                           (dotimes (i (length contents))
308                             (frob (1+ axis) (cdr dims) (aref contents i))))))))
309       (frob 0 dimensions initial-contents))))
310
311 (defun vector (&rest objects)
312   #!+sb-doc
313   "Construct a SIMPLE-VECTOR from the given objects."
314   (coerce (the list objects) 'simple-vector))
315 \f
316 ;;;; accessor/setter functions
317 (eval-when (:compile-toplevel :execute)
318   (defparameter *specialized-array-element-types*
319     ;; FIXME: Ideally we would generate this list from
320     ;; SPECIALIZED-ARRAY-ELEMENT-TYPE-PROPERTIES.  However, this list
321     ;; is optimized for frequency of occurrence, not type lattice
322     ;; relationships, so it's tricky to do so cleanly.
323     '(t
324       character
325       bit
326       (unsigned-byte 8)
327       (unsigned-byte 16)
328       (unsigned-byte 32)
329       (signed-byte 8)
330       (signed-byte 16)
331       (signed-byte 30)
332       (signed-byte 32)
333       single-float
334       double-float
335       #!+long-float long-float
336       (complex single-float)
337       (complex double-float)
338       #!+long-float (complex long-float)
339       (unsigned-byte 4)
340       (unsigned-byte 2)
341       nil)))
342
343 (defun hairy-data-vector-ref (array index)
344   (with-array-data ((vector array) (index index) (end))
345     (declare (ignore end))
346     (etypecase vector .
347                #.(mapcar (lambda (type)
348                            (let ((atype `(simple-array ,type (*))))
349                              `(,atype
350                                (data-vector-ref (the ,atype vector)
351                                                 index))))
352                          *specialized-array-element-types*))))
353
354 ;;; (Ordinary DATA-VECTOR-REF usage compiles into a vop, but
355 ;;; DATA-VECTOR-REF is also FOLDABLE, and this ordinary function
356 ;;; definition is needed for the compiler to use in constant folding.)
357 (defun data-vector-ref (array index)
358   (hairy-data-vector-ref array index))
359
360 (defun hairy-data-vector-set (array index new-value)
361   (with-array-data ((vector array) (index index) (end))
362     (declare (ignore end))
363     (etypecase vector .
364                #.(mapcar (lambda (type)
365                            (let ((atype `(simple-array ,type (*))))
366                              `(,atype
367                                (data-vector-set (the ,atype vector)
368                                                 index
369                                                 (the ,type
370                                                   new-value))
371                                ;; For specialized arrays, the return
372                                ;; from data-vector-set would have to
373                                ;; be reboxed to be a (Lisp) return
374                                ;; value; instead, we use the
375                                ;; already-boxed value as the return.
376                                new-value)))
377                          *specialized-array-element-types*))))
378
379 (defun %array-row-major-index (array subscripts
380                                      &optional (invalid-index-error-p t))
381   (declare (array array)
382            (list subscripts))
383   (let ((rank (array-rank array)))
384     (unless (= rank (length subscripts))
385       (error "wrong number of subscripts, ~W, for array of rank ~W"
386              (length subscripts) rank))
387     (if (array-header-p array)
388         (do ((subs (nreverse subscripts) (cdr subs))
389              (axis (1- (array-rank array)) (1- axis))
390              (chunk-size 1)
391              (result 0))
392             ((null subs) result)
393           (declare (list subs) (fixnum axis chunk-size result))
394           (let ((index (car subs))
395                 (dim (%array-dimension array axis)))
396             (declare (fixnum dim))
397             (unless (< -1 index dim)
398               (if invalid-index-error-p
399                   (error 'simple-type-error
400                          :format-control "invalid index ~W~[~;~:; on axis ~:*~W~] in ~S"
401                          :format-arguments (list index axis array)
402                          :datum index
403                          :expected-type `(integer 0 (,dim)))
404                   (return-from %array-row-major-index nil)))
405             (incf result (* chunk-size (the fixnum index)))
406             (setf chunk-size (* chunk-size dim))))
407         (let ((index (first subscripts))
408               (length (length (the (simple-array * (*)) array))))
409           (unless (< -1 index length)
410             (if invalid-index-error-p
411                 ;; FIXME: perhaps this should share a format-string
412                 ;; with INVALID-ARRAY-INDEX-ERROR or
413                 ;; INDEX-TOO-LARGE-ERROR?
414                 (error 'simple-type-error
415                        :format-control "invalid index ~W in ~S"
416                        :format-arguments (list index array)
417                        :datum index
418                        :expected-type `(integer 0 (,length)))
419                 (return-from %array-row-major-index nil)))
420           index))))
421
422 (defun array-in-bounds-p (array &rest subscripts)
423   #!+sb-doc
424   "Return T if the Subscipts are in bounds for the Array, Nil otherwise."
425   (if (%array-row-major-index array subscripts nil)
426       t))
427
428 (defun array-row-major-index (array &rest subscripts)
429   (%array-row-major-index array subscripts))
430
431 (defun aref (array &rest subscripts)
432   #!+sb-doc
433   "Return the element of the Array specified by the Subscripts."
434   (row-major-aref array (%array-row-major-index array subscripts)))
435
436 (defun %aset (array &rest stuff)
437   (let ((subscripts (butlast stuff))
438         (new-value (car (last stuff))))
439     (setf (row-major-aref array (%array-row-major-index array subscripts))
440           new-value)))
441
442 ;;; FIXME: What's supposed to happen with functions
443 ;;; like AREF when we (DEFUN (SETF FOO) ..) when
444 ;;; DEFSETF FOO is also defined? It seems as though the logical
445 ;;; thing to do would be to nuke the macro definition for (SETF FOO)
446 ;;; and replace it with the (SETF FOO) function, issuing a warning,
447 ;;; just as for ordinary functions
448 ;;;  * (LISP-IMPLEMENTATION-VERSION)
449 ;;;  "18a+ release x86-linux 2.4.7 6 November 1998 cvs"
450 ;;;  * (DEFMACRO ZOO (X) `(+ ,X ,X))
451 ;;;  ZOO
452 ;;;  * (DEFUN ZOO (X) (* 3 X))
453 ;;;  Warning: ZOO previously defined as a macro.
454 ;;;  ZOO
455 ;;; But that doesn't seem to be what happens in CMU CL.
456 ;;;
457 ;;; KLUDGE: this is probably because ANSI, in its wisdom (CLHS
458 ;;; 5.1.2.5) requires implementations to support
459 ;;;   (SETF (APPLY #'AREF ...) ...)
460 ;;; [and also #'BIT and #'SBIT].  Yes, this is terrifying, and it's
461 ;;; also terrifying that this sequence of definitions causes it to
462 ;;; work.
463 ;;;
464 ;;; Also, it would be nice to make DESCRIBE FOO tell whether a symbol
465 ;;; has a setf expansion and/or a setf function defined.
466
467 #!-sb-fluid (declaim (inline (setf aref)))
468 (defun (setf aref) (new-value array &rest subscripts)
469   (declare (type array array))
470   (setf (row-major-aref array (%array-row-major-index array subscripts))
471         new-value))
472
473 (defun row-major-aref (array index)
474   #!+sb-doc
475   "Return the element of array corressponding to the row-major index. This is
476    SETF'able."
477   (declare (optimize (safety 1)))
478   (row-major-aref array index))
479
480 (defun %set-row-major-aref (array index new-value)
481   (declare (optimize (safety 1)))
482   (setf (row-major-aref array index) new-value))
483
484 (defun svref (simple-vector index)
485   #!+sb-doc
486   "Return the INDEX'th element of the given Simple-Vector."
487   (declare (optimize (safety 1)))
488   (aref simple-vector index))
489
490 (defun %svset (simple-vector index new)
491   (declare (optimize (safety 1)))
492   (setf (aref simple-vector index) new))
493
494 (defun bit (bit-array &rest subscripts)
495   #!+sb-doc
496   "Return the bit from the BIT-ARRAY at the specified SUBSCRIPTS."
497   (declare (type (array bit) bit-array) (optimize (safety 1)))
498   (row-major-aref bit-array (%array-row-major-index bit-array subscripts)))
499
500 (defun %bitset (bit-array &rest stuff)
501   (declare (type (array bit) bit-array) (optimize (safety 1)))
502   (let ((subscripts (butlast stuff))
503         (new-value (car (last stuff))))
504     (setf (row-major-aref bit-array
505                           (%array-row-major-index bit-array subscripts))
506           new-value)))
507
508 #!-sb-fluid (declaim (inline (setf bit)))
509 (defun (setf bit) (new-value bit-array &rest subscripts)
510   (declare (type (array bit) bit-array) (optimize (safety 1)))
511   (setf (row-major-aref bit-array
512                         (%array-row-major-index bit-array subscripts))
513         new-value))
514
515 (defun sbit (simple-bit-array &rest subscripts)
516   #!+sb-doc
517   "Return the bit from SIMPLE-BIT-ARRAY at the specified SUBSCRIPTS."
518   (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
519   (row-major-aref simple-bit-array
520                   (%array-row-major-index simple-bit-array subscripts)))
521
522 ;;; KLUDGE: Not all these things (%SET-ROW-MAJOR-AREF, %SET-FILL-POINTER,
523 ;;; %SET-FDEFINITION, %SCHARSET, %SBITSET..) seem to deserve separate names.
524 ;;; Could we just DEFUN (SETF SBIT) etc. and get rid of the non-ANSI names?
525 ;;; -- WHN 19990911
526 (defun %sbitset (simple-bit-array &rest stuff)
527   (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
528   (let ((subscripts (butlast stuff))
529         (new-value (car (last stuff))))
530     (setf (row-major-aref simple-bit-array
531                           (%array-row-major-index simple-bit-array subscripts))
532           new-value)))
533
534 #!-sb-fluid (declaim (inline (setf sbit)))
535 (defun (setf sbit) (new-value bit-array &rest subscripts)
536   (declare (type (simple-array bit) bit-array) (optimize (safety 1)))
537   (setf (row-major-aref bit-array
538                         (%array-row-major-index bit-array subscripts))
539         new-value))
540 \f
541 ;;;; miscellaneous array properties
542
543 (defun array-element-type (array)
544   #!+sb-doc
545   "Return the type of the elements of the array"
546   (let ((widetag (widetag-of array)))
547     (macrolet ((pick-element-type (&rest stuff)
548                  `(cond ,@(mapcar (lambda (stuff)
549                                     (cons
550                                      (let ((item (car stuff)))
551                                        (cond ((eq item t)
552                                               t)
553                                              ((listp item)
554                                               (cons 'or
555                                                     (mapcar (lambda (x)
556                                                               `(= widetag ,x))
557                                                             item)))
558                                              (t
559                                               `(= widetag ,item))))
560                                      (cdr stuff)))
561                                   stuff))))
562       ;; FIXME: The data here are redundant with
563       ;; *SPECIALIZED-ARRAY-ELEMENT-TYPE-PROPERTIES*.
564       (pick-element-type
565        ((sb!vm:simple-array-nil-widetag sb!vm:complex-vector-nil-widetag) nil)
566        ((sb!vm:simple-base-string-widetag sb!vm:complex-base-string-widetag) 'base-char)
567        ((sb!vm:simple-bit-vector-widetag
568          sb!vm:complex-bit-vector-widetag) 'bit)
569        (sb!vm:simple-vector-widetag t)
570        (sb!vm:simple-array-unsigned-byte-2-widetag '(unsigned-byte 2))
571        (sb!vm:simple-array-unsigned-byte-4-widetag '(unsigned-byte 4))
572        (sb!vm:simple-array-unsigned-byte-8-widetag '(unsigned-byte 8))
573        (sb!vm:simple-array-unsigned-byte-16-widetag '(unsigned-byte 16))
574        (sb!vm:simple-array-unsigned-byte-32-widetag '(unsigned-byte 32))
575        (sb!vm:simple-array-signed-byte-8-widetag '(signed-byte 8))
576        (sb!vm:simple-array-signed-byte-16-widetag '(signed-byte 16))
577        (sb!vm:simple-array-signed-byte-30-widetag '(signed-byte 30))
578        (sb!vm:simple-array-signed-byte-32-widetag '(signed-byte 32))
579        (sb!vm:simple-array-single-float-widetag 'single-float)
580        (sb!vm:simple-array-double-float-widetag 'double-float)
581        #!+long-float
582        (sb!vm:simple-array-long-float-widetag 'long-float)
583        (sb!vm:simple-array-complex-single-float-widetag
584         '(complex single-float))
585        (sb!vm:simple-array-complex-double-float-widetag
586         '(complex double-float))
587        #!+long-float
588        (sb!vm:simple-array-complex-long-float-widetag '(complex long-float))
589        ((sb!vm:simple-array-widetag
590          sb!vm:complex-vector-widetag
591          sb!vm:complex-array-widetag)
592         (with-array-data ((array array) (start) (end))
593           (declare (ignore start end))
594           (array-element-type array)))
595        (t
596         (error 'type-error :datum array :expected-type 'array))))))
597
598 (defun array-rank (array)
599   #!+sb-doc
600   "Return the number of dimensions of ARRAY."
601   (if (array-header-p array)
602       (%array-rank array)
603       1))
604
605 (defun array-dimension (array axis-number)
606   #!+sb-doc
607   "Return the length of dimension AXIS-NUMBER of ARRAY."
608   (declare (array array) (type index axis-number))
609   (cond ((not (array-header-p array))
610          (unless (= axis-number 0)
611            (error "Vector axis is not zero: ~S" axis-number))
612          (length (the (simple-array * (*)) array)))
613         ((>= axis-number (%array-rank array))
614          (error "Axis number ~W is too big; ~S only has ~D dimension~:P."
615                 axis-number array (%array-rank array)))
616         (t
617          (%array-dimension array axis-number))))
618
619 (defun array-dimensions (array)
620   #!+sb-doc
621   "Return a list whose elements are the dimensions of the array"
622   (declare (array array))
623   (if (array-header-p array)
624       (do ((results nil (cons (array-dimension array index) results))
625            (index (1- (array-rank array)) (1- index)))
626           ((minusp index) results))
627       (list (array-dimension array 0))))
628
629 (defun array-total-size (array)
630   #!+sb-doc
631   "Return the total number of elements in the Array."
632   (declare (array array))
633   (if (array-header-p array)
634       (%array-available-elements array)
635       (length (the vector array))))
636
637 (defun array-displacement (array)
638   #!+sb-doc
639   "Return the values of :DISPLACED-TO and :DISPLACED-INDEX-offset
640    options to MAKE-ARRAY, or NIL and 0 if not a displaced array."
641   (declare (type array array))
642   (if (and (array-header-p array) ; if unsimple and
643            (%array-displaced-p array)) ; displaced
644       (values (%array-data-vector array) (%array-displacement array))
645       (values nil 0)))
646
647 (defun adjustable-array-p (array)
648   #!+sb-doc
649   "Return T if (ADJUST-ARRAY ARRAY...) would return an array identical
650    to the argument, this happens for complex arrays."
651   (declare (array array))
652   (not (typep array 'simple-array)))
653 \f
654 ;;;; fill pointer frobbing stuff
655
656 (defun array-has-fill-pointer-p (array)
657   #!+sb-doc
658   "Return T if the given ARRAY has a fill pointer, or NIL otherwise."
659   (declare (array array))
660   (and (array-header-p array) (%array-fill-pointer-p array)))
661
662 (defun fill-pointer (vector)
663   #!+sb-doc
664   "Return the FILL-POINTER of the given VECTOR."
665   (declare (vector vector))
666   (if (and (array-header-p vector) (%array-fill-pointer-p vector))
667       (%array-fill-pointer vector)
668       (error 'simple-type-error
669              :datum vector
670              :expected-type '(and vector (satisfies array-has-fill-pointer-p))
671              :format-control "~S is not an array with a fill pointer."
672              :format-arguments (list vector))))
673
674 (defun %set-fill-pointer (vector new)
675   (declare (vector vector) (fixnum new))
676   (if (and (array-header-p vector) (%array-fill-pointer-p vector))
677       (if (> new (%array-available-elements vector))
678         (error
679          "The new fill pointer, ~S, is larger than the length of the vector."
680          new)
681         (setf (%array-fill-pointer vector) new))
682       (error 'simple-type-error
683              :datum vector
684              :expected-type '(and vector (satisfies array-has-fill-pointer-p))
685              :format-control "~S is not an array with a fill pointer."
686              :format-arguments (list vector))))
687
688 ;;; FIXME: It'd probably make sense to use a MACROLET to share the
689 ;;; guts of VECTOR-PUSH between VECTOR-PUSH-EXTEND. Such a macro
690 ;;; should probably be based on the VECTOR-PUSH-EXTEND code (which is
691 ;;; new ca. sbcl-0.7.0) rather than the VECTOR-PUSH code (which dates
692 ;;; back to CMU CL).
693 (defun vector-push (new-el array)
694   #!+sb-doc
695   "Attempt to set the element of ARRAY designated by its fill pointer
696    to NEW-EL, and increment the fill pointer by one. If the fill pointer is
697    too large, NIL is returned, otherwise the index of the pushed element is
698    returned."
699   (declare (vector array))
700   (let ((fill-pointer (fill-pointer array)))
701     (declare (fixnum fill-pointer))
702     (cond ((= fill-pointer (%array-available-elements array))
703            nil)
704           (t
705            (setf (aref array fill-pointer) new-el)
706            (setf (%array-fill-pointer array) (1+ fill-pointer))
707            fill-pointer))))
708
709 (defun vector-push-extend (new-element
710                            vector
711                            &optional
712                            (extension (1+ (length vector))))
713   (declare (vector vector) (fixnum extension))
714   (let ((fill-pointer (fill-pointer vector)))
715     (declare (fixnum fill-pointer))
716     (when (= fill-pointer (%array-available-elements vector))
717       (adjust-array vector (+ fill-pointer extension)))
718     (setf (aref vector fill-pointer) new-element)
719     (setf (%array-fill-pointer vector) (1+ fill-pointer))
720     fill-pointer))
721
722 (defun vector-pop (array)
723   #!+sb-doc
724   "Decrease the fill pointer by 1 and return the element pointed to by the
725   new fill pointer."
726   (declare (vector array))
727   (let ((fill-pointer (fill-pointer array)))
728     (declare (fixnum fill-pointer))
729     (if (zerop fill-pointer)
730         (error "There is nothing left to pop.")
731         (aref array
732               (setf (%array-fill-pointer array)
733                     (1- fill-pointer))))))
734 \f
735 ;;;; ADJUST-ARRAY
736
737 (defun adjust-array (array dimensions &key
738                            (element-type (array-element-type array))
739                            (initial-element nil initial-element-p)
740                            initial-contents fill-pointer
741                            displaced-to displaced-index-offset)
742   #!+sb-doc
743   "Adjust ARRAY's dimensions to the given DIMENSIONS and stuff."
744   (let ((dimensions (if (listp dimensions) dimensions (list dimensions))))
745     (cond ((/= (the fixnum (length (the list dimensions)))
746                (the fixnum (array-rank array)))
747            (error "The number of dimensions not equal to rank of array."))
748           ((not (subtypep element-type (array-element-type array)))
749            (error "The new element type, ~S, is incompatible with old type."
750                   element-type)))
751     (let ((array-rank (length (the list dimensions))))
752       (declare (fixnum array-rank))
753       (when (and fill-pointer (> array-rank 1))
754         (error "Multidimensional arrays can't have fill pointers."))
755       (cond (initial-contents
756              ;; array former contents replaced by INITIAL-CONTENTS
757              (if (or initial-element-p displaced-to)
758                  (error "INITIAL-CONTENTS may not be specified with ~
759                  the :INITIAL-ELEMENT or :DISPLACED-TO option."))
760              (let* ((array-size (apply #'* dimensions))
761                     (array-data (data-vector-from-inits
762                                  dimensions array-size element-type
763                                  initial-contents initial-element
764                                  initial-element-p)))
765                (if (adjustable-array-p array)
766                    (set-array-header array array-data array-size
767                                  (get-new-fill-pointer array array-size
768                                                        fill-pointer)
769                                  0 dimensions nil)
770                    (if (array-header-p array)
771                        ;; simple multidimensional or single dimensional array
772                        (make-array dimensions
773                                    :element-type element-type
774                                    :initial-contents initial-contents)
775                        array-data))))
776             (displaced-to
777              ;; We already established that no INITIAL-CONTENTS was supplied.
778              (when initial-element
779                (error "The :INITIAL-ELEMENT option may not be specified ~
780                       with :DISPLACED-TO."))
781              (unless (subtypep element-type (array-element-type displaced-to))
782                (error "can't displace an array of type ~S into another of ~
783                        type ~S"
784                       element-type (array-element-type displaced-to)))
785              (let ((displacement (or displaced-index-offset 0))
786                    (array-size (apply #'* dimensions)))
787                (declare (fixnum displacement array-size))
788                (if (< (the fixnum (array-total-size displaced-to))
789                       (the fixnum (+ displacement array-size)))
790                    (error "The :DISPLACED-TO array is too small."))
791                (if (adjustable-array-p array)
792                    ;; None of the original contents appear in adjusted array.
793                    (set-array-header array displaced-to array-size
794                                      (get-new-fill-pointer array array-size
795                                                            fill-pointer)
796                                      displacement dimensions t)
797                    ;; simple multidimensional or single dimensional array
798                    (make-array dimensions
799                                :element-type element-type
800                                :displaced-to displaced-to
801                                :displaced-index-offset
802                                displaced-index-offset))))
803             ((= array-rank 1)
804              (let ((old-length (array-total-size array))
805                    (new-length (car dimensions))
806                    new-data)
807                (declare (fixnum old-length new-length))
808                (with-array-data ((old-data array) (old-start)
809                                  (old-end old-length))
810                  (cond ((or (%array-displaced-p array)
811                             (< old-length new-length))
812                         (setf new-data
813                               (data-vector-from-inits
814                                dimensions new-length element-type
815                                initial-contents initial-element
816                                initial-element-p))
817                         (replace new-data old-data
818                                  :start2 old-start :end2 old-end))
819                        (t (setf new-data
820                                 (shrink-vector old-data new-length))))
821                  (if (adjustable-array-p array)
822                      (set-array-header array new-data new-length
823                                        (get-new-fill-pointer array new-length
824                                                              fill-pointer)
825                                        0 dimensions nil)
826                      new-data))))
827             (t
828              (let ((old-length (%array-available-elements array))
829                    (new-length (apply #'* dimensions)))
830                (declare (fixnum old-length new-length))
831                (with-array-data ((old-data array) (old-start)
832                                  (old-end old-length))
833                  (declare (ignore old-end))
834                  (let ((new-data (if (or (%array-displaced-p array)
835                                          (> new-length old-length))
836                                      (data-vector-from-inits
837                                       dimensions new-length
838                                       element-type () initial-element
839                                       initial-element-p)
840                                      old-data)))
841                    (if (or (zerop old-length) (zerop new-length))
842                        (when initial-element-p (fill new-data initial-element))
843                        (zap-array-data old-data (array-dimensions array)
844                                        old-start
845                                        new-data dimensions new-length
846                                        element-type initial-element
847                                        initial-element-p))
848                    (set-array-header array new-data new-length
849                                      new-length 0 dimensions nil)))))))))
850
851 (defun get-new-fill-pointer (old-array new-array-size fill-pointer)
852   (cond ((not fill-pointer)
853          (when (array-has-fill-pointer-p old-array)
854            (when (> (%array-fill-pointer old-array) new-array-size)
855              (error "cannot ADJUST-ARRAY an array (~S) to a size (~S) that is ~
856                     smaller than its fill pointer (~S)"
857                     old-array new-array-size (fill-pointer old-array)))
858            (%array-fill-pointer old-array)))
859         ((not (array-has-fill-pointer-p old-array))
860          (error "cannot supply a non-NIL value (~S) for :FILL-POINTER ~
861                 in ADJUST-ARRAY unless the array (~S) was originally ~
862                 created with a fill pointer"
863                 fill-pointer
864                 old-array))
865         ((numberp fill-pointer)
866          (when (> fill-pointer new-array-size)
867            (error "can't supply a value for :FILL-POINTER (~S) that is larger ~
868                   than the new length of the vector (~S)"
869                   fill-pointer new-array-size))
870          fill-pointer)
871         ((eq fill-pointer t)
872          new-array-size)
873         (t
874          (error "bogus value for :FILL-POINTER in ADJUST-ARRAY: ~S"
875                 fill-pointer))))
876
877 ;;; Destructively alter VECTOR, changing its length to NEW-LENGTH,
878 ;;; which must be less than or equal to its current length.
879 (defun shrink-vector (vector new-length)
880   (declare (vector vector))
881   (unless (array-header-p vector)
882     (macrolet ((frob (name &rest things)
883                  `(etypecase ,name
884                     ((simple-array nil (*)) (error 'nil-array-accessed-error))
885                     ,@(mapcar (lambda (thing)
886                                 (destructuring-bind (type-spec fill-value)
887                                     thing
888                                   `(,type-spec
889                                     (fill (truly-the ,type-spec ,name)
890                                           ,fill-value
891                                           :start new-length))))
892                               things))))
893       ;; FIXME: The associations between vector types and initial
894       ;; values here are redundant with
895       ;; *SPECIALIZED-ARRAY-ELEMENT-TYPE-PROPERTIES*.
896       (frob vector
897         (simple-vector 0)
898         (simple-base-string #.*default-init-char-form*)
899         (simple-bit-vector 0)
900         ((simple-array (unsigned-byte 2) (*)) 0)
901         ((simple-array (unsigned-byte 4) (*)) 0)
902         ((simple-array (unsigned-byte 8) (*)) 0)
903         ((simple-array (unsigned-byte 16) (*)) 0)
904         ((simple-array (unsigned-byte 32) (*)) 0)
905         ((simple-array (signed-byte 8) (*)) 0)
906         ((simple-array (signed-byte 16) (*)) 0)
907         ((simple-array (signed-byte 30) (*)) 0)
908         ((simple-array (signed-byte 32) (*)) 0)
909         ((simple-array single-float (*)) (coerce 0 'single-float))
910         ((simple-array double-float (*)) (coerce 0 'double-float))
911         #!+long-float
912         ((simple-array long-float (*)) (coerce 0 'long-float))
913         ((simple-array (complex single-float) (*))
914          (coerce 0 '(complex single-float)))
915         ((simple-array (complex double-float) (*))
916          (coerce 0 '(complex double-float)))
917         #!+long-float
918         ((simple-array (complex long-float) (*))
919          (coerce 0 '(complex long-float))))))
920   ;; Only arrays have fill-pointers, but vectors have their length
921   ;; parameter in the same place.
922   (setf (%array-fill-pointer vector) new-length)
923   vector)
924
925 ;;; Fill in array header with the provided information, and return the array.
926 (defun set-array-header (array data length fill-pointer displacement dimensions
927                          &optional displacedp)
928   (setf (%array-data-vector array) data)
929   (setf (%array-available-elements array) length)
930   (cond (fill-pointer
931          (setf (%array-fill-pointer array) fill-pointer)
932          (setf (%array-fill-pointer-p array) t))
933         (t
934          (setf (%array-fill-pointer array) length)
935          (setf (%array-fill-pointer-p array) nil)))
936   (setf (%array-displacement array) displacement)
937   (if (listp dimensions)
938       (dotimes (axis (array-rank array))
939         (declare (type index axis))
940         (setf (%array-dimension array axis) (pop dimensions)))
941       (setf (%array-dimension array 0) dimensions))
942   (setf (%array-displaced-p array) displacedp)
943   array)
944 \f
945 ;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY
946
947 ;;; a temporary to be used when OLD-DATA and NEW-DATA are EQ.
948 ;;; KLUDGE: Boy, DYNAMIC-EXTENT would be nice.
949 (defvar *zap-array-data-temp* (make-array 1000 :initial-element t))
950
951 (defun zap-array-data-temp (length element-type initial-element
952                             initial-element-p)
953   (declare (fixnum length))
954   (when (> length (the fixnum (length *zap-array-data-temp*)))
955     (setf *zap-array-data-temp*
956           (make-array length :initial-element t)))
957   (when initial-element-p
958     (unless (typep initial-element element-type)
959       (error "~S can't be used to initialize an array of type ~S."
960              initial-element element-type))
961     (fill (the simple-vector *zap-array-data-temp*) initial-element
962           :end length))
963   *zap-array-data-temp*)
964
965 ;;; This does the grinding work for ADJUST-ARRAY. It zaps the data
966 ;;; from the OLD-DATA in an arrangement specified by the OLD-DIMS to
967 ;;; the NEW-DATA in an arrangement specified by the NEW-DIMS. OFFSET
968 ;;; is a displaced offset to be added to computed indices of OLD-DATA.
969 ;;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and INITIAL-ELEMENT-P
970 ;;; are used when OLD-DATA and NEW-DATA are EQ; in this case, a
971 ;;; temporary must be used and filled appropriately. When OLD-DATA and
972 ;;; NEW-DATA are not EQ, NEW-DATA has already been filled with any
973 ;;; specified initial-element.
974 (defun zap-array-data (old-data old-dims offset new-data new-dims new-length
975                        element-type initial-element initial-element-p)
976   (declare (list old-dims new-dims))
977   (setq old-dims (nreverse old-dims))
978   (setq new-dims (reverse new-dims))
979   (if (eq old-data new-data)
980       (let ((temp (zap-array-data-temp new-length element-type
981                                        initial-element initial-element-p)))
982         (zap-array-data-aux old-data old-dims offset temp new-dims)
983         (dotimes (i new-length) (setf (aref new-data i) (aref temp i))))
984       (zap-array-data-aux old-data old-dims offset new-data new-dims)))
985
986 (defun zap-array-data-aux (old-data old-dims offset new-data new-dims)
987   (declare (fixnum offset))
988   (let ((limits (mapcar (lambda (x y)
989                           (declare (fixnum x y))
990                           (1- (the fixnum (min x y))))
991                         old-dims new-dims)))
992     (macrolet ((bump-index-list (index limits)
993                  `(do ((subscripts ,index (cdr subscripts))
994                        (limits ,limits (cdr limits)))
995                       ((null subscripts) nil)
996                     (cond ((< (the fixnum (car subscripts))
997                               (the fixnum (car limits)))
998                            (rplaca subscripts
999                                    (1+ (the fixnum (car subscripts))))
1000                            (return ,index))
1001                           (t (rplaca subscripts 0))))))
1002       (do ((index (make-list (length old-dims) :initial-element 0)
1003                   (bump-index-list index limits)))
1004           ((null index))
1005         (setf (aref new-data (row-major-index-from-dims index new-dims))
1006               (aref old-data
1007                     (+ (the fixnum (row-major-index-from-dims index old-dims))
1008                        offset)))))))
1009
1010 ;;; Figure out the row-major-order index of an array reference from a
1011 ;;; list of subscripts and a list of dimensions. This is for internal
1012 ;;; calls only, and the subscripts and dim-list variables are assumed
1013 ;;; to be reversed from what the user supplied.
1014 (defun row-major-index-from-dims (rev-subscripts rev-dim-list)
1015   (do ((rev-subscripts rev-subscripts (cdr rev-subscripts))
1016        (rev-dim-list rev-dim-list (cdr rev-dim-list))
1017        (chunk-size 1)
1018        (result 0))
1019       ((null rev-dim-list) result)
1020     (declare (fixnum chunk-size result))
1021     (setq result (+ result
1022                     (the fixnum (* (the fixnum (car rev-subscripts))
1023                                    chunk-size))))
1024     (setq chunk-size (* chunk-size (the fixnum (car rev-dim-list))))))
1025 \f
1026 ;;;; some bit stuff
1027
1028 (defun bit-array-same-dimensions-p (array1 array2)
1029   (declare (type (array bit) array1 array2))
1030   (and (= (array-rank array1)
1031           (array-rank array2))
1032        (dotimes (index (array-rank array1) t)
1033          (when (/= (array-dimension array1 index)
1034                    (array-dimension array2 index))
1035            (return nil)))))
1036
1037 (defun pick-result-array (result-bit-array bit-array-1)
1038   (case result-bit-array
1039     ((t) bit-array-1)
1040     ((nil) (make-array (array-dimensions bit-array-1)
1041                        :element-type 'bit
1042                        :initial-element 0))
1043     (t
1044      (unless (bit-array-same-dimensions-p bit-array-1
1045                                           result-bit-array)
1046        (error "~S and ~S don't have the same dimensions."
1047               bit-array-1 result-bit-array))
1048      result-bit-array)))
1049
1050 (defmacro def-bit-array-op (name function)
1051   `(defun ,name (bit-array-1 bit-array-2 &optional result-bit-array)
1052      ,(format nil
1053               "Perform a bit-wise ~A on the elements of BIT-ARRAY-1 and ~
1054               BIT-ARRAY-2,~%  putting the results in RESULT-BIT-ARRAY. ~
1055               If RESULT-BIT-ARRAY is T,~%  BIT-ARRAY-1 is used. If ~
1056               RESULT-BIT-ARRAY is NIL or omitted, a new array is~%  created. ~
1057               All the arrays must have the same rank and dimensions."
1058               (symbol-name function))
1059      (declare (type (array bit) bit-array-1 bit-array-2)
1060               (type (or (array bit) (member t nil)) result-bit-array))
1061      (unless (bit-array-same-dimensions-p bit-array-1 bit-array-2)
1062        (error "~S and ~S don't have the same dimensions."
1063               bit-array-1 bit-array-2))
1064      (let ((result-bit-array (pick-result-array result-bit-array bit-array-1)))
1065        (if (and (simple-bit-vector-p bit-array-1)
1066                 (simple-bit-vector-p bit-array-2)
1067                 (simple-bit-vector-p result-bit-array))
1068            (locally (declare (optimize (speed 3) (safety 0)))
1069              (,name bit-array-1 bit-array-2 result-bit-array))
1070            (with-array-data ((data1 bit-array-1) (start1) (end1))
1071              (declare (ignore end1))
1072              (with-array-data ((data2 bit-array-2) (start2) (end2))
1073                (declare (ignore end2))
1074                (with-array-data ((data3 result-bit-array) (start3) (end3))
1075                  (do ((index-1 start1 (1+ index-1))
1076                       (index-2 start2 (1+ index-2))
1077                       (index-3 start3 (1+ index-3)))
1078                      ((>= index-3 end3) result-bit-array)
1079                    (declare (type index index-1 index-2 index-3))
1080                    (setf (sbit data3 index-3)
1081                          (logand (,function (sbit data1 index-1)
1082                                             (sbit data2 index-2))
1083                                  1))))))))))
1084
1085 (def-bit-array-op bit-and logand)
1086 (def-bit-array-op bit-ior logior)
1087 (def-bit-array-op bit-xor logxor)
1088 (def-bit-array-op bit-eqv logeqv)
1089 (def-bit-array-op bit-nand lognand)
1090 (def-bit-array-op bit-nor lognor)
1091 (def-bit-array-op bit-andc1 logandc1)
1092 (def-bit-array-op bit-andc2 logandc2)
1093 (def-bit-array-op bit-orc1 logorc1)
1094 (def-bit-array-op bit-orc2 logorc2)
1095
1096 (defun bit-not (bit-array &optional result-bit-array)
1097   #!+sb-doc
1098   "Performs a bit-wise logical NOT on the elements of BIT-ARRAY,
1099   putting the results in RESULT-BIT-ARRAY. If RESULT-BIT-ARRAY is T,
1100   BIT-ARRAY is used. If RESULT-BIT-ARRAY is NIL or omitted, a new array is
1101   created. Both arrays must have the same rank and dimensions."
1102   (declare (type (array bit) bit-array)
1103            (type (or (array bit) (member t nil)) result-bit-array))
1104   (let ((result-bit-array (pick-result-array result-bit-array bit-array)))
1105     (if (and (simple-bit-vector-p bit-array)
1106              (simple-bit-vector-p result-bit-array))
1107         (locally (declare (optimize (speed 3) (safety 0)))
1108           (bit-not bit-array result-bit-array))
1109         (with-array-data ((src bit-array) (src-start) (src-end))
1110           (declare (ignore src-end))
1111           (with-array-data ((dst result-bit-array) (dst-start) (dst-end))
1112             (do ((src-index src-start (1+ src-index))
1113                  (dst-index dst-start (1+ dst-index)))
1114                 ((>= dst-index dst-end) result-bit-array)
1115               (declare (type index src-index dst-index))
1116               (setf (sbit dst dst-index)
1117                     (logxor (sbit src src-index) 1))))))))