1 ;;;; functions to implement arrays
3 ;;;; This software is part of the SBCL system. See the README file for
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.
12 (in-package "SB!IMPL")
15 (declaim (inline adjustable-array-p
18 ;;;; miscellaneous accessor functions
20 ;;; These functions are only needed by the interpreter, 'cause the
21 ;;; compiler inlines them.
22 (macrolet ((def (name)
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 (def %array-diplaced-from))
36 (defun %array-rank (array)
39 (defun %array-dimension (array axis)
40 (%array-dimension array axis))
42 (defun %set-array-dimension (array axis value)
43 (%set-array-dimension array axis value))
45 (defun %check-bound (array bound index)
46 (declare (type index bound)
48 (%check-bound array bound index))
50 (defun %with-array-data/fp (array start end)
51 (%with-array-data-macro array start end :check-bounds t :check-fill-pointer t))
53 (defun %with-array-data (array start end)
54 (%with-array-data-macro array start end :check-bounds t :check-fill-pointer nil))
56 (defun %data-vector-and-index (array index)
57 (if (array-header-p array)
58 (multiple-value-bind (vector index)
59 (%with-array-data array index nil)
60 (values vector index))
61 (values array index)))
64 (eval-when (:compile-toplevel :execute)
65 (sb!xc:defmacro pick-vector-type (type &rest specs)
66 `(cond ,@(mapcar (lambda (spec)
67 `(,(if (eq (car spec) t)
69 `(subtypep ,type ',(car spec)))
73 ;;; These functions are used in the implementation of MAKE-ARRAY for
74 ;;; complex arrays. There are lots of transforms to simplify
75 ;;; MAKE-ARRAY for various easy cases, but not for all reasonable
76 ;;; cases, so e.g. as of sbcl-0.6.6 we still make full calls to
77 ;;; MAKE-ARRAY for any non-simple array. Thus, there's some value to
78 ;;; making this somewhat efficient, at least not doing full calls to
79 ;;; SUBTYPEP in the easy cases.
80 (defun %vector-widetag-and-n-bits (type)
82 ;; Pick off some easy common cases.
84 ;; (Perhaps we should make a much more exhaustive table of easy
85 ;; common cases here. Or perhaps the effort would be better spent
86 ;; on smarter compiler transforms which do the calculation once
87 ;; and for all in any reasonable user programs.)
89 (values #.sb!vm:simple-vector-widetag #.sb!vm:n-word-bits))
90 ((base-char standard-char #!-sb-unicode character)
91 (values #.sb!vm:simple-base-string-widetag #.sb!vm:n-byte-bits))
94 (values #.sb!vm:simple-character-string-widetag #.sb!vm:n-word-bits))
96 (values #.sb!vm:simple-bit-vector-widetag 1))
97 ;; OK, we have to wade into SUBTYPEPing after all.
99 (unless *type-system-initialized*
100 (bug "SUBTYPEP dispatch for MAKE-ARRAY before the type system is ready"))
101 #.`(pick-vector-type type
104 `(,(sb!vm:saetp-specifier saetp)
105 (values ,(sb!vm:saetp-typecode saetp)
106 ,(sb!vm:saetp-n-bits saetp))))
107 sb!vm:*specialized-array-element-type-properties*)))))
109 (defun %complex-vector-widetag (type)
111 ;; Pick off some easy common cases.
113 #.sb!vm:complex-vector-widetag)
114 ((base-char #!-sb-unicode character)
115 #.sb!vm:complex-base-string-widetag)
118 #.sb!vm:complex-character-string-widetag)
120 #.sb!vm:complex-vector-nil-widetag)
122 #.sb!vm:complex-bit-vector-widetag)
123 ;; OK, we have to wade into SUBTYPEPing after all.
125 (pick-vector-type type
126 (nil #.sb!vm:complex-vector-nil-widetag)
128 (character #.sb!vm:complex-base-string-widetag)
130 (base-char #.sb!vm:complex-base-string-widetag)
132 (character #.sb!vm:complex-character-string-widetag)
133 (bit #.sb!vm:complex-bit-vector-widetag)
134 (t #.sb!vm:complex-vector-widetag)))))
136 (defun make-array (dimensions &key
138 (initial-element nil initial-element-p)
139 (initial-contents nil initial-contents-p)
140 adjustable fill-pointer
141 displaced-to displaced-index-offset)
142 (let* ((dimensions (if (listp dimensions) dimensions (list dimensions)))
143 (array-rank (length (the list dimensions)))
144 (simple (and (null fill-pointer)
146 (null displaced-to))))
147 (declare (fixnum array-rank))
148 (when (and displaced-index-offset (null displaced-to))
149 (error "can't specify :DISPLACED-INDEX-OFFSET without :DISPLACED-TO"))
150 (when (and displaced-to
151 (arrayp displaced-to)
152 (not (equal (array-element-type displaced-to)
153 (upgraded-array-element-type element-type))))
154 (error "Array element type of :DISPLACED-TO array does not match specified element type"))
155 (if (and simple (= array-rank 1))
156 ;; it's a (SIMPLE-ARRAY * (*))
157 (multiple-value-bind (type n-bits)
158 (%vector-widetag-and-n-bits element-type)
159 (declare (type (unsigned-byte 8) type)
160 (type (integer 0 256) n-bits))
161 (let* ((length (car dimensions))
162 (array (allocate-vector
166 (* (if (or (= type sb!vm:simple-base-string-widetag)
169 sb!vm:simple-character-string-widetag))
173 sb!vm:n-word-bits))))
174 (declare (type index length))
175 (when initial-element-p
176 (fill array initial-element))
177 (when initial-contents-p
178 (when initial-element-p
179 (error "can't specify both :INITIAL-ELEMENT and ~
181 (unless (= length (length initial-contents))
182 (error "There are ~W elements in the :INITIAL-CONTENTS, but ~
183 the vector length is ~W."
184 (length initial-contents)
186 (replace array initial-contents))
188 ;; it's either a complex array or a multidimensional array.
189 (let* ((total-size (reduce #'* dimensions))
190 (data (or displaced-to
191 (data-vector-from-inits
192 dimensions total-size element-type
193 initial-contents initial-contents-p
194 initial-element initial-element-p)))
195 (array (make-array-header
196 (cond ((= array-rank 1)
197 (%complex-vector-widetag element-type))
198 (simple sb!vm:simple-array-widetag)
199 (t sb!vm:complex-array-widetag))
202 (unless (= array-rank 1)
203 (error "Only vectors can have fill pointers."))
204 (let ((length (car dimensions)))
205 (declare (fixnum length))
206 (setf (%array-fill-pointer array)
207 (cond ((eq fill-pointer t)
210 (unless (and (fixnump fill-pointer)
212 (<= fill-pointer length))
213 ;; FIXME: should be TYPE-ERROR?
214 (error "invalid fill-pointer ~W"
217 (setf (%array-fill-pointer-p array) t))
219 (setf (%array-fill-pointer array) total-size)
220 (setf (%array-fill-pointer-p array) nil)))
221 (setf (%array-available-elements array) total-size)
222 (setf (%array-data-vector array) data)
223 (setf (%array-displaced-from array) nil)
225 (when (or initial-element-p initial-contents-p)
226 (error "Neither :INITIAL-ELEMENT nor :INITIAL-CONTENTS ~
227 can be specified along with :DISPLACED-TO"))
228 (let ((offset (or displaced-index-offset 0)))
229 (when (> (+ offset total-size)
230 (array-total-size displaced-to))
231 (error "~S doesn't have enough elements." displaced-to))
232 (setf (%array-displacement array) offset)
233 (setf (%array-displaced-p array) t)
234 (%save-displaced-array-backpointer array data)))
236 (setf (%array-displaced-p array) nil)))
238 (dolist (dim dimensions)
239 (setf (%array-dimension array axis) dim)
243 (defun make-static-vector (length &key
244 (element-type '(unsigned-byte 8))
245 (initial-contents nil initial-contents-p)
246 (initial-element nil initial-element-p))
247 "Allocate vector of LENGTH elements in static space. Only allocation
248 of specialized arrays is supported."
249 ;; STEP 1: check inputs fully
251 ;; This way of doing explicit checks before the vector is allocated
252 ;; is expensive, but probably worth the trouble as once we've allocated
253 ;; the vector we have no way to get rid of it anymore...
254 (when (eq t (upgraded-array-element-type element-type))
255 (error "Static arrays of type ~S not supported."
257 (when initial-contents-p
258 (when initial-element-p
259 (error "can't specify both :INITIAL-ELEMENT and :INITIAL-CONTENTS"))
260 (unless (= length (length initial-contents))
261 (error "There are ~W elements in the :INITIAL-CONTENTS, but the ~
262 vector length is ~W."
263 (length initial-contents)
265 (unless (every (lambda (x) (typep x element-type)) initial-contents)
266 (error ":INITIAL-CONTENTS contains elements not of type ~S."
268 (when initial-element-p
269 (unless (typep initial-element element-type)
270 (error ":INITIAL-ELEMENT ~S is not of type ~S."
271 initial-element element-type)))
274 ;; Allocate and possibly initialize the vector.
275 (multiple-value-bind (type n-bits)
276 (sb!impl::%vector-widetag-and-n-bits element-type)
278 (allocate-static-vector type length
279 (ceiling (* length n-bits)
280 sb!vm:n-word-bits))))
281 (cond (initial-element-p
282 (fill vector initial-element))
284 (replace vector initial-contents))
288 ;;; DATA-VECTOR-FROM-INITS returns a simple vector that has the
289 ;;; specified array characteristics. Dimensions is only used to pass
290 ;;; to FILL-DATA-VECTOR for error checking on the structure of
291 ;;; initial-contents.
292 (defun data-vector-from-inits (dimensions total-size element-type
293 initial-contents initial-contents-p
294 initial-element initial-element-p)
295 (when (and initial-contents-p initial-element-p)
296 (error "cannot supply both :INITIAL-CONTENTS and :INITIAL-ELEMENT to
297 either MAKE-ARRAY or ADJUST-ARRAY."))
298 (let ((data (if initial-element-p
299 (make-array total-size
300 :element-type element-type
301 :initial-element initial-element)
302 (make-array total-size
303 :element-type element-type))))
304 (cond (initial-element-p
305 (unless (simple-vector-p data)
306 (unless (typep initial-element element-type)
307 (error "~S cannot be used to initialize an array of type ~S."
308 initial-element element-type))
309 (fill (the vector data) initial-element)))
311 (fill-data-vector data dimensions initial-contents)))
314 (defun vector (&rest objects)
316 "Construct a SIMPLE-VECTOR from the given objects."
317 (coerce (the list objects) 'simple-vector))
320 ;;;; accessor/setter functions
322 ;;; Dispatch to an optimized routine the data vector accessors for
323 ;;; each different specialized vector type. Do dispatching by looking
324 ;;; up the widetag in the array rather than with the typecases, which
325 ;;; as of 1.0.5 compiles to a naive sequence of linear TYPEPs. Also
326 ;;; provide separate versions where bounds checking has been moved
327 ;;; from the callee to the caller, since it's much cheaper to do once
328 ;;; the type information is available. Finally, for each of these
329 ;;; routines also provide a slow path, taken for arrays that are not
330 ;;; vectors or not simple.
331 (macrolet ((def (name table-name)
333 (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)))
334 (defmacro ,name (array-var)
337 (when (sb!vm::%other-pointer-p ,array-var)
338 (setf tag (%other-pointer-widetag ,array-var)))
339 (svref ,',table-name tag)))))))
340 (def !find-data-vector-setter %%data-vector-setters%%)
341 (def !find-data-vector-setter/check-bounds %%data-vector-setters/check-bounds%%)
342 (def !find-data-vector-reffer %%data-vector-reffers%%)
343 (def !find-data-vector-reffer/check-bounds %%data-vector-reffers/check-bounds%%))
345 (macrolet ((%ref (accessor-getter extra-params)
346 `(funcall (,accessor-getter array) array index ,@extra-params))
347 (define (accessor-name slow-accessor-name accessor-getter
348 extra-params check-bounds)
350 (defun ,accessor-name (array index ,@extra-params)
351 (declare (optimize speed
352 ;; (SAFETY 0) is ok. All calls to
353 ;; these functions are generated by
354 ;; the compiler, so argument count
355 ;; checking isn't needed. Type checking
356 ;; is done implicitly via the widetag
359 (%ref ,accessor-getter ,extra-params))
360 (defun ,slow-accessor-name (array index ,@extra-params)
361 (declare (optimize speed (safety 0)))
362 (if (not (%array-displaced-p array))
363 ;; The reasonably quick path of non-displaced complex
365 (let ((array (%array-data-vector array)))
366 (%ref ,accessor-getter ,extra-params))
367 ;; The real slow path.
371 (declare (optimize (speed 1) (safety 1)))
372 (,@check-bounds index)))
375 (declare (ignore end))
376 (,accessor-name vector index ,@extra-params)))))))
377 (define hairy-data-vector-ref slow-hairy-data-vector-ref
378 !find-data-vector-reffer
380 (define hairy-data-vector-set slow-hairy-data-vector-set
381 !find-data-vector-setter
383 (define hairy-data-vector-ref/check-bounds
384 slow-hairy-data-vector-ref/check-bounds
385 !find-data-vector-reffer/check-bounds
386 nil (%check-bound array (array-dimension array 0)))
387 (define hairy-data-vector-set/check-bounds
388 slow-hairy-data-vector-set/check-bounds
389 !find-data-vector-setter/check-bounds
390 (new-value) (%check-bound array (array-dimension array 0))))
392 (defun hairy-ref-error (array index &optional new-value)
393 (declare (ignore index new-value))
396 :expected-type 'vector))
398 ;;; Populate the dispatch tables.
399 (macrolet ((define-reffer (saetp check-form)
400 (let* ((type (sb!vm:saetp-specifier saetp))
401 (atype `(simple-array ,type (*))))
402 `(named-lambda optimized-data-vector-ref (vector index)
403 (declare (optimize speed (safety 0)))
404 (data-vector-ref (the ,atype vector)
406 (declare (optimize (safety 1)))
408 (,@check-form index)))))))
409 (define-setter (saetp check-form)
410 (let* ((type (sb!vm:saetp-specifier saetp))
411 (atype `(simple-array ,type (*))))
412 `(named-lambda optimized-data-vector-set (vector index new-value)
413 (declare (optimize speed (safety 0)))
414 (data-vector-set (the ,atype vector)
416 (declare (optimize (safety 1)))
418 (,@check-form index)))
420 ;; SPEED 1 needed to avoid the compiler
421 ;; from downgrading the type check to
423 (declare (optimize (speed 1)
425 (the ,type new-value)))
426 ;; For specialized arrays, the return from
427 ;; data-vector-set would have to be reboxed to be a
428 ;; (Lisp) return value; instead, we use the
429 ;; already-boxed value as the return.
431 (define-reffers (symbol deffer check-form slow-path)
433 ;; FIXME/KLUDGE: can't just FILL here, because genesis doesn't
434 ;; preserve the binding, so re-initiaize as NS doesn't have
435 ;; the energy to figure out to change that right now.
436 (setf ,symbol (make-array (1+ sb!vm::widetag-mask)
437 :initial-element #'hairy-ref-error))
438 ,@(loop for widetag in '(sb!vm:complex-vector-widetag
439 sb!vm:complex-vector-nil-widetag
440 sb!vm:complex-bit-vector-widetag
441 #!+sb-unicode sb!vm:complex-character-string-widetag
442 sb!vm:complex-base-string-widetag
443 sb!vm:simple-array-widetag
444 sb!vm:complex-array-widetag)
445 collect `(setf (svref ,symbol ,widetag) ,slow-path))
446 ,@(loop for saetp across sb!vm:*specialized-array-element-type-properties*
447 for widetag = (sb!vm:saetp-typecode saetp)
448 collect `(setf (svref ,symbol ,widetag)
449 (,deffer ,saetp ,check-form))))))
450 (defun !hairy-data-vector-reffer-init ()
451 (define-reffers %%data-vector-reffers%% define-reffer
453 #'slow-hairy-data-vector-ref)
454 (define-reffers %%data-vector-setters%% define-setter
456 #'slow-hairy-data-vector-set)
457 (define-reffers %%data-vector-reffers/check-bounds%% define-reffer
458 (%check-bound vector (length vector))
459 #'slow-hairy-data-vector-ref/check-bounds)
460 (define-reffers %%data-vector-setters/check-bounds%% define-setter
461 (%check-bound vector (length vector))
462 #'slow-hairy-data-vector-set/check-bounds)))
464 ;;; (Ordinary DATA-VECTOR-REF usage compiles into a vop, but
465 ;;; DATA-VECTOR-REF is also FOLDABLE, and this ordinary function
466 ;;; definition is needed for the compiler to use in constant folding.)
467 (defun data-vector-ref (array index)
468 (hairy-data-vector-ref array index))
470 (defun data-vector-ref-with-offset (array index offset)
471 (hairy-data-vector-ref array (+ index offset)))
473 (defun invalid-array-p (array)
474 (and (array-header-p array)
475 (consp (%array-displaced-p array))))
477 (declaim (ftype (function (array) nil) invalid-array-error))
478 (defun invalid-array-error (array)
479 (aver (array-header-p array))
480 ;; Array invalidation stashes the original dimensions here...
481 (let ((dims (%array-displaced-p array))
482 (et (array-element-type array)))
483 (error 'invalid-array-error
488 `(vector ,et ,@dims)))))
490 (declaim (ftype (function (array integer integer &optional t) nil)
491 invalid-array-index-error))
492 (defun invalid-array-index-error (array index bound &optional axis)
493 (if (invalid-array-p array)
494 (invalid-array-error array)
495 (error 'invalid-array-index-error
499 :expected-type `(integer 0 (,bound)))))
501 ;;; SUBSCRIPTS has a dynamic-extent list structure and is destroyed
502 (defun %array-row-major-index (array subscripts
503 &optional (invalid-index-error-p t))
504 (declare (array array)
506 (let ((rank (array-rank array)))
507 (unless (= rank (length subscripts))
508 (error "wrong number of subscripts, ~W, for array of rank ~W"
509 (length subscripts) rank))
510 (if (array-header-p array)
511 (do ((subs (nreverse subscripts) (cdr subs))
512 (axis (1- (array-rank array)) (1- axis))
516 (declare (list subs) (fixnum axis chunk-size result))
517 (let ((index (car subs))
518 (dim (%array-dimension array axis)))
519 (declare (fixnum dim))
520 (unless (and (fixnump index) (< -1 index dim))
521 (if invalid-index-error-p
522 (invalid-array-index-error array index dim axis)
523 (return-from %array-row-major-index nil)))
524 (incf result (* chunk-size (the fixnum index)))
525 (setf chunk-size (* chunk-size dim))))
526 (let ((index (first subscripts))
527 (length (length (the (simple-array * (*)) array))))
528 (unless (and (fixnump index) (< -1 index length))
529 (if invalid-index-error-p
530 (invalid-array-index-error array index length)
531 (return-from %array-row-major-index nil)))
534 (defun array-in-bounds-p (array &rest subscripts)
536 "Return T if the SUBSCRIPTS are in bounds for the ARRAY, NIL otherwise."
537 (if (%array-row-major-index array subscripts nil)
540 (defun array-row-major-index (array &rest subscripts)
541 (declare (truly-dynamic-extent subscripts))
542 (%array-row-major-index array subscripts))
544 (defun aref (array &rest subscripts)
546 "Return the element of the ARRAY specified by the SUBSCRIPTS."
547 (declare (truly-dynamic-extent subscripts))
548 (row-major-aref array (%array-row-major-index array subscripts)))
550 (defun %aset (array &rest stuff)
551 (declare (truly-dynamic-extent stuff))
552 (let ((subscripts (butlast stuff))
553 (new-value (car (last stuff))))
554 (setf (row-major-aref array (%array-row-major-index array subscripts))
557 ;;; FIXME: What's supposed to happen with functions
558 ;;; like AREF when we (DEFUN (SETF FOO) ..) when
559 ;;; DEFSETF FOO is also defined? It seems as though the logical
560 ;;; thing to do would be to nuke the macro definition for (SETF FOO)
561 ;;; and replace it with the (SETF FOO) function, issuing a warning,
562 ;;; just as for ordinary functions
563 ;;; * (LISP-IMPLEMENTATION-VERSION)
564 ;;; "18a+ release x86-linux 2.4.7 6 November 1998 cvs"
565 ;;; * (DEFMACRO ZOO (X) `(+ ,X ,X))
567 ;;; * (DEFUN ZOO (X) (* 3 X))
568 ;;; Warning: ZOO previously defined as a macro.
570 ;;; But that doesn't seem to be what happens in CMU CL.
572 ;;; KLUDGE: this is probably because ANSI, in its wisdom (CLHS
573 ;;; 5.1.2.5) requires implementations to support
574 ;;; (SETF (APPLY #'AREF ...) ...)
575 ;;; [and also #'BIT and #'SBIT]. Yes, this is terrifying, and it's
576 ;;; also terrifying that this sequence of definitions causes it to
579 ;;; Also, it would be nice to make DESCRIBE FOO tell whether a symbol
580 ;;; has a setf expansion and/or a setf function defined.
582 #!-sb-fluid (declaim (inline (setf aref)))
583 (defun (setf aref) (new-value array &rest subscripts)
584 (declare (truly-dynamic-extent subscripts))
585 (declare (type array array))
586 (setf (row-major-aref array (%array-row-major-index array subscripts))
589 (defun row-major-aref (array index)
591 "Return the element of array corressponding to the row-major index. This is
593 (declare (optimize (safety 1)))
594 (row-major-aref array index))
596 (defun %set-row-major-aref (array index new-value)
597 (declare (optimize (safety 1)))
598 (setf (row-major-aref array index) new-value))
600 (defun svref (simple-vector index)
602 "Return the INDEX'th element of the given Simple-Vector."
603 (declare (optimize (safety 1)))
604 (aref simple-vector index))
606 (defun %svset (simple-vector index new)
607 (declare (optimize (safety 1)))
608 (setf (aref simple-vector index) new))
610 (defun bit (bit-array &rest subscripts)
612 "Return the bit from the BIT-ARRAY at the specified SUBSCRIPTS."
613 (declare (type (array bit) bit-array) (optimize (safety 1)))
614 (row-major-aref bit-array (%array-row-major-index bit-array subscripts)))
616 (defun %bitset (bit-array &rest stuff)
617 (declare (type (array bit) bit-array) (optimize (safety 1)))
618 (let ((subscripts (butlast stuff))
619 (new-value (car (last stuff))))
620 (setf (row-major-aref bit-array
621 (%array-row-major-index bit-array subscripts))
624 #!-sb-fluid (declaim (inline (setf bit)))
625 (defun (setf bit) (new-value bit-array &rest subscripts)
626 (declare (type (array bit) bit-array) (optimize (safety 1)))
627 (setf (row-major-aref bit-array
628 (%array-row-major-index bit-array subscripts))
631 (defun sbit (simple-bit-array &rest subscripts)
633 "Return the bit from SIMPLE-BIT-ARRAY at the specified SUBSCRIPTS."
634 (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
635 (row-major-aref simple-bit-array
636 (%array-row-major-index simple-bit-array subscripts)))
638 ;;; KLUDGE: Not all these things (%SET-ROW-MAJOR-AREF, %SET-FILL-POINTER,
639 ;;; %SET-FDEFINITION, %SCHARSET, %SBITSET..) seem to deserve separate names.
640 ;;; Could we just DEFUN (SETF SBIT) etc. and get rid of the non-ANSI names?
642 (defun %sbitset (simple-bit-array &rest stuff)
643 (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
644 (let ((subscripts (butlast stuff))
645 (new-value (car (last stuff))))
646 (setf (row-major-aref simple-bit-array
647 (%array-row-major-index simple-bit-array subscripts))
650 #!-sb-fluid (declaim (inline (setf sbit)))
651 (defun (setf sbit) (new-value bit-array &rest subscripts)
652 (declare (type (simple-array bit) bit-array) (optimize (safety 1)))
653 (setf (row-major-aref bit-array
654 (%array-row-major-index bit-array subscripts))
657 ;;;; miscellaneous array properties
659 (defun array-element-type (array)
661 "Return the type of the elements of the array"
662 (let ((widetag (widetag-of array)))
663 (macrolet ((pick-element-type (&rest stuff)
664 `(cond ,@(mapcar (lambda (stuff)
666 (let ((item (car stuff)))
675 `(= widetag ,item))))
678 #.`(pick-element-type
681 `(,(if (sb!vm:saetp-complex-typecode saetp)
682 (list (sb!vm:saetp-typecode saetp)
683 (sb!vm:saetp-complex-typecode saetp))
684 (sb!vm:saetp-typecode saetp))
685 ',(sb!vm:saetp-specifier saetp)))
686 sb!vm:*specialized-array-element-type-properties*)
687 ((sb!vm:simple-array-widetag
688 sb!vm:complex-vector-widetag
689 sb!vm:complex-array-widetag)
690 (with-array-data ((array array) (start) (end))
691 (declare (ignore start end))
692 (array-element-type array)))
694 (error 'type-error :datum array :expected-type 'array))))))
696 (defun array-rank (array)
698 "Return the number of dimensions of ARRAY."
699 (if (array-header-p array)
703 (defun array-dimension (array axis-number)
705 "Return the length of dimension AXIS-NUMBER of ARRAY."
706 (declare (array array) (type index axis-number))
707 (cond ((not (array-header-p array))
708 (unless (= axis-number 0)
709 (error "Vector axis is not zero: ~S" axis-number))
710 (length (the (simple-array * (*)) array)))
711 ((>= axis-number (%array-rank array))
712 (error "Axis number ~W is too big; ~S only has ~D dimension~:P."
713 axis-number array (%array-rank array)))
715 (%array-dimension array axis-number))))
717 (defun array-dimensions (array)
719 "Return a list whose elements are the dimensions of the array"
720 (declare (array array))
721 (if (array-header-p array)
722 (do ((results nil (cons (array-dimension array index) results))
723 (index (1- (array-rank array)) (1- index)))
724 ((minusp index) results))
725 (list (array-dimension array 0))))
727 (defun array-total-size (array)
729 "Return the total number of elements in the Array."
730 (declare (array array))
731 (if (array-header-p array)
732 (%array-available-elements array)
733 (length (the vector array))))
735 (defun array-displacement (array)
737 "Return the values of :DISPLACED-TO and :DISPLACED-INDEX-offset
738 options to MAKE-ARRAY, or NIL and 0 if not a displaced array."
739 (declare (type array array))
740 (if (and (array-header-p array) ; if unsimple and
741 (%array-displaced-p array)) ; displaced
742 (values (%array-data-vector array) (%array-displacement array))
745 (defun adjustable-array-p (array)
747 "Return T if (ADJUST-ARRAY ARRAY...) would return an array identical
748 to the argument, this happens for complex arrays."
749 (declare (array array))
750 ;; Note that this appears not to be a fundamental limitation.
751 ;; non-vector SIMPLE-ARRAYs are in fact capable of being adjusted,
752 ;; but in practice we test using ADJUSTABLE-ARRAY-P in ADJUST-ARRAY.
753 ;; -- CSR, 2004-03-01.
754 (not (typep array 'simple-array)))
756 ;;;; fill pointer frobbing stuff
758 (declaim (inline array-has-fill-pointer-p))
759 (defun array-has-fill-pointer-p (array)
761 "Return T if the given ARRAY has a fill pointer, or NIL otherwise."
762 (declare (array array))
763 (and (array-header-p array) (%array-fill-pointer-p array)))
765 (defun fill-pointer-error (vector arg)
767 (aver (array-has-fill-pointer-p vector))
768 (let ((max (%array-available-elements vector)))
769 (error 'simple-type-error
771 :expected-type (list 'integer 0 max)
772 :format-control "The new fill pointer, ~S, is larger than the length of the vector (~S.)"
773 :format-arguments (list arg max))))
775 (error 'simple-type-error
777 :expected-type '(and vector (satisfies array-has-fill-pointer-p))
778 :format-control "~S is not an array with a fill pointer."
779 :format-arguments (list vector)))))
781 (declaim (inline fill-pointer))
782 (defun fill-pointer (vector)
784 "Return the FILL-POINTER of the given VECTOR."
785 (if (array-has-fill-pointer-p vector)
786 (%array-fill-pointer vector)
787 (fill-pointer-error vector nil)))
789 (defun %set-fill-pointer (vector new)
791 (fill-pointer-error vector x)))
792 (if (array-has-fill-pointer-p vector)
793 (if (> new (%array-available-elements vector))
795 (setf (%array-fill-pointer vector) new))
798 ;;; FIXME: It'd probably make sense to use a MACROLET to share the
799 ;;; guts of VECTOR-PUSH between VECTOR-PUSH-EXTEND. Such a macro
800 ;;; should probably be based on the VECTOR-PUSH-EXTEND code (which is
801 ;;; new ca. sbcl-0.7.0) rather than the VECTOR-PUSH code (which dates
803 (defun vector-push (new-el array)
805 "Attempt to set the element of ARRAY designated by its fill pointer
806 to NEW-EL, and increment the fill pointer by one. If the fill pointer is
807 too large, NIL is returned, otherwise the index of the pushed element is
809 (let ((fill-pointer (fill-pointer array)))
810 (declare (fixnum fill-pointer))
811 (cond ((= fill-pointer (%array-available-elements array))
814 (locally (declare (optimize (safety 0)))
815 (setf (aref array fill-pointer) new-el))
816 (setf (%array-fill-pointer array) (1+ fill-pointer))
819 (defun vector-push-extend (new-element
823 (let ((length (length vector)))
825 (- array-dimension-limit length)))))
826 (declare (fixnum min-extension))
827 (let ((fill-pointer (fill-pointer vector)))
828 (declare (fixnum fill-pointer))
829 (when (= fill-pointer (%array-available-elements vector))
830 (adjust-array vector (+ fill-pointer (max 1 min-extension))))
831 ;; disable bounds checking
832 (locally (declare (optimize (safety 0)))
833 (setf (aref vector fill-pointer) new-element))
834 (setf (%array-fill-pointer vector) (1+ fill-pointer))
837 (defun vector-pop (array)
839 "Decrease the fill pointer by 1 and return the element pointed to by the
841 (let ((fill-pointer (fill-pointer array)))
842 (declare (fixnum fill-pointer))
843 (if (zerop fill-pointer)
844 (error "There is nothing left to pop.")
845 ;; disable bounds checking (and any fixnum test)
846 (locally (declare (optimize (safety 0)))
848 (setf (%array-fill-pointer array)
849 (1- fill-pointer)))))))
854 (defun adjust-array (array dimensions &key
855 (element-type (array-element-type array))
856 (initial-element nil initial-element-p)
857 (initial-contents nil initial-contents-p)
859 displaced-to displaced-index-offset)
861 "Adjust ARRAY's dimensions to the given DIMENSIONS and stuff."
862 (when (invalid-array-p array)
863 (invalid-array-error array))
864 (let ((dimensions (if (listp dimensions) dimensions (list dimensions))))
865 (cond ((/= (the fixnum (length (the list dimensions)))
866 (the fixnum (array-rank array)))
867 (error "The number of dimensions not equal to rank of array."))
868 ((not (subtypep element-type (array-element-type array)))
869 (error "The new element type, ~S, is incompatible with old type."
871 ((and fill-pointer (not (array-has-fill-pointer-p array)))
874 :expected-type '(satisfies array-has-fill-pointer-p))))
875 (let ((array-rank (length (the list dimensions))))
876 (declare (fixnum array-rank))
877 (unless (= array-rank 1)
879 (error "Only vectors can have fill pointers.")))
880 (cond (initial-contents-p
881 ;; array former contents replaced by INITIAL-CONTENTS
882 (if (or initial-element-p displaced-to)
883 (error "INITIAL-CONTENTS may not be specified with ~
884 the :INITIAL-ELEMENT or :DISPLACED-TO option."))
885 (let* ((array-size (apply #'* dimensions))
886 (array-data (data-vector-from-inits
887 dimensions array-size element-type
888 initial-contents initial-contents-p
889 initial-element initial-element-p)))
890 (if (adjustable-array-p array)
891 (set-array-header array array-data array-size
892 (get-new-fill-pointer array array-size
894 0 dimensions nil nil)
895 (if (array-header-p array)
896 ;; simple multidimensional or single dimensional array
897 (make-array dimensions
898 :element-type element-type
899 :initial-contents initial-contents)
902 ;; We already established that no INITIAL-CONTENTS was supplied.
903 (when initial-element
904 (error "The :INITIAL-ELEMENT option may not be specified ~
905 with :DISPLACED-TO."))
906 (unless (subtypep element-type (array-element-type displaced-to))
907 (error "can't displace an array of type ~S into another of ~
909 element-type (array-element-type displaced-to)))
910 (let ((displacement (or displaced-index-offset 0))
911 (array-size (apply #'* dimensions)))
912 (declare (fixnum displacement array-size))
913 (if (< (the fixnum (array-total-size displaced-to))
914 (the fixnum (+ displacement array-size)))
915 (error "The :DISPLACED-TO array is too small."))
916 (if (adjustable-array-p array)
917 ;; None of the original contents appear in adjusted array.
918 (set-array-header array displaced-to array-size
919 (get-new-fill-pointer array array-size
921 displacement dimensions t nil)
922 ;; simple multidimensional or single dimensional array
923 (make-array dimensions
924 :element-type element-type
925 :displaced-to displaced-to
926 :displaced-index-offset
927 displaced-index-offset))))
929 (let ((old-length (array-total-size array))
930 (new-length (car dimensions))
932 (declare (fixnum old-length new-length))
933 (with-array-data ((old-data array) (old-start)
934 (old-end old-length))
935 (cond ((or (and (array-header-p array)
936 (%array-displaced-p array))
937 (< old-length new-length))
939 (data-vector-from-inits
940 dimensions new-length element-type
941 initial-contents initial-contents-p
942 initial-element initial-element-p))
943 (replace new-data old-data
944 :start2 old-start :end2 old-end))
946 (shrink-vector old-data new-length))))
947 (if (adjustable-array-p array)
948 (set-array-header array new-data new-length
949 (get-new-fill-pointer array new-length
951 0 dimensions nil nil)
954 (let ((old-length (%array-available-elements array))
955 (new-length (apply #'* dimensions)))
956 (declare (fixnum old-length new-length))
957 (with-array-data ((old-data array) (old-start)
958 (old-end old-length))
959 (declare (ignore old-end))
960 (let ((new-data (if (or (and (array-header-p array)
961 (%array-displaced-p array))
962 (> new-length old-length))
963 (data-vector-from-inits
964 dimensions new-length
966 initial-element initial-element-p)
968 (if (or (zerop old-length) (zerop new-length))
969 (when initial-element-p (fill new-data initial-element))
970 (zap-array-data old-data (array-dimensions array)
972 new-data dimensions new-length
973 element-type initial-element
975 (if (adjustable-array-p array)
976 (set-array-header array new-data new-length
977 nil 0 dimensions nil nil)
980 sb!vm:simple-array-widetag array-rank)))
981 (set-array-header new-array new-data new-length
982 nil 0 dimensions nil t)))))))))))
985 (defun get-new-fill-pointer (old-array new-array-size fill-pointer)
986 (cond ((not fill-pointer)
987 (when (array-has-fill-pointer-p old-array)
988 (when (> (%array-fill-pointer old-array) new-array-size)
989 (error "cannot ADJUST-ARRAY an array (~S) to a size (~S) that is ~
990 smaller than its fill pointer (~S)"
991 old-array new-array-size (fill-pointer old-array)))
992 (%array-fill-pointer old-array)))
993 ((not (array-has-fill-pointer-p old-array))
994 (error "cannot supply a non-NIL value (~S) for :FILL-POINTER ~
995 in ADJUST-ARRAY unless the array (~S) was originally ~
996 created with a fill pointer"
999 ((numberp fill-pointer)
1000 (when (> fill-pointer new-array-size)
1001 (error "can't supply a value for :FILL-POINTER (~S) that is larger ~
1002 than the new length of the vector (~S)"
1003 fill-pointer new-array-size))
1005 ((eq fill-pointer t)
1008 (error "bogus value for :FILL-POINTER in ADJUST-ARRAY: ~S"
1011 ;;; Destructively alter VECTOR, changing its length to NEW-LENGTH,
1012 ;;; which must be less than or equal to its current length. This can
1013 ;;; be called on vectors without a fill pointer but it is extremely
1014 ;;; dangerous to do so: shrinking the size of an object (as viewed by
1015 ;;; the gc) makes bounds checking unreliable in the face of interrupts
1016 ;;; or multi-threading. Call it only on provably local vectors.
1017 (defun %shrink-vector (vector new-length)
1018 (declare (vector vector))
1019 (unless (array-header-p vector)
1020 (macrolet ((frob (name &rest things)
1022 ((simple-array nil (*)) (error 'nil-array-accessed-error))
1023 ,@(mapcar (lambda (thing)
1024 (destructuring-bind (type-spec fill-value)
1027 (fill (truly-the ,type-spec ,name)
1029 :start new-length))))
1031 ;; Set the 'tail' of the vector to the appropriate type of zero,
1032 ;; "because in some cases we'll scavenge larger areas in one go,
1033 ;; like groups of pages that had triggered the write barrier, or
1034 ;; the whole static space" according to jsnell.
1038 `((simple-array ,(sb!vm:saetp-specifier saetp) (*))
1039 ,(if (or (eq (sb!vm:saetp-specifier saetp) 'character)
1041 (eq (sb!vm:saetp-specifier saetp) 'base-char))
1042 *default-init-char-form*
1043 (sb!vm:saetp-initial-element-default saetp))))
1045 #'sb!vm:saetp-specifier
1046 sb!vm:*specialized-array-element-type-properties*)))))
1047 ;; Only arrays have fill-pointers, but vectors have their length
1048 ;; parameter in the same place.
1049 (setf (%array-fill-pointer vector) new-length)
1052 (defun shrink-vector (vector new-length)
1053 (declare (vector vector))
1055 ((eq (length vector) new-length)
1057 ((array-has-fill-pointer-p vector)
1058 (setf (%array-fill-pointer vector) new-length)
1060 (t (subseq vector 0 new-length))))
1062 ;;; BIG THREAD SAFETY NOTE
1064 ;;; ADJUST-ARRAY/SET-ARRAY-HEADER, and its callees are very
1065 ;;; thread unsafe. They are nonatomic, and can mess with parallel
1066 ;;; code using the same arrays.
1068 ;;; A likely seeming fix is an additional level of indirection:
1069 ;;; ARRAY-HEADER -> ARRAY-INFO -> ... where ARRAY-HEADER would
1070 ;;; hold nothing but the pointer to ARRAY-INFO, and ARRAY-INFO
1071 ;;; would hold everything ARRAY-HEADER now holds. This allows
1072 ;;; consing up a new ARRAY-INFO and replacing it atomically in
1073 ;;; the ARRAY-HEADER.
1075 ;;; %WALK-DISPLACED-ARRAY-BACKPOINTERS is an especially nasty
1076 ;;; one: not only is it needed extremely rarely, which makes
1077 ;;; any thread safety bugs involving it look like rare random
1078 ;;; corruption, but because it walks the chain *upwards*, which
1079 ;;; may violate user expectations.
1081 (defun %save-displaced-array-backpointer (array data)
1082 (flet ((purge (pointers)
1083 (remove-if (lambda (value)
1084 (or (not value) (eq array value)))
1086 :key #'weak-pointer-value)))
1087 ;; Add backpointer to the new data vector if it has a header.
1088 (when (array-header-p data)
1089 (setf (%array-displaced-from data)
1090 (cons (make-weak-pointer array)
1091 (purge (%array-displaced-from data)))))
1092 ;; Remove old backpointer, if any.
1093 (let ((old-data (%array-data-vector array)))
1094 (when (and (neq data old-data) (array-header-p old-data))
1095 (setf (%array-displaced-from old-data)
1096 (purge (%array-displaced-from old-data)))))))
1098 (defun %walk-displaced-array-backpointers (array new-length)
1099 (dolist (p (%array-displaced-from array))
1100 (let ((from (weak-pointer-value p)))
1101 (when (and from (eq array (%array-data-vector from)))
1102 (let ((requires (+ (%array-available-elements from)
1103 (%array-displacement from))))
1104 (unless (>= new-length requires)
1105 ;; ANSI sayeth (ADJUST-ARRAY dictionary entry):
1107 ;; "If A is displaced to B, the consequences are unspecified if B is
1108 ;; adjusted in such a way that it no longer has enough elements to
1111 ;; since we're hanging on a weak pointer here, we can't signal an
1112 ;; error right now: the array that we're looking at might be
1113 ;; garbage. Instead, we set all dimensions to zero so that next
1114 ;; safe access to the displaced array will trap. Additionally, we
1115 ;; save the original dimensions, so we can signal a more
1116 ;; understandable error when the time comes.
1117 (%walk-displaced-array-backpointers from 0)
1118 (setf (%array-fill-pointer from) 0
1119 (%array-available-elements from) 0
1120 (%array-displaced-p from) (array-dimensions array))
1121 (dotimes (i (%array-rank from))
1122 (setf (%array-dimension from i) 0))))))))
1124 ;;; Fill in array header with the provided information, and return the array.
1125 (defun set-array-header (array data length fill-pointer displacement dimensions
1128 (setf (%array-displaced-from array) nil)
1129 (%walk-displaced-array-backpointers array length))
1131 (%save-displaced-array-backpointer array data))
1132 (setf (%array-data-vector array) data)
1133 (setf (%array-available-elements array) length)
1135 (setf (%array-fill-pointer array) fill-pointer)
1136 (setf (%array-fill-pointer-p array) t))
1138 (setf (%array-fill-pointer array) length)
1139 (setf (%array-fill-pointer-p array) nil)))
1140 (setf (%array-displacement array) displacement)
1141 (if (listp dimensions)
1142 (dotimes (axis (array-rank array))
1143 (declare (type index axis))
1144 (setf (%array-dimension array axis) (pop dimensions)))
1145 (setf (%array-dimension array 0) dimensions))
1146 (setf (%array-displaced-p array) displacedp)
1149 ;;; User visible extension
1150 (declaim (ftype (function (array) (values (simple-array * (*)) &optional))
1151 array-storage-vector))
1152 (defun array-storage-vector (array)
1153 "Returns the underlying storage vector of ARRAY, which must be a non-displaced array.
1155 In SBCL, if ARRAY is a of type \(SIMPLE-ARRAY * \(*)), it is its own storage
1156 vector. Multidimensional arrays, arrays with fill pointers, and adjustable
1157 arrays have an underlying storage vector with the same ARRAY-ELEMENT-TYPE as
1158 ARRAY, which this function returns.
1160 Important note: the underlying vector is an implementation detail. Even though
1161 this function exposes it, changes in the implementation may cause this
1162 function to be removed without further warning."
1163 ;; KLUDGE: Without TRULY-THE the system is not smart enough to figure out that
1164 ;; the return value is always of the known type.
1165 (truly-the (simple-array * (*))
1166 (if (array-header-p array)
1167 (if (%array-displaced-p array)
1168 (error "~S cannot be used with displaced arrays. Use ~S instead."
1169 'array-storage-vector 'array-displacement)
1170 (%array-data-vector array))
1174 ;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY
1176 ;;; This does the grinding work for ADJUST-ARRAY. It zaps the data
1177 ;;; from the OLD-DATA in an arrangement specified by the OLD-DIMS to
1178 ;;; the NEW-DATA in an arrangement specified by the NEW-DIMS. OFFSET
1179 ;;; is a displaced offset to be added to computed indices of OLD-DATA.
1180 (defun zap-array-data (old-data old-dims offset new-data new-dims new-length
1181 element-type initial-element initial-element-p)
1182 (declare (list old-dims new-dims)
1183 (fixnum new-length))
1184 ;; OLD-DIMS comes from array-dimensions, which returns a fresh list
1185 ;; at least in SBCL.
1186 ;; NEW-DIMS comes from the user.
1187 (setf old-dims (nreverse old-dims)
1188 new-dims (reverse new-dims))
1189 (cond ((eq old-data new-data)
1190 ;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and
1191 ;; INITIAL-ELEMENT-P are used when OLD-DATA and NEW-DATA are
1192 ;; EQ; in this case, a temporary must be used and filled
1193 ;; appropriately. specified initial-element.
1194 (when initial-element-p
1195 ;; FIXME: transforming this TYPEP to someting a bit faster
1196 ;; would be a win...
1197 (unless (typep initial-element element-type)
1198 (error "~S can't be used to initialize an array of type ~S."
1199 initial-element element-type)))
1200 (let ((temp (if initial-element-p
1201 (make-array new-length :initial-element initial-element)
1202 (make-array new-length))))
1203 (declare (simple-vector temp))
1204 (zap-array-data-aux old-data old-dims offset temp new-dims)
1205 (dotimes (i new-length)
1206 (setf (aref new-data i) (aref temp i)))
1207 ;; Kill the temporary vector to prevent garbage retention.
1208 (%shrink-vector temp 0)))
1210 ;; When OLD-DATA and NEW-DATA are not EQ, NEW-DATA has
1211 ;; already been filled with any
1212 (zap-array-data-aux old-data old-dims offset new-data new-dims))))
1214 (defun zap-array-data-aux (old-data old-dims offset new-data new-dims)
1215 (declare (fixnum offset))
1216 (let ((limits (mapcar (lambda (x y)
1217 (declare (fixnum x y))
1218 (1- (the fixnum (min x y))))
1219 old-dims new-dims)))
1220 (macrolet ((bump-index-list (index limits)
1221 `(do ((subscripts ,index (cdr subscripts))
1222 (limits ,limits (cdr limits)))
1223 ((null subscripts) :eof)
1224 (cond ((< (the fixnum (car subscripts))
1225 (the fixnum (car limits)))
1227 (1+ (the fixnum (car subscripts))))
1229 (t (rplaca subscripts 0))))))
1230 (do ((index (make-list (length old-dims) :initial-element 0)
1231 (bump-index-list index limits)))
1233 (setf (aref new-data (row-major-index-from-dims index new-dims))
1235 (+ (the fixnum (row-major-index-from-dims index old-dims))
1238 ;;; Figure out the row-major-order index of an array reference from a
1239 ;;; list of subscripts and a list of dimensions. This is for internal
1240 ;;; calls only, and the subscripts and dim-list variables are assumed
1241 ;;; to be reversed from what the user supplied.
1242 (defun row-major-index-from-dims (rev-subscripts rev-dim-list)
1243 (do ((rev-subscripts rev-subscripts (cdr rev-subscripts))
1244 (rev-dim-list rev-dim-list (cdr rev-dim-list))
1247 ((null rev-dim-list) result)
1248 (declare (fixnum chunk-size result))
1249 (setq result (+ result
1250 (the fixnum (* (the fixnum (car rev-subscripts))
1252 (setq chunk-size (* chunk-size (the fixnum (car rev-dim-list))))))
1256 (defun bit-array-same-dimensions-p (array1 array2)
1257 (declare (type (array bit) array1 array2))
1258 (and (= (array-rank array1)
1259 (array-rank array2))
1260 (dotimes (index (array-rank array1) t)
1261 (when (/= (array-dimension array1 index)
1262 (array-dimension array2 index))
1265 (defun pick-result-array (result-bit-array bit-array-1)
1266 (case result-bit-array
1268 ((nil) (make-array (array-dimensions bit-array-1)
1270 :initial-element 0))
1272 (unless (bit-array-same-dimensions-p bit-array-1
1274 (error "~S and ~S don't have the same dimensions."
1275 bit-array-1 result-bit-array))
1278 (defmacro def-bit-array-op (name function)
1279 `(defun ,name (bit-array-1 bit-array-2 &optional result-bit-array)
1282 "Perform a bit-wise ~A on the elements of BIT-ARRAY-1 and ~
1283 BIT-ARRAY-2,~% putting the results in RESULT-BIT-ARRAY. ~
1284 If RESULT-BIT-ARRAY is T,~% BIT-ARRAY-1 is used. If ~
1285 RESULT-BIT-ARRAY is NIL or omitted, a new array is~% created. ~
1286 All the arrays must have the same rank and dimensions."
1287 (symbol-name function))
1288 (declare (type (array bit) bit-array-1 bit-array-2)
1289 (type (or (array bit) (member t nil)) result-bit-array))
1290 (unless (bit-array-same-dimensions-p bit-array-1 bit-array-2)
1291 (error "~S and ~S don't have the same dimensions."
1292 bit-array-1 bit-array-2))
1293 (let ((result-bit-array (pick-result-array result-bit-array bit-array-1)))
1294 (if (and (simple-bit-vector-p bit-array-1)
1295 (simple-bit-vector-p bit-array-2)
1296 (simple-bit-vector-p result-bit-array))
1297 (locally (declare (optimize (speed 3) (safety 0)))
1298 (,name bit-array-1 bit-array-2 result-bit-array))
1299 (with-array-data ((data1 bit-array-1) (start1) (end1))
1300 (declare (ignore end1))
1301 (with-array-data ((data2 bit-array-2) (start2) (end2))
1302 (declare (ignore end2))
1303 (with-array-data ((data3 result-bit-array) (start3) (end3))
1304 (do ((index-1 start1 (1+ index-1))
1305 (index-2 start2 (1+ index-2))
1306 (index-3 start3 (1+ index-3)))
1307 ((>= index-3 end3) result-bit-array)
1308 (declare (type index index-1 index-2 index-3))
1309 (setf (sbit data3 index-3)
1310 (logand (,function (sbit data1 index-1)
1311 (sbit data2 index-2))
1314 (def-bit-array-op bit-and logand)
1315 (def-bit-array-op bit-ior logior)
1316 (def-bit-array-op bit-xor logxor)
1317 (def-bit-array-op bit-eqv logeqv)
1318 (def-bit-array-op bit-nand lognand)
1319 (def-bit-array-op bit-nor lognor)
1320 (def-bit-array-op bit-andc1 logandc1)
1321 (def-bit-array-op bit-andc2 logandc2)
1322 (def-bit-array-op bit-orc1 logorc1)
1323 (def-bit-array-op bit-orc2 logorc2)
1325 (defun bit-not (bit-array &optional result-bit-array)
1327 "Performs a bit-wise logical NOT on the elements of BIT-ARRAY,
1328 putting the results in RESULT-BIT-ARRAY. If RESULT-BIT-ARRAY is T,
1329 BIT-ARRAY is used. If RESULT-BIT-ARRAY is NIL or omitted, a new array is
1330 created. Both arrays must have the same rank and dimensions."
1331 (declare (type (array bit) bit-array)
1332 (type (or (array bit) (member t nil)) result-bit-array))
1333 (let ((result-bit-array (pick-result-array result-bit-array bit-array)))
1334 (if (and (simple-bit-vector-p bit-array)
1335 (simple-bit-vector-p result-bit-array))
1336 (locally (declare (optimize (speed 3) (safety 0)))
1337 (bit-not bit-array result-bit-array))
1338 (with-array-data ((src bit-array) (src-start) (src-end))
1339 (declare (ignore src-end))
1340 (with-array-data ((dst result-bit-array) (dst-start) (dst-end))
1341 (do ((src-index src-start (1+ src-index))
1342 (dst-index dst-start (1+ dst-index)))
1343 ((>= dst-index dst-end) result-bit-array)
1344 (declare (type index src-index dst-index))
1345 (setf (sbit dst dst-index)
1346 (logxor (sbit src src-index) 1))))))))