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 (defglobal %%simple-array-n-bits%% (make-array (1+ sb!vm:widetag-mask)))
137 #.(loop for info across sb!vm:*specialized-array-element-type-properties*
138 collect `(setf (aref %%simple-array-n-bits%% ,(sb!vm:saetp-typecode info))
139 ,(sb!vm:saetp-n-bits info)) into forms
140 finally (return `(progn ,@forms)))
142 (defun allocate-vector-with-widetag (widetag length &optional n-bits)
143 (declare (type (unsigned-byte 8) widetag)
145 (let ((n-bits (or n-bits (aref %%simple-array-n-bits%% widetag))))
146 (declare (type (integer 0 256) n-bits))
147 (allocate-vector widetag length
149 (* (if (or (= widetag sb!vm:simple-base-string-widetag)
152 sb!vm:simple-character-string-widetag))
156 sb!vm:n-word-bits))))
158 (defun make-array (dimensions &key
160 (initial-element nil initial-element-p)
161 (initial-contents nil initial-contents-p)
162 adjustable fill-pointer
163 displaced-to displaced-index-offset)
164 (let* ((dimensions (if (listp dimensions) dimensions (list dimensions)))
165 (array-rank (length (the list dimensions)))
166 (simple (and (null fill-pointer)
168 (null displaced-to))))
169 (declare (fixnum array-rank))
170 (when (and displaced-index-offset (null displaced-to))
171 (error "can't specify :DISPLACED-INDEX-OFFSET without :DISPLACED-TO"))
172 (when (and displaced-to
173 (arrayp displaced-to)
174 (not (equal (array-element-type displaced-to)
175 (upgraded-array-element-type element-type))))
176 (error "Array element type of :DISPLACED-TO array does not match specified element type"))
177 (if (and simple (= array-rank 1))
178 ;; it's a (SIMPLE-ARRAY * (*))
179 (multiple-value-bind (type n-bits)
180 (%vector-widetag-and-n-bits element-type)
181 (declare (type (unsigned-byte 8) type)
182 (type (integer 0 256) n-bits))
183 (let* ((length (car dimensions))
184 (array (allocate-vector-with-widetag type length n-bits)))
185 (declare (type index length))
186 (when initial-element-p
187 (fill array initial-element))
188 (when initial-contents-p
189 (when initial-element-p
190 (error "can't specify both :INITIAL-ELEMENT and ~
192 (unless (= length (length initial-contents))
193 (error "There are ~W elements in the :INITIAL-CONTENTS, but ~
194 the vector length is ~W."
195 (length initial-contents)
197 (replace array initial-contents))
199 ;; it's either a complex array or a multidimensional array.
200 (let* ((total-size (reduce #'* dimensions))
201 (data (or displaced-to
202 (data-vector-from-inits
203 dimensions total-size element-type nil
204 initial-contents initial-contents-p
205 initial-element initial-element-p)))
206 (array (make-array-header
207 (cond ((= array-rank 1)
208 (%complex-vector-widetag element-type))
209 (simple sb!vm:simple-array-widetag)
210 (t sb!vm:complex-array-widetag))
213 (unless (= array-rank 1)
214 (error "Only vectors can have fill pointers."))
215 (let ((length (car dimensions)))
216 (declare (fixnum length))
217 (setf (%array-fill-pointer array)
218 (cond ((eq fill-pointer t)
221 (unless (and (fixnump fill-pointer)
223 (<= fill-pointer length))
224 ;; FIXME: should be TYPE-ERROR?
225 (error "invalid fill-pointer ~W"
228 (setf (%array-fill-pointer-p array) t))
230 (setf (%array-fill-pointer array) total-size)
231 (setf (%array-fill-pointer-p array) nil)))
232 (setf (%array-available-elements array) total-size)
233 (setf (%array-data-vector array) data)
234 (setf (%array-displaced-from array) nil)
236 (when (or initial-element-p initial-contents-p)
237 (error "Neither :INITIAL-ELEMENT nor :INITIAL-CONTENTS ~
238 can be specified along with :DISPLACED-TO"))
239 (let ((offset (or displaced-index-offset 0)))
240 (when (> (+ offset total-size)
241 (array-total-size displaced-to))
242 (error "~S doesn't have enough elements." displaced-to))
243 (setf (%array-displacement array) offset)
244 (setf (%array-displaced-p array) t)
245 (%save-displaced-array-backpointer array data)))
247 (setf (%array-displaced-p array) nil)))
249 (dolist (dim dimensions)
250 (setf (%array-dimension array axis) dim)
254 (defun make-static-vector (length &key
255 (element-type '(unsigned-byte 8))
256 (initial-contents nil initial-contents-p)
257 (initial-element nil initial-element-p))
258 "Allocate vector of LENGTH elements in static space. Only allocation
259 of specialized arrays is supported."
260 ;; STEP 1: check inputs fully
262 ;; This way of doing explicit checks before the vector is allocated
263 ;; is expensive, but probably worth the trouble as once we've allocated
264 ;; the vector we have no way to get rid of it anymore...
265 (when (eq t (upgraded-array-element-type element-type))
266 (error "Static arrays of type ~S not supported."
268 (when initial-contents-p
269 (when initial-element-p
270 (error "can't specify both :INITIAL-ELEMENT and :INITIAL-CONTENTS"))
271 (unless (= length (length initial-contents))
272 (error "There are ~W elements in the :INITIAL-CONTENTS, but the ~
273 vector length is ~W."
274 (length initial-contents)
276 (unless (every (lambda (x) (typep x element-type)) initial-contents)
277 (error ":INITIAL-CONTENTS contains elements not of type ~S."
279 (when initial-element-p
280 (unless (typep initial-element element-type)
281 (error ":INITIAL-ELEMENT ~S is not of type ~S."
282 initial-element element-type)))
285 ;; Allocate and possibly initialize the vector.
286 (multiple-value-bind (type n-bits)
287 (sb!impl::%vector-widetag-and-n-bits element-type)
289 (allocate-static-vector type length
290 (ceiling (* length n-bits)
291 sb!vm:n-word-bits))))
292 (cond (initial-element-p
293 (fill vector initial-element))
295 (replace vector initial-contents))
299 ;;; DATA-VECTOR-FROM-INITS returns a simple vector that has the
300 ;;; specified array characteristics. Dimensions is only used to pass
301 ;;; to FILL-DATA-VECTOR for error checking on the structure of
302 ;;; initial-contents.
303 (defun data-vector-from-inits (dimensions total-size
305 initial-contents initial-contents-p
306 initial-element initial-element-p)
307 (when initial-element-p
308 (when initial-contents-p
309 (error "cannot supply both :INITIAL-CONTENTS and :INITIAL-ELEMENT to
310 either MAKE-ARRAY or ADJUST-ARRAY."))
311 (unless (typep initial-element element-type)
312 (error "~S cannot be used to initialize an array of type ~S."
313 initial-element element-type)))
314 (let ((data (if widetag
315 (allocate-vector-with-widetag widetag total-size)
316 (make-array total-size :element-type element-type))))
317 (cond (initial-element-p
318 (fill (the vector data) initial-element))
320 (fill-data-vector data dimensions initial-contents)))
323 (defun vector (&rest objects)
325 "Construct a SIMPLE-VECTOR from the given objects."
326 (coerce (the list objects) 'simple-vector))
329 ;;;; accessor/setter functions
331 ;;; Dispatch to an optimized routine the data vector accessors for
332 ;;; each different specialized vector type. Do dispatching by looking
333 ;;; up the widetag in the array rather than with the typecases, which
334 ;;; as of 1.0.5 compiles to a naive sequence of linear TYPEPs. Also
335 ;;; provide separate versions where bounds checking has been moved
336 ;;; from the callee to the caller, since it's much cheaper to do once
337 ;;; the type information is available. Finally, for each of these
338 ;;; routines also provide a slow path, taken for arrays that are not
339 ;;; vectors or not simple.
340 (macrolet ((def (name table-name)
342 (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)))
343 (defmacro ,name (array-var)
346 (when (sb!vm::%other-pointer-p ,array-var)
347 (setf tag (%other-pointer-widetag ,array-var)))
348 (svref ,',table-name tag)))))))
349 (def !find-data-vector-setter %%data-vector-setters%%)
350 (def !find-data-vector-setter/check-bounds %%data-vector-setters/check-bounds%%)
351 ;; Used by DO-VECTOR-DATA -- which in turn appears in DOSEQUENCE expansion,
352 ;; meaning we can have post-build dependences on this.
353 (def %find-data-vector-reffer %%data-vector-reffers%%)
354 (def !find-data-vector-reffer/check-bounds %%data-vector-reffers/check-bounds%%))
356 ;;; Like DOVECTOR, but more magical -- can't use this on host.
357 (defmacro do-vector-data ((elt vector &optional result) &body body)
358 (multiple-value-bind (forms decls) (parse-body body :doc-string-allowed nil)
359 (with-unique-names (index vec start end ref)
360 `(with-array-data ((,vec ,vector)
363 :check-fill-pointer t)
364 (let ((,ref (%find-data-vector-reffer ,vec)))
365 (do ((,index ,start (1+ ,index)))
368 ,@(filter-dolist-declarations decls)
371 (let ((,elt (funcall ,ref ,vec ,index)))
373 (tagbody ,@forms))))))))
375 (macrolet ((%ref (accessor-getter extra-params)
376 `(funcall (,accessor-getter array) array index ,@extra-params))
377 (define (accessor-name slow-accessor-name accessor-getter
378 extra-params check-bounds)
380 (defun ,accessor-name (array index ,@extra-params)
381 (declare (optimize speed
382 ;; (SAFETY 0) is ok. All calls to
383 ;; these functions are generated by
384 ;; the compiler, so argument count
385 ;; checking isn't needed. Type checking
386 ;; is done implicitly via the widetag
389 (%ref ,accessor-getter ,extra-params))
390 (defun ,slow-accessor-name (array index ,@extra-params)
391 (declare (optimize speed (safety 0)))
392 (if (not (%array-displaced-p array))
393 ;; The reasonably quick path of non-displaced complex
395 (let ((array (%array-data-vector array)))
396 (%ref ,accessor-getter ,extra-params))
397 ;; The real slow path.
401 (declare (optimize (speed 1) (safety 1)))
402 (,@check-bounds index)))
405 (declare (ignore end))
406 (,accessor-name vector index ,@extra-params)))))))
407 (define hairy-data-vector-ref slow-hairy-data-vector-ref
408 %find-data-vector-reffer
410 (define hairy-data-vector-set slow-hairy-data-vector-set
411 !find-data-vector-setter
413 (define hairy-data-vector-ref/check-bounds
414 slow-hairy-data-vector-ref/check-bounds
415 !find-data-vector-reffer/check-bounds
416 nil (%check-bound array (array-dimension array 0)))
417 (define hairy-data-vector-set/check-bounds
418 slow-hairy-data-vector-set/check-bounds
419 !find-data-vector-setter/check-bounds
420 (new-value) (%check-bound array (array-dimension array 0))))
422 (defun hairy-ref-error (array index &optional new-value)
423 (declare (ignore index new-value))
426 :expected-type 'vector))
428 (macrolet ((define-reffer (saetp check-form)
429 (let* ((type (sb!vm:saetp-specifier saetp))
430 (atype `(simple-array ,type (*))))
431 `(named-lambda optimized-data-vector-ref (vector index)
432 (declare (optimize speed (safety 0)))
433 (data-vector-ref (the ,atype vector)
435 (declare (optimize (safety 1)))
437 (,@check-form index)))))))
438 (define-setter (saetp check-form)
439 (let* ((type (sb!vm:saetp-specifier saetp))
440 (atype `(simple-array ,type (*))))
441 `(named-lambda optimized-data-vector-set (vector index new-value)
442 (declare (optimize speed (safety 0)))
443 (data-vector-set (the ,atype vector)
445 (declare (optimize (safety 1)))
447 (,@check-form index)))
449 ;; SPEED 1 needed to avoid the compiler
450 ;; from downgrading the type check to
452 (declare (optimize (speed 1)
454 (the ,type new-value)))
455 ;; For specialized arrays, the return from
456 ;; data-vector-set would have to be reboxed to be a
457 ;; (Lisp) return value; instead, we use the
458 ;; already-boxed value as the return.
460 (define-reffers (symbol deffer check-form slow-path)
462 ;; FIXME/KLUDGE: can't just FILL here, because genesis doesn't
463 ;; preserve the binding, so re-initiaize as NS doesn't have
464 ;; the energy to figure out to change that right now.
465 (setf ,symbol (make-array (1+ sb!vm::widetag-mask)
466 :initial-element #'hairy-ref-error))
467 ,@(loop for widetag in '(sb!vm:complex-vector-widetag
468 sb!vm:complex-vector-nil-widetag
469 sb!vm:complex-bit-vector-widetag
470 #!+sb-unicode sb!vm:complex-character-string-widetag
471 sb!vm:complex-base-string-widetag
472 sb!vm:simple-array-widetag
473 sb!vm:complex-array-widetag)
474 collect `(setf (svref ,symbol ,widetag) ,slow-path))
475 ,@(loop for saetp across sb!vm:*specialized-array-element-type-properties*
476 for widetag = (sb!vm:saetp-typecode saetp)
477 collect `(setf (svref ,symbol ,widetag)
478 (,deffer ,saetp ,check-form))))))
479 (defun !hairy-data-vector-reffer-init ()
480 (define-reffers %%data-vector-reffers%% define-reffer
482 #'slow-hairy-data-vector-ref)
483 (define-reffers %%data-vector-setters%% define-setter
485 #'slow-hairy-data-vector-set)
486 (define-reffers %%data-vector-reffers/check-bounds%% define-reffer
487 (%check-bound vector (length vector))
488 #'slow-hairy-data-vector-ref/check-bounds)
489 (define-reffers %%data-vector-setters/check-bounds%% define-setter
490 (%check-bound vector (length vector))
491 #'slow-hairy-data-vector-set/check-bounds)))
493 ;;; (Ordinary DATA-VECTOR-REF usage compiles into a vop, but
494 ;;; DATA-VECTOR-REF is also FOLDABLE, and this ordinary function
495 ;;; definition is needed for the compiler to use in constant folding.)
496 (defun data-vector-ref (array index)
497 (hairy-data-vector-ref array index))
499 (defun data-vector-ref-with-offset (array index offset)
500 (hairy-data-vector-ref array (+ index offset)))
502 (defun invalid-array-p (array)
503 (and (array-header-p array)
504 (consp (%array-displaced-p array))))
506 (declaim (ftype (function (array) nil) invalid-array-error))
507 (defun invalid-array-error (array)
508 (aver (array-header-p array))
509 ;; Array invalidation stashes the original dimensions here...
510 (let ((dims (%array-displaced-p array))
511 (et (array-element-type array)))
512 (error 'invalid-array-error
517 `(vector ,et ,@dims)))))
519 (declaim (ftype (function (array integer integer &optional t) nil)
520 invalid-array-index-error))
521 (defun invalid-array-index-error (array index bound &optional axis)
522 (if (invalid-array-p array)
523 (invalid-array-error array)
524 (error 'invalid-array-index-error
528 :expected-type `(integer 0 (,bound)))))
530 ;;; SUBSCRIPTS has a dynamic-extent list structure and is destroyed
531 (defun %array-row-major-index (array subscripts
532 &optional (invalid-index-error-p t))
533 (declare (array array)
535 (let ((rank (array-rank array)))
536 (unless (= rank (length subscripts))
537 (error "wrong number of subscripts, ~W, for array of rank ~W"
538 (length subscripts) rank))
539 (if (array-header-p array)
540 (do ((subs (nreverse subscripts) (cdr subs))
541 (axis (1- (array-rank array)) (1- axis))
545 (declare (list subs) (fixnum axis chunk-size result))
546 (let ((index (car subs))
547 (dim (%array-dimension array axis)))
548 (declare (fixnum dim))
549 (unless (and (fixnump index) (< -1 index dim))
550 (if invalid-index-error-p
551 (invalid-array-index-error array index dim axis)
552 (return-from %array-row-major-index nil)))
553 (incf result (* chunk-size (the fixnum index)))
554 (setf chunk-size (* chunk-size dim))))
555 (let ((index (first subscripts))
556 (length (length (the (simple-array * (*)) array))))
557 (unless (and (fixnump index) (< -1 index length))
558 (if invalid-index-error-p
559 (invalid-array-index-error array index length)
560 (return-from %array-row-major-index nil)))
563 (defun array-in-bounds-p (array &rest subscripts)
565 "Return T if the SUBSCRIPTS are in bounds for the ARRAY, NIL otherwise."
566 (if (%array-row-major-index array subscripts nil)
569 (defun array-row-major-index (array &rest subscripts)
570 (declare (truly-dynamic-extent subscripts))
571 (%array-row-major-index array subscripts))
573 (defun aref (array &rest subscripts)
575 "Return the element of the ARRAY specified by the SUBSCRIPTS."
576 (declare (truly-dynamic-extent subscripts))
577 (row-major-aref array (%array-row-major-index array subscripts)))
579 (defun %aset (array &rest stuff)
580 (declare (truly-dynamic-extent stuff))
581 (let ((subscripts (butlast stuff))
582 (new-value (car (last stuff))))
583 (setf (row-major-aref array (%array-row-major-index array subscripts))
586 ;;; FIXME: What's supposed to happen with functions
587 ;;; like AREF when we (DEFUN (SETF FOO) ..) when
588 ;;; DEFSETF FOO is also defined? It seems as though the logical
589 ;;; thing to do would be to nuke the macro definition for (SETF FOO)
590 ;;; and replace it with the (SETF FOO) function, issuing a warning,
591 ;;; just as for ordinary functions
592 ;;; * (LISP-IMPLEMENTATION-VERSION)
593 ;;; "18a+ release x86-linux 2.4.7 6 November 1998 cvs"
594 ;;; * (DEFMACRO ZOO (X) `(+ ,X ,X))
596 ;;; * (DEFUN ZOO (X) (* 3 X))
597 ;;; Warning: ZOO previously defined as a macro.
599 ;;; But that doesn't seem to be what happens in CMU CL.
601 ;;; KLUDGE: this is probably because ANSI, in its wisdom (CLHS
602 ;;; 5.1.2.5) requires implementations to support
603 ;;; (SETF (APPLY #'AREF ...) ...)
604 ;;; [and also #'BIT and #'SBIT]. Yes, this is terrifying, and it's
605 ;;; also terrifying that this sequence of definitions causes it to
608 ;;; Also, it would be nice to make DESCRIBE FOO tell whether a symbol
609 ;;; has a setf expansion and/or a setf function defined.
611 #!-sb-fluid (declaim (inline (setf aref)))
612 (defun (setf aref) (new-value array &rest subscripts)
613 (declare (truly-dynamic-extent subscripts))
614 (declare (type array array))
615 (setf (row-major-aref array (%array-row-major-index array subscripts))
618 (defun row-major-aref (array index)
620 "Return the element of array corressponding to the row-major index. This is
622 (declare (optimize (safety 1)))
623 (row-major-aref array index))
625 (defun %set-row-major-aref (array index new-value)
626 (declare (optimize (safety 1)))
627 (setf (row-major-aref array index) new-value))
629 (defun svref (simple-vector index)
631 "Return the INDEX'th element of the given Simple-Vector."
632 (declare (optimize (safety 1)))
633 (aref simple-vector index))
635 (defun %svset (simple-vector index new)
636 (declare (optimize (safety 1)))
637 (setf (aref simple-vector index) new))
639 (defun bit (bit-array &rest subscripts)
641 "Return the bit from the BIT-ARRAY at the specified SUBSCRIPTS."
642 (declare (type (array bit) bit-array) (optimize (safety 1)))
643 (row-major-aref bit-array (%array-row-major-index bit-array subscripts)))
645 (defun %bitset (bit-array &rest stuff)
646 (declare (type (array bit) bit-array) (optimize (safety 1)))
647 (let ((subscripts (butlast stuff))
648 (new-value (car (last stuff))))
649 (setf (row-major-aref bit-array
650 (%array-row-major-index bit-array subscripts))
653 #!-sb-fluid (declaim (inline (setf bit)))
654 (defun (setf bit) (new-value bit-array &rest subscripts)
655 (declare (type (array bit) bit-array) (optimize (safety 1)))
656 (setf (row-major-aref bit-array
657 (%array-row-major-index bit-array subscripts))
660 (defun sbit (simple-bit-array &rest subscripts)
662 "Return the bit from SIMPLE-BIT-ARRAY at the specified SUBSCRIPTS."
663 (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
664 (row-major-aref simple-bit-array
665 (%array-row-major-index simple-bit-array subscripts)))
667 ;;; KLUDGE: Not all these things (%SET-ROW-MAJOR-AREF, %SET-FILL-POINTER,
668 ;;; %SET-FDEFINITION, %SCHARSET, %SBITSET..) seem to deserve separate names.
669 ;;; Could we just DEFUN (SETF SBIT) etc. and get rid of the non-ANSI names?
671 (defun %sbitset (simple-bit-array &rest stuff)
672 (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
673 (let ((subscripts (butlast stuff))
674 (new-value (car (last stuff))))
675 (setf (row-major-aref simple-bit-array
676 (%array-row-major-index simple-bit-array subscripts))
679 #!-sb-fluid (declaim (inline (setf sbit)))
680 (defun (setf sbit) (new-value bit-array &rest subscripts)
681 (declare (type (simple-array bit) bit-array) (optimize (safety 1)))
682 (setf (row-major-aref bit-array
683 (%array-row-major-index bit-array subscripts))
686 ;;;; miscellaneous array properties
688 (defun array-element-type (array)
690 "Return the type of the elements of the array"
691 (let ((widetag (widetag-of array)))
692 (macrolet ((pick-element-type (&rest stuff)
693 `(cond ,@(mapcar (lambda (stuff)
695 (let ((item (car stuff)))
704 `(= widetag ,item))))
707 #.`(pick-element-type
710 `(,(if (sb!vm:saetp-complex-typecode saetp)
711 (list (sb!vm:saetp-typecode saetp)
712 (sb!vm:saetp-complex-typecode saetp))
713 (sb!vm:saetp-typecode saetp))
714 ',(sb!vm:saetp-specifier saetp)))
715 sb!vm:*specialized-array-element-type-properties*)
716 ((sb!vm:simple-array-widetag
717 sb!vm:complex-vector-widetag
718 sb!vm:complex-array-widetag)
719 (with-array-data ((array array) (start) (end))
720 (declare (ignore start end))
721 (array-element-type array)))
723 (error 'type-error :datum array :expected-type 'array))))))
725 (defun array-rank (array)
727 "Return the number of dimensions of ARRAY."
728 (if (array-header-p array)
732 (defun array-dimension (array axis-number)
734 "Return the length of dimension AXIS-NUMBER of ARRAY."
735 (declare (array array) (type index axis-number))
736 (cond ((not (array-header-p array))
737 (unless (= axis-number 0)
738 (error "Vector axis is not zero: ~S" axis-number))
739 (length (the (simple-array * (*)) array)))
740 ((>= axis-number (%array-rank array))
741 (error "Axis number ~W is too big; ~S only has ~D dimension~:P."
742 axis-number array (%array-rank array)))
744 (%array-dimension array axis-number))))
746 (defun array-dimensions (array)
748 "Return a list whose elements are the dimensions of the array"
749 (declare (array array))
750 (if (array-header-p array)
751 (do ((results nil (cons (array-dimension array index) results))
752 (index (1- (array-rank array)) (1- index)))
753 ((minusp index) results))
754 (list (array-dimension array 0))))
756 (defun array-total-size (array)
758 "Return the total number of elements in the Array."
759 (declare (array array))
760 (if (array-header-p array)
761 (%array-available-elements array)
762 (length (the vector array))))
764 (defun array-displacement (array)
766 "Return the values of :DISPLACED-TO and :DISPLACED-INDEX-offset
767 options to MAKE-ARRAY, or NIL and 0 if not a displaced array."
768 (declare (type array array))
769 (if (and (array-header-p array) ; if unsimple and
770 (%array-displaced-p array)) ; displaced
771 (values (%array-data-vector array) (%array-displacement array))
774 (defun adjustable-array-p (array)
776 "Return T if (ADJUST-ARRAY ARRAY...) would return an array identical
777 to the argument, this happens for complex arrays."
778 (declare (array array))
779 ;; Note that this appears not to be a fundamental limitation.
780 ;; non-vector SIMPLE-ARRAYs are in fact capable of being adjusted,
781 ;; but in practice we test using ADJUSTABLE-ARRAY-P in ADJUST-ARRAY.
782 ;; -- CSR, 2004-03-01.
783 (not (typep array 'simple-array)))
785 ;;;; fill pointer frobbing stuff
787 (declaim (inline array-has-fill-pointer-p))
788 (defun array-has-fill-pointer-p (array)
790 "Return T if the given ARRAY has a fill pointer, or NIL otherwise."
791 (declare (array array))
792 (and (array-header-p array) (%array-fill-pointer-p array)))
794 (defun fill-pointer-error (vector arg)
796 (aver (array-has-fill-pointer-p vector))
797 (let ((max (%array-available-elements vector)))
798 (error 'simple-type-error
800 :expected-type (list 'integer 0 max)
801 :format-control "The new fill pointer, ~S, is larger than the length of the vector (~S.)"
802 :format-arguments (list arg max))))
804 (error 'simple-type-error
806 :expected-type '(and vector (satisfies array-has-fill-pointer-p))
807 :format-control "~S is not an array with a fill pointer."
808 :format-arguments (list vector)))))
810 (declaim (inline fill-pointer))
811 (defun fill-pointer (vector)
813 "Return the FILL-POINTER of the given VECTOR."
814 (if (array-has-fill-pointer-p vector)
815 (%array-fill-pointer vector)
816 (fill-pointer-error vector nil)))
818 (defun %set-fill-pointer (vector new)
820 (fill-pointer-error vector x)))
821 (if (array-has-fill-pointer-p vector)
822 (if (> new (%array-available-elements vector))
824 (setf (%array-fill-pointer vector) new))
827 ;;; FIXME: It'd probably make sense to use a MACROLET to share the
828 ;;; guts of VECTOR-PUSH between VECTOR-PUSH-EXTEND. Such a macro
829 ;;; should probably be based on the VECTOR-PUSH-EXTEND code (which is
830 ;;; new ca. sbcl-0.7.0) rather than the VECTOR-PUSH code (which dates
832 (defun vector-push (new-el array)
834 "Attempt to set the element of ARRAY designated by its fill pointer
835 to NEW-EL, and increment the fill pointer by one. If the fill pointer is
836 too large, NIL is returned, otherwise the index of the pushed element is
838 (let ((fill-pointer (fill-pointer array)))
839 (declare (fixnum fill-pointer))
840 (cond ((= fill-pointer (%array-available-elements array))
843 (locally (declare (optimize (safety 0)))
844 (setf (aref array fill-pointer) new-el))
845 (setf (%array-fill-pointer array) (1+ fill-pointer))
848 (defun vector-push-extend (new-element vector &optional min-extension)
849 (declare (type (or null fixnum) min-extension))
850 (let ((fill-pointer (fill-pointer vector)))
851 (declare (fixnum fill-pointer))
852 (when (= fill-pointer (%array-available-elements vector))
855 (let ((length (length vector)))
857 (- array-dimension-limit length))))))
858 (adjust-array vector (+ fill-pointer (max 1 min-extension)))))
859 ;; disable bounds checking
860 (locally (declare (optimize (safety 0)))
861 (setf (aref vector fill-pointer) new-element))
862 (setf (%array-fill-pointer vector) (1+ fill-pointer))
865 (defun vector-pop (array)
867 "Decrease the fill pointer by 1 and return the element pointed to by the
869 (let ((fill-pointer (fill-pointer array)))
870 (declare (fixnum fill-pointer))
871 (if (zerop fill-pointer)
872 (error "There is nothing left to pop.")
873 ;; disable bounds checking (and any fixnum test)
874 (locally (declare (optimize (safety 0)))
876 (setf (%array-fill-pointer array)
877 (1- fill-pointer)))))))
882 (defun adjust-array (array dimensions &key
883 (element-type (array-element-type array) element-type-p)
884 (initial-element nil initial-element-p)
885 (initial-contents nil initial-contents-p)
887 displaced-to displaced-index-offset)
889 "Adjust ARRAY's dimensions to the given DIMENSIONS and stuff."
890 (when (invalid-array-p array)
891 (invalid-array-error array))
892 (let ((dimensions (if (listp dimensions) dimensions (list dimensions))))
893 (cond ((/= (the fixnum (length (the list dimensions)))
894 (the fixnum (array-rank array)))
895 (error "The number of dimensions not equal to rank of array."))
897 (not (subtypep element-type (array-element-type array))))
898 (error "The new element type, ~S, is incompatible with old type."
900 ((and fill-pointer (not (array-has-fill-pointer-p array)))
903 :expected-type '(satisfies array-has-fill-pointer-p))))
904 (let ((array-rank (length (the list dimensions))))
905 (declare (fixnum array-rank))
906 (unless (= array-rank 1)
908 (error "Only vectors can have fill pointers.")))
909 (cond (initial-contents-p
910 ;; array former contents replaced by INITIAL-CONTENTS
911 (if (or initial-element-p displaced-to)
912 (error ":INITIAL-CONTENTS may not be specified with ~
913 the :INITIAL-ELEMENT or :DISPLACED-TO option."))
914 (let* ((array-size (apply #'* dimensions))
915 (array-data (data-vector-from-inits
916 dimensions array-size element-type nil
917 initial-contents initial-contents-p
918 initial-element initial-element-p)))
919 (if (adjustable-array-p array)
920 (set-array-header array array-data array-size
921 (get-new-fill-pointer array array-size
923 0 dimensions nil nil)
924 (if (array-header-p array)
925 ;; simple multidimensional or single dimensional array
926 (make-array dimensions
927 :element-type element-type
928 :initial-contents initial-contents)
931 ;; We already established that no INITIAL-CONTENTS was supplied.
932 (when initial-element
933 (error "The :INITIAL-ELEMENT option may not be specified ~
934 with :DISPLACED-TO."))
935 (unless (subtypep element-type (array-element-type displaced-to))
936 (error "can't displace an array of type ~S into another of ~
938 element-type (array-element-type displaced-to)))
939 (let ((displacement (or displaced-index-offset 0))
940 (array-size (apply #'* dimensions)))
941 (declare (fixnum displacement array-size))
942 (if (< (the fixnum (array-total-size displaced-to))
943 (the fixnum (+ displacement array-size)))
944 (error "The :DISPLACED-TO array is too small."))
945 (if (adjustable-array-p array)
946 ;; None of the original contents appear in adjusted array.
947 (set-array-header array displaced-to array-size
948 (get-new-fill-pointer array array-size
950 displacement dimensions t nil)
951 ;; simple multidimensional or single dimensional array
952 (make-array dimensions
953 :element-type element-type
954 :displaced-to displaced-to
955 :displaced-index-offset
956 displaced-index-offset))))
958 (let ((old-length (array-total-size array))
959 (new-length (car dimensions))
961 (declare (fixnum old-length new-length))
962 (with-array-data ((old-data array) (old-start)
963 (old-end old-length))
964 (cond ((or (and (array-header-p array)
965 (%array-displaced-p array))
966 (< old-length new-length))
968 (data-vector-from-inits
969 dimensions new-length element-type
970 (widetag-of old-data)
971 initial-contents initial-contents-p
972 initial-element initial-element-p))
973 ;; Provide :END1 to avoid full call to LENGTH
975 (replace new-data old-data
977 :start2 old-start :end2 old-end))
979 (shrink-vector old-data new-length))))
980 (if (adjustable-array-p array)
981 (set-array-header array new-data new-length
982 (get-new-fill-pointer array new-length
984 0 dimensions nil nil)
987 (let ((old-length (%array-available-elements array))
988 (new-length (apply #'* dimensions)))
989 (declare (fixnum old-length new-length))
990 (with-array-data ((old-data array) (old-start)
991 (old-end old-length))
992 (declare (ignore old-end))
993 (let ((new-data (if (or (and (array-header-p array)
994 (%array-displaced-p array))
995 (> new-length old-length))
996 (data-vector-from-inits
997 dimensions new-length
999 (widetag-of old-data) () nil
1000 initial-element initial-element-p)
1002 (if (or (zerop old-length) (zerop new-length))
1003 (when initial-element-p (fill new-data initial-element))
1004 (zap-array-data old-data (array-dimensions array)
1006 new-data dimensions new-length
1007 element-type initial-element
1009 (if (adjustable-array-p array)
1010 (set-array-header array new-data new-length
1011 nil 0 dimensions nil nil)
1014 sb!vm:simple-array-widetag array-rank)))
1015 (set-array-header new-array new-data new-length
1016 nil 0 dimensions nil t)))))))))))
1019 (defun get-new-fill-pointer (old-array new-array-size fill-pointer)
1020 (cond ((not fill-pointer)
1021 (when (array-has-fill-pointer-p old-array)
1022 (when (> (%array-fill-pointer old-array) new-array-size)
1023 (error "cannot ADJUST-ARRAY an array (~S) to a size (~S) that is ~
1024 smaller than its fill pointer (~S)"
1025 old-array new-array-size (fill-pointer old-array)))
1026 (%array-fill-pointer old-array)))
1027 ((not (array-has-fill-pointer-p old-array))
1028 (error "cannot supply a non-NIL value (~S) for :FILL-POINTER ~
1029 in ADJUST-ARRAY unless the array (~S) was originally ~
1030 created with a fill pointer"
1033 ((numberp fill-pointer)
1034 (when (> fill-pointer new-array-size)
1035 (error "can't supply a value for :FILL-POINTER (~S) that is larger ~
1036 than the new length of the vector (~S)"
1037 fill-pointer new-array-size))
1039 ((eq fill-pointer t)
1042 (error "bogus value for :FILL-POINTER in ADJUST-ARRAY: ~S"
1045 ;;; Destructively alter VECTOR, changing its length to NEW-LENGTH,
1046 ;;; which must be less than or equal to its current length. This can
1047 ;;; be called on vectors without a fill pointer but it is extremely
1048 ;;; dangerous to do so: shrinking the size of an object (as viewed by
1049 ;;; the gc) makes bounds checking unreliable in the face of interrupts
1050 ;;; or multi-threading. Call it only on provably local vectors.
1051 (defun %shrink-vector (vector new-length)
1052 (declare (vector vector))
1053 (unless (array-header-p vector)
1054 (macrolet ((frob (name &rest things)
1056 ((simple-array nil (*)) (error 'nil-array-accessed-error))
1057 ,@(mapcar (lambda (thing)
1058 (destructuring-bind (type-spec fill-value)
1061 (fill (truly-the ,type-spec ,name)
1063 :start new-length))))
1065 ;; Set the 'tail' of the vector to the appropriate type of zero,
1066 ;; "because in some cases we'll scavenge larger areas in one go,
1067 ;; like groups of pages that had triggered the write barrier, or
1068 ;; the whole static space" according to jsnell.
1072 `((simple-array ,(sb!vm:saetp-specifier saetp) (*))
1073 ,(if (or (eq (sb!vm:saetp-specifier saetp) 'character)
1075 (eq (sb!vm:saetp-specifier saetp) 'base-char))
1076 *default-init-char-form*
1077 (sb!vm:saetp-initial-element-default saetp))))
1079 #'sb!vm:saetp-specifier
1080 sb!vm:*specialized-array-element-type-properties*)))))
1081 ;; Only arrays have fill-pointers, but vectors have their length
1082 ;; parameter in the same place.
1083 (setf (%array-fill-pointer vector) new-length)
1086 (defun shrink-vector (vector new-length)
1087 (declare (vector vector))
1089 ((eq (length vector) new-length)
1091 ((array-has-fill-pointer-p vector)
1092 (setf (%array-fill-pointer vector) new-length)
1094 (t (subseq vector 0 new-length))))
1096 ;;; BIG THREAD SAFETY NOTE
1098 ;;; ADJUST-ARRAY/SET-ARRAY-HEADER, and its callees are very
1099 ;;; thread unsafe. They are nonatomic, and can mess with parallel
1100 ;;; code using the same arrays.
1102 ;;; A likely seeming fix is an additional level of indirection:
1103 ;;; ARRAY-HEADER -> ARRAY-INFO -> ... where ARRAY-HEADER would
1104 ;;; hold nothing but the pointer to ARRAY-INFO, and ARRAY-INFO
1105 ;;; would hold everything ARRAY-HEADER now holds. This allows
1106 ;;; consing up a new ARRAY-INFO and replacing it atomically in
1107 ;;; the ARRAY-HEADER.
1109 ;;; %WALK-DISPLACED-ARRAY-BACKPOINTERS is an especially nasty
1110 ;;; one: not only is it needed extremely rarely, which makes
1111 ;;; any thread safety bugs involving it look like rare random
1112 ;;; corruption, but because it walks the chain *upwards*, which
1113 ;;; may violate user expectations.
1115 (defun %save-displaced-array-backpointer (array data)
1116 (flet ((purge (pointers)
1117 (remove-if (lambda (value)
1118 (or (not value) (eq array value)))
1120 :key #'weak-pointer-value)))
1121 ;; Add backpointer to the new data vector if it has a header.
1122 (when (array-header-p data)
1123 (setf (%array-displaced-from data)
1124 (cons (make-weak-pointer array)
1125 (purge (%array-displaced-from data)))))
1126 ;; Remove old backpointer, if any.
1127 (let ((old-data (%array-data-vector array)))
1128 (when (and (neq data old-data) (array-header-p old-data))
1129 (setf (%array-displaced-from old-data)
1130 (purge (%array-displaced-from old-data)))))))
1132 (defun %walk-displaced-array-backpointers (array new-length)
1133 (dolist (p (%array-displaced-from array))
1134 (let ((from (weak-pointer-value p)))
1135 (when (and from (eq array (%array-data-vector from)))
1136 (let ((requires (+ (%array-available-elements from)
1137 (%array-displacement from))))
1138 (unless (>= new-length requires)
1139 ;; ANSI sayeth (ADJUST-ARRAY dictionary entry):
1141 ;; "If A is displaced to B, the consequences are unspecified if B is
1142 ;; adjusted in such a way that it no longer has enough elements to
1145 ;; since we're hanging on a weak pointer here, we can't signal an
1146 ;; error right now: the array that we're looking at might be
1147 ;; garbage. Instead, we set all dimensions to zero so that next
1148 ;; safe access to the displaced array will trap. Additionally, we
1149 ;; save the original dimensions, so we can signal a more
1150 ;; understandable error when the time comes.
1151 (%walk-displaced-array-backpointers from 0)
1152 (setf (%array-fill-pointer from) 0
1153 (%array-available-elements from) 0
1154 (%array-displaced-p from) (array-dimensions array))
1155 (dotimes (i (%array-rank from))
1156 (setf (%array-dimension from i) 0))))))))
1158 ;;; Fill in array header with the provided information, and return the array.
1159 (defun set-array-header (array data length fill-pointer displacement dimensions
1162 (setf (%array-displaced-from array) nil)
1163 (%walk-displaced-array-backpointers array length))
1165 (%save-displaced-array-backpointer array data))
1166 (setf (%array-data-vector array) data)
1167 (setf (%array-available-elements array) length)
1169 (setf (%array-fill-pointer array) fill-pointer)
1170 (setf (%array-fill-pointer-p array) t))
1172 (setf (%array-fill-pointer array) length)
1173 (setf (%array-fill-pointer-p array) nil)))
1174 (setf (%array-displacement array) displacement)
1175 (if (listp dimensions)
1176 (dotimes (axis (array-rank array))
1177 (declare (type index axis))
1178 (setf (%array-dimension array axis) (pop dimensions)))
1179 (setf (%array-dimension array 0) dimensions))
1180 (setf (%array-displaced-p array) displacedp)
1183 ;;; User visible extension
1184 (declaim (ftype (function (array) (values (simple-array * (*)) &optional))
1185 array-storage-vector))
1186 (defun array-storage-vector (array)
1187 "Returns the underlying storage vector of ARRAY, which must be a non-displaced array.
1189 In SBCL, if ARRAY is a of type \(SIMPLE-ARRAY * \(*)), it is its own storage
1190 vector. Multidimensional arrays, arrays with fill pointers, and adjustable
1191 arrays have an underlying storage vector with the same ARRAY-ELEMENT-TYPE as
1192 ARRAY, which this function returns.
1194 Important note: the underlying vector is an implementation detail. Even though
1195 this function exposes it, changes in the implementation may cause this
1196 function to be removed without further warning."
1197 ;; KLUDGE: Without TRULY-THE the system is not smart enough to figure out that
1198 ;; the return value is always of the known type.
1199 (truly-the (simple-array * (*))
1200 (if (array-header-p array)
1201 (if (%array-displaced-p array)
1202 (error "~S cannot be used with displaced arrays. Use ~S instead."
1203 'array-storage-vector 'array-displacement)
1204 (%array-data-vector array))
1208 ;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY
1210 ;;; This does the grinding work for ADJUST-ARRAY. It zaps the data
1211 ;;; from the OLD-DATA in an arrangement specified by the OLD-DIMS to
1212 ;;; the NEW-DATA in an arrangement specified by the NEW-DIMS. OFFSET
1213 ;;; is a displaced offset to be added to computed indices of OLD-DATA.
1214 (defun zap-array-data (old-data old-dims offset new-data new-dims new-length
1215 element-type initial-element initial-element-p)
1216 (declare (list old-dims new-dims)
1217 (fixnum new-length))
1218 ;; OLD-DIMS comes from array-dimensions, which returns a fresh list
1219 ;; at least in SBCL.
1220 ;; NEW-DIMS comes from the user.
1221 (setf old-dims (nreverse old-dims)
1222 new-dims (reverse new-dims))
1223 (cond ((eq old-data new-data)
1224 ;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and
1225 ;; INITIAL-ELEMENT-P are used when OLD-DATA and NEW-DATA are
1226 ;; EQ; in this case, a temporary must be used and filled
1227 ;; appropriately. specified initial-element.
1228 (when initial-element-p
1229 ;; FIXME: transforming this TYPEP to someting a bit faster
1230 ;; would be a win...
1231 (unless (typep initial-element element-type)
1232 (error "~S can't be used to initialize an array of type ~S."
1233 initial-element element-type)))
1234 (let ((temp (if initial-element-p
1235 (make-array new-length :initial-element initial-element)
1236 (make-array new-length))))
1237 (declare (simple-vector temp))
1238 (zap-array-data-aux old-data old-dims offset temp new-dims)
1239 (dotimes (i new-length)
1240 (setf (aref new-data i) (aref temp i)))
1241 ;; Kill the temporary vector to prevent garbage retention.
1242 (%shrink-vector temp 0)))
1244 ;; When OLD-DATA and NEW-DATA are not EQ, NEW-DATA has
1245 ;; already been filled with any
1246 (zap-array-data-aux old-data old-dims offset new-data new-dims))))
1248 (defun zap-array-data-aux (old-data old-dims offset new-data new-dims)
1249 (declare (fixnum offset))
1250 (let ((limits (mapcar (lambda (x y)
1251 (declare (fixnum x y))
1252 (1- (the fixnum (min x y))))
1253 old-dims new-dims)))
1254 (macrolet ((bump-index-list (index limits)
1255 `(do ((subscripts ,index (cdr subscripts))
1256 (limits ,limits (cdr limits)))
1257 ((null subscripts) :eof)
1258 (cond ((< (the fixnum (car subscripts))
1259 (the fixnum (car limits)))
1261 (1+ (the fixnum (car subscripts))))
1263 (t (rplaca subscripts 0))))))
1264 (do ((index (make-list (length old-dims) :initial-element 0)
1265 (bump-index-list index limits)))
1267 (setf (aref new-data (row-major-index-from-dims index new-dims))
1269 (+ (the fixnum (row-major-index-from-dims index old-dims))
1272 ;;; Figure out the row-major-order index of an array reference from a
1273 ;;; list of subscripts and a list of dimensions. This is for internal
1274 ;;; calls only, and the subscripts and dim-list variables are assumed
1275 ;;; to be reversed from what the user supplied.
1276 (defun row-major-index-from-dims (rev-subscripts rev-dim-list)
1277 (do ((rev-subscripts rev-subscripts (cdr rev-subscripts))
1278 (rev-dim-list rev-dim-list (cdr rev-dim-list))
1281 ((null rev-dim-list) result)
1282 (declare (fixnum chunk-size result))
1283 (setq result (+ result
1284 (the fixnum (* (the fixnum (car rev-subscripts))
1286 (setq chunk-size (* chunk-size (the fixnum (car rev-dim-list))))))
1290 (defun bit-array-same-dimensions-p (array1 array2)
1291 (declare (type (array bit) array1 array2))
1292 (and (= (array-rank array1)
1293 (array-rank array2))
1294 (dotimes (index (array-rank array1) t)
1295 (when (/= (array-dimension array1 index)
1296 (array-dimension array2 index))
1299 (defun pick-result-array (result-bit-array bit-array-1)
1300 (case result-bit-array
1302 ((nil) (make-array (array-dimensions bit-array-1)
1304 :initial-element 0))
1306 (unless (bit-array-same-dimensions-p bit-array-1
1308 (error "~S and ~S don't have the same dimensions."
1309 bit-array-1 result-bit-array))
1312 (defmacro def-bit-array-op (name function)
1313 `(defun ,name (bit-array-1 bit-array-2 &optional result-bit-array)
1316 "Perform a bit-wise ~A on the elements of BIT-ARRAY-1 and ~
1317 BIT-ARRAY-2,~% putting the results in RESULT-BIT-ARRAY. ~
1318 If RESULT-BIT-ARRAY is T,~% BIT-ARRAY-1 is used. If ~
1319 RESULT-BIT-ARRAY is NIL or omitted, a new array is~% created. ~
1320 All the arrays must have the same rank and dimensions."
1321 (symbol-name function))
1322 (declare (type (array bit) bit-array-1 bit-array-2)
1323 (type (or (array bit) (member t nil)) result-bit-array))
1324 (unless (bit-array-same-dimensions-p bit-array-1 bit-array-2)
1325 (error "~S and ~S don't have the same dimensions."
1326 bit-array-1 bit-array-2))
1327 (let ((result-bit-array (pick-result-array result-bit-array bit-array-1)))
1328 (if (and (simple-bit-vector-p bit-array-1)
1329 (simple-bit-vector-p bit-array-2)
1330 (simple-bit-vector-p result-bit-array))
1331 (locally (declare (optimize (speed 3) (safety 0)))
1332 (,name bit-array-1 bit-array-2 result-bit-array))
1333 (with-array-data ((data1 bit-array-1) (start1) (end1))
1334 (declare (ignore end1))
1335 (with-array-data ((data2 bit-array-2) (start2) (end2))
1336 (declare (ignore end2))
1337 (with-array-data ((data3 result-bit-array) (start3) (end3))
1338 (do ((index-1 start1 (1+ index-1))
1339 (index-2 start2 (1+ index-2))
1340 (index-3 start3 (1+ index-3)))
1341 ((>= index-3 end3) result-bit-array)
1342 (declare (type index index-1 index-2 index-3))
1343 (setf (sbit data3 index-3)
1344 (logand (,function (sbit data1 index-1)
1345 (sbit data2 index-2))
1348 (def-bit-array-op bit-and logand)
1349 (def-bit-array-op bit-ior logior)
1350 (def-bit-array-op bit-xor logxor)
1351 (def-bit-array-op bit-eqv logeqv)
1352 (def-bit-array-op bit-nand lognand)
1353 (def-bit-array-op bit-nor lognor)
1354 (def-bit-array-op bit-andc1 logandc1)
1355 (def-bit-array-op bit-andc2 logandc2)
1356 (def-bit-array-op bit-orc1 logorc1)
1357 (def-bit-array-op bit-orc2 logorc2)
1359 (defun bit-not (bit-array &optional result-bit-array)
1361 "Performs a bit-wise logical NOT on the elements of BIT-ARRAY,
1362 putting the results in RESULT-BIT-ARRAY. If RESULT-BIT-ARRAY is T,
1363 BIT-ARRAY is used. If RESULT-BIT-ARRAY is NIL or omitted, a new array is
1364 created. Both arrays must have the same rank and dimensions."
1365 (declare (type (array bit) bit-array)
1366 (type (or (array bit) (member t nil)) result-bit-array))
1367 (let ((result-bit-array (pick-result-array result-bit-array bit-array)))
1368 (if (and (simple-bit-vector-p bit-array)
1369 (simple-bit-vector-p result-bit-array))
1370 (locally (declare (optimize (speed 3) (safety 0)))
1371 (bit-not bit-array result-bit-array))
1372 (with-array-data ((src bit-array) (src-start) (src-end))
1373 (declare (ignore src-end))
1374 (with-array-data ((dst result-bit-array) (dst-start) (dst-end))
1375 (do ((src-index src-start (1+ src-index))
1376 (dst-index dst-start (1+ dst-index)))
1377 ((>= dst-index dst-end) result-bit-array)
1378 (declare (type index src-index dst-index))
1379 (setf (sbit dst dst-index)
1380 (logxor (sbit src src-index) 1))))))))
1382 ;;;; array type dispatching
1384 ;;; Given DISPATCH-FOO as the DISPATCH-NAME argument (unevaluated),
1385 ;;; defines the functions
1387 ;;; DISPATCH-FOO/SIMPLE-BASE-STRING
1388 ;;; DISPATCH-FOO/SIMPLE-CHARACTER-STRING
1389 ;;; DISPATCH-FOO/SIMPLE-ARRAY-SINGLE-FLOAT
1392 ;;; PARAMS are the function parameters in the definition of each
1393 ;;; specializer function. The array being specialized must be the
1394 ;;; first parameter in PARAMS. A type declaration for this parameter
1395 ;;; is automatically inserted into the body of each function.
1397 ;;; The dispatch table %%FOO-FUNS%% is defined and populated by these
1398 ;;; functions. The table is padded by the function
1399 ;;; HAIRY-FOO-DISPATCH-ERROR, also defined by DEFINE-ARRAY-DISPATCH.
1401 ;;; Finally, the DISPATCH-FOO macro is defined which does the actual
1402 ;;; dispatching when called. It expects arguments that match PARAMS.
1404 (defmacro define-array-dispatch (dispatch-name params &body body)
1405 (let ((table-name (symbolicate "%%" dispatch-name "-FUNS%%"))
1406 (error-name (symbolicate "HAIRY-" dispatch-name "-ERROR")))
1408 (eval-when (:compile-toplevel :load-toplevel :execute)
1409 (defun ,error-name (&rest args)
1412 :expected-type '(simple-array * (*)))))
1413 (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)
1414 :initial-element #',error-name))
1415 ,@(loop for info across sb!vm:*specialized-array-element-type-properties*
1416 for typecode = (sb!vm:saetp-typecode info)
1417 for specifier = (sb!vm:saetp-specifier info)
1418 for primitive-type-name = (sb!vm:saetp-primitive-type-name info)
1419 collect (let ((fun-name (symbolicate (string dispatch-name)
1420 "/" primitive-type-name)))
1422 (defun ,fun-name ,params
1423 (declare (type (simple-array ,specifier (*))
1426 (setf (svref ,table-name ,typecode) #',fun-name))))
1427 (defmacro ,dispatch-name (&rest args)
1428 (check-type (first args) symbol)
1429 (let ((tag (gensym "TAG")))
1433 (when (sb!vm::%other-pointer-p ,(first args))
1434 (setf ,tag (%other-pointer-widetag ,(first args))))
1435 (svref ,',table-name ,tag)))