e367539fd3199b89f0611c5b59ee5590649bf5b6
[sbcl.git] / src / code / array.lisp
1 ;;;; functions to implement arrays
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!IMPL")
13
14 #!-sb-fluid
15 (declaim (inline adjustable-array-p
16                  array-displacement))
17 \f
18 ;;;; miscellaneous accessor functions
19
20 ;;; These functions are only needed by the interpreter, 'cause the
21 ;;; compiler inlines them.
22 (macrolet ((def (name)
23              `(progn
24                 (defun ,name (array)
25                   (,name array))
26                 (defun (setf ,name) (value array)
27                   (setf (,name array) value)))))
28   (def %array-fill-pointer)
29   (def %array-fill-pointer-p)
30   (def %array-available-elements)
31   (def %array-data-vector)
32   (def %array-displacement)
33   (def %array-displaced-p)
34   (def %array-diplaced-from))
35
36 (defun %array-rank (array)
37   (%array-rank array))
38
39 (defun %array-dimension (array axis)
40   (%array-dimension array axis))
41
42 (defun %set-array-dimension (array axis value)
43   (%set-array-dimension array axis value))
44
45 (defun %check-bound (array bound index)
46   (declare (type index bound)
47            (fixnum index))
48   (%check-bound array bound index))
49
50 (defun %with-array-data/fp (array start end)
51   (%with-array-data-macro array start end :check-bounds t :check-fill-pointer t))
52
53 (defun %with-array-data (array start end)
54   (%with-array-data-macro array start end :check-bounds t :check-fill-pointer nil))
55
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)))
62 \f
63 ;;;; MAKE-ARRAY
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)
68                               t
69                               `(subtypep ,type ',(car spec)))
70                          ,@(cdr spec)))
71                      specs))))
72
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)
81   (case type
82     ;; Pick off some easy common cases.
83     ;;
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.)
88     ((t)
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))
92     #!+sb-unicode
93     ((character)
94      (values #.sb!vm:simple-character-string-widetag #.sb!vm:n-word-bits))
95     ((bit)
96      (values #.sb!vm:simple-bit-vector-widetag 1))
97     ;; OK, we have to wade into SUBTYPEPing after all.
98     (t
99      (unless *type-system-initialized*
100        (bug "SUBTYPEP dispatch for MAKE-ARRAY before the type system is ready"))
101      #.`(pick-vector-type type
102          ,@(map 'list
103                 (lambda (saetp)
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*)))))
108
109 (defun %complex-vector-widetag (widetag)
110   (macrolet ((make-case ()
111                `(case widetag
112                   ,@(loop for saetp across sb!vm:*specialized-array-element-type-properties*
113                           for complex = (sb!vm:saetp-complex-typecode saetp)
114                           when complex
115                           collect (list (sb!vm:saetp-typecode saetp) complex))
116                   (t
117                    #.sb!vm:complex-vector-widetag))))
118     (make-case)))
119
120 (defglobal %%simple-array-n-bits%% (make-array (1+ sb!vm:widetag-mask)))
121 #.(loop for info across sb!vm:*specialized-array-element-type-properties*
122         collect `(setf (aref %%simple-array-n-bits%% ,(sb!vm:saetp-typecode info))
123                        ,(sb!vm:saetp-n-bits info)) into forms
124         finally (return `(progn ,@forms)))
125
126 (defun allocate-vector-with-widetag (widetag length &optional n-bits)
127   (declare (type (unsigned-byte 8) widetag)
128            (type index length))
129   (let ((n-bits (or n-bits (aref %%simple-array-n-bits%% widetag))))
130     (declare (type (integer 0 256) n-bits))
131     (allocate-vector widetag length
132                      (ceiling
133                       (* (if (or (= widetag sb!vm:simple-base-string-widetag)
134                                  #!+sb-unicode
135                                  (= widetag
136                                     sb!vm:simple-character-string-widetag))
137                              (1+ length)
138                              length)
139                          n-bits)
140                       sb!vm:n-word-bits))))
141
142 (defun array-underlying-widetag (array)
143   (macrolet ((make-case ()
144                `(case widetag
145                   ,@(loop for saetp across sb!vm:*specialized-array-element-type-properties*
146                           for complex = (sb!vm:saetp-complex-typecode saetp)
147                           when complex
148                           collect (list complex (sb!vm:saetp-typecode saetp)))
149                   ((,sb!vm:simple-array-widetag
150                     ,sb!vm:complex-vector-widetag
151                     ,sb!vm:complex-array-widetag)
152                    (with-array-data ((array array) (start) (end))
153                      (declare (ignore start end))
154                      (widetag-of array)))
155                   (t
156                    widetag))))
157     (let ((widetag (widetag-of array)))
158       (make-case))))
159
160 ;;; Widetag is the widetag of the underlying vector,
161 ;;; it'll be the same as the resulting array widetag only for simple vectors
162 (defun %make-array (dimensions widetag n-bits
163                     &key
164                       element-type
165                       (initial-element nil initial-element-p)
166                       (initial-contents nil initial-contents-p)
167                       adjustable fill-pointer
168                       displaced-to displaced-index-offset)
169   (declare (ignore element-type))
170   (let* ((dimensions (if (listp dimensions) dimensions (list dimensions)))
171          (array-rank (length (the list dimensions)))
172          (simple (and (null fill-pointer)
173                       (not adjustable)
174                       (null displaced-to))))
175     (declare (fixnum array-rank))
176     (cond ((and displaced-index-offset (null displaced-to))
177            (error "can't specify :DISPLACED-INDEX-OFFSET without :DISPLACED-TO"))
178           ((and simple (= array-rank 1))
179            ;; it's a (SIMPLE-ARRAY * (*))
180            (let* ((length (car dimensions))
181                   (array (allocate-vector-with-widetag widetag length n-bits)))
182              (declare (type index length))
183              (when initial-element-p
184                (fill array initial-element))
185              (when initial-contents-p
186                (when initial-element-p
187                  (error "can't specify both :INITIAL-ELEMENT and ~
188                        :INITIAL-CONTENTS"))
189                (unless (= length (length initial-contents))
190                  (error "There are ~W elements in the :INITIAL-CONTENTS, but ~
191                        the vector length is ~W."
192                         (length initial-contents)
193                         length))
194                (replace array initial-contents))
195              array))
196           ((and (arrayp displaced-to)
197                 (/= (array-underlying-widetag displaced-to) widetag))
198            (error "Array element type of :DISPLACED-TO array does not match specified element type"))
199           (t
200            ;; it's either a complex array or a multidimensional array.
201            (let* ((total-size (reduce #'* dimensions))
202                   (data (or displaced-to
203                             (data-vector-from-inits
204                              dimensions total-size nil widetag n-bits
205                              initial-contents initial-contents-p
206                              initial-element initial-element-p)))
207                   (array (make-array-header
208                           (cond ((= array-rank 1)
209                                  (%complex-vector-widetag widetag))
210                                 (simple sb!vm:simple-array-widetag)
211                                 (t sb!vm:complex-array-widetag))
212                           array-rank)))
213              (cond (fill-pointer
214                     (unless (= array-rank 1)
215                       (error "Only vectors can have fill pointers."))
216                     (let ((length (car dimensions)))
217                       (declare (fixnum length))
218                       (setf (%array-fill-pointer array)
219                             (cond ((eq fill-pointer t)
220                                    length)
221                                   (t
222                                    (unless (and (fixnump fill-pointer)
223                                                 (>= fill-pointer 0)
224                                                 (<= fill-pointer length))
225                                      ;; FIXME: should be TYPE-ERROR?
226                                      (error "invalid fill-pointer ~W"
227                                             fill-pointer))
228                                    fill-pointer))))
229                     (setf (%array-fill-pointer-p array) t))
230                    (t
231                     (setf (%array-fill-pointer array) total-size)
232                     (setf (%array-fill-pointer-p array) nil)))
233              (setf (%array-available-elements array) total-size)
234              (setf (%array-data-vector array) data)
235              (setf (%array-displaced-from array) nil)
236              (cond (displaced-to
237                     (when (or initial-element-p initial-contents-p)
238                       (error "Neither :INITIAL-ELEMENT nor :INITIAL-CONTENTS ~
239                    can be specified along with :DISPLACED-TO"))
240                     (let ((offset (or displaced-index-offset 0)))
241                       (when (> (+ offset total-size)
242                                (array-total-size displaced-to))
243                         (error "~S doesn't have enough elements." displaced-to))
244                       (setf (%array-displacement array) offset)
245                       (setf (%array-displaced-p array) t)
246                       (%save-displaced-array-backpointer array data)))
247                    (t
248                     (setf (%array-displaced-p array) nil)))
249              (let ((axis 0))
250                (dolist (dim dimensions)
251                  (setf (%array-dimension array axis) dim)
252                  (incf axis)))
253              array)))))
254
255 (defun make-array (dimensions &rest args
256                    &key (element-type t)
257                         initial-element initial-contents
258                         adjustable
259                         fill-pointer
260                         displaced-to
261                         displaced-index-offset)
262   (declare (ignore initial-element
263                    initial-contents adjustable
264                    fill-pointer displaced-to displaced-index-offset))
265   (multiple-value-bind (widetag n-bits) (%vector-widetag-and-n-bits element-type)
266     (apply #'%make-array dimensions widetag n-bits args)))
267
268 (defun make-static-vector (length &key
269                            (element-type '(unsigned-byte 8))
270                            (initial-contents nil initial-contents-p)
271                            (initial-element nil initial-element-p))
272   "Allocate vector of LENGTH elements in static space. Only allocation
273 of specialized arrays is supported."
274   ;; STEP 1: check inputs fully
275   ;;
276   ;; This way of doing explicit checks before the vector is allocated
277   ;; is expensive, but probably worth the trouble as once we've allocated
278   ;; the vector we have no way to get rid of it anymore...
279   (when (eq t (upgraded-array-element-type element-type))
280     (error "Static arrays of type ~S not supported."
281            element-type))
282   (when initial-contents-p
283     (when initial-element-p
284       (error "can't specify both :INITIAL-ELEMENT and :INITIAL-CONTENTS"))
285     (unless (= length (length initial-contents))
286       (error "There are ~W elements in the :INITIAL-CONTENTS, but the ~
287               vector length is ~W."
288              (length initial-contents)
289              length))
290     (unless (every (lambda (x) (typep x element-type)) initial-contents)
291       (error ":INITIAL-CONTENTS contains elements not of type ~S."
292              element-type)))
293   (when initial-element-p
294     (unless (typep initial-element element-type)
295       (error ":INITIAL-ELEMENT ~S is not of type ~S."
296              initial-element element-type)))
297   ;; STEP 2
298   ;;
299   ;; Allocate and possibly initialize the vector.
300   (multiple-value-bind (type n-bits)
301       (sb!impl::%vector-widetag-and-n-bits element-type)
302     (let ((vector
303            (allocate-static-vector type length
304                                    (ceiling (* length n-bits)
305                                             sb!vm:n-word-bits))))
306       (cond (initial-element-p
307              (fill vector initial-element))
308             (initial-contents-p
309              (replace vector initial-contents))
310             (t
311              vector)))))
312
313 ;;; DATA-VECTOR-FROM-INITS returns a simple vector that has the
314 ;;; specified array characteristics. Dimensions is only used to pass
315 ;;; to FILL-DATA-VECTOR for error checking on the structure of
316 ;;; initial-contents.
317 (defun data-vector-from-inits (dimensions total-size
318                                element-type widetag n-bits
319                                initial-contents initial-contents-p
320                                initial-element initial-element-p)
321   (when initial-element-p
322     (when initial-contents-p
323       (error "cannot supply both :INITIAL-CONTENTS and :INITIAL-ELEMENT to
324             either MAKE-ARRAY or ADJUST-ARRAY."))
325     ;; FIXME: element-type can be NIL when widetag is non-nil,
326     ;; and FILL will check the type, although the error will be not as nice.
327     ;; (cond (typep initial-element element-type)
328     ;;   (error "~S cannot be used to initialize an array of type ~S."
329     ;;          initial-element element-type))
330     )
331   (let ((data (if widetag
332                   (allocate-vector-with-widetag widetag total-size n-bits)
333                   (make-array total-size :element-type element-type))))
334     (cond (initial-element-p
335            (fill (the vector data) initial-element))
336           (initial-contents-p
337            (fill-data-vector data dimensions initial-contents)))
338     data))
339
340 (defun vector (&rest objects)
341   #!+sb-doc
342   "Construct a SIMPLE-VECTOR from the given objects."
343   (coerce (the list objects) 'simple-vector))
344 \f
345
346 ;;;; accessor/setter functions
347
348 ;;; Dispatch to an optimized routine the data vector accessors for
349 ;;; each different specialized vector type. Do dispatching by looking
350 ;;; up the widetag in the array rather than with the typecases, which
351 ;;; as of 1.0.5 compiles to a naive sequence of linear TYPEPs. Also
352 ;;; provide separate versions where bounds checking has been moved
353 ;;; from the callee to the caller, since it's much cheaper to do once
354 ;;; the type information is available. Finally, for each of these
355 ;;; routines also provide a slow path, taken for arrays that are not
356 ;;; vectors or not simple.
357 (macrolet ((def (name table-name)
358              `(progn
359                 (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)))
360                 (defmacro ,name (array-var)
361                   `(the function
362                      (let ((tag 0))
363                        (when (sb!vm::%other-pointer-p ,array-var)
364                          (setf tag (%other-pointer-widetag ,array-var)))
365                        (svref ,',table-name tag)))))))
366   (def !find-data-vector-setter %%data-vector-setters%%)
367   (def !find-data-vector-setter/check-bounds %%data-vector-setters/check-bounds%%)
368   ;; Used by DO-VECTOR-DATA -- which in turn appears in DOSEQUENCE expansion,
369   ;; meaning we can have post-build dependences on this.
370   (def %find-data-vector-reffer %%data-vector-reffers%%)
371   (def !find-data-vector-reffer/check-bounds %%data-vector-reffers/check-bounds%%))
372
373 ;;; Like DOVECTOR, but more magical -- can't use this on host.
374 (defmacro do-vector-data ((elt vector &optional result) &body body)
375   (multiple-value-bind (forms decls) (parse-body body :doc-string-allowed nil)
376     (with-unique-names (index vec start end ref)
377       `(with-array-data ((,vec ,vector)
378                          (,start)
379                          (,end)
380                          :check-fill-pointer t)
381          (let ((,ref (%find-data-vector-reffer ,vec)))
382            (do ((,index ,start (1+ ,index)))
383                ((>= ,index ,end)
384                 (let ((,elt nil))
385                   ,@(filter-dolist-declarations decls)
386                   ,elt
387                   ,result))
388              (let ((,elt (funcall ,ref ,vec ,index)))
389                ,@decls
390                (tagbody ,@forms))))))))
391
392 (macrolet ((%ref (accessor-getter extra-params)
393              `(funcall (,accessor-getter array) array index ,@extra-params))
394            (define (accessor-name slow-accessor-name accessor-getter
395                                   extra-params check-bounds)
396              `(progn
397                 (defun ,accessor-name (array index ,@extra-params)
398                   (declare (optimize speed
399                                      ;; (SAFETY 0) is ok. All calls to
400                                      ;; these functions are generated by
401                                      ;; the compiler, so argument count
402                                      ;; checking isn't needed. Type checking
403                                      ;; is done implicitly via the widetag
404                                      ;; dispatch.
405                                      (safety 0)))
406                   (%ref ,accessor-getter ,extra-params))
407                 (defun ,slow-accessor-name (array index ,@extra-params)
408                   (declare (optimize speed (safety 0)))
409                   (if (not (%array-displaced-p array))
410                       ;; The reasonably quick path of non-displaced complex
411                       ;; arrays.
412                       (let ((array (%array-data-vector array)))
413                         (%ref ,accessor-getter ,extra-params))
414                       ;; The real slow path.
415                       (with-array-data
416                           ((vector array)
417                            (index (locally
418                                       (declare (optimize (speed 1) (safety 1)))
419                                     (,@check-bounds index)))
420                            (end)
421                            :force-inline t)
422                         (declare (ignore end))
423                         (,accessor-name vector index ,@extra-params)))))))
424   (define hairy-data-vector-ref slow-hairy-data-vector-ref
425     %find-data-vector-reffer
426     nil (progn))
427   (define hairy-data-vector-set slow-hairy-data-vector-set
428     !find-data-vector-setter
429     (new-value) (progn))
430   (define hairy-data-vector-ref/check-bounds
431       slow-hairy-data-vector-ref/check-bounds
432     !find-data-vector-reffer/check-bounds
433     nil (%check-bound array (array-dimension array 0)))
434   (define hairy-data-vector-set/check-bounds
435       slow-hairy-data-vector-set/check-bounds
436     !find-data-vector-setter/check-bounds
437     (new-value) (%check-bound array (array-dimension array 0))))
438
439 (defun hairy-ref-error (array index &optional new-value)
440   (declare (ignore index new-value))
441   (error 'type-error
442          :datum array
443          :expected-type 'vector))
444
445 (macrolet ((define-reffer (saetp check-form)
446              (let* ((type (sb!vm:saetp-specifier saetp))
447                     (atype `(simple-array ,type (*))))
448                `(named-lambda optimized-data-vector-ref (vector index)
449                   (declare (optimize speed (safety 0)))
450                   (data-vector-ref (the ,atype vector)
451                                    (locally
452                                        (declare (optimize (safety 1)))
453                                      (the index
454                                        (,@check-form index)))))))
455            (define-setter (saetp check-form)
456              (let* ((type (sb!vm:saetp-specifier saetp))
457                     (atype `(simple-array ,type (*))))
458                `(named-lambda optimized-data-vector-set (vector index new-value)
459                   (declare (optimize speed (safety 0)))
460                   (data-vector-set (the ,atype vector)
461                                    (locally
462                                        (declare (optimize (safety 1)))
463                                      (the index
464                                        (,@check-form index)))
465                                    (locally
466                                        ;; SPEED 1 needed to avoid the compiler
467                                        ;; from downgrading the type check to
468                                        ;; a cheaper one.
469                                        (declare (optimize (speed 1)
470                                                           (safety 1)))
471                                      (the ,type new-value)))
472                   ;; For specialized arrays, the return from
473                   ;; data-vector-set would have to be reboxed to be a
474                   ;; (Lisp) return value; instead, we use the
475                   ;; already-boxed value as the return.
476                   new-value)))
477            (define-reffers (symbol deffer check-form slow-path)
478              `(progn
479                 ;; FIXME/KLUDGE: can't just FILL here, because genesis doesn't
480                 ;; preserve the binding, so re-initiaize as NS doesn't have
481                 ;; the energy to figure out to change that right now.
482                 (setf ,symbol (make-array (1+ sb!vm::widetag-mask)
483                                           :initial-element #'hairy-ref-error))
484                 ,@(loop for widetag in '(sb!vm:complex-vector-widetag
485                                          sb!vm:complex-vector-nil-widetag
486                                          sb!vm:complex-bit-vector-widetag
487                                          #!+sb-unicode sb!vm:complex-character-string-widetag
488                                          sb!vm:complex-base-string-widetag
489                                          sb!vm:simple-array-widetag
490                                          sb!vm:complex-array-widetag)
491                         collect `(setf (svref ,symbol ,widetag) ,slow-path))
492                 ,@(loop for saetp across sb!vm:*specialized-array-element-type-properties*
493                         for widetag = (sb!vm:saetp-typecode saetp)
494                         collect `(setf (svref ,symbol ,widetag)
495                                        (,deffer ,saetp ,check-form))))))
496   (defun !hairy-data-vector-reffer-init ()
497     (define-reffers %%data-vector-reffers%% define-reffer
498       (progn)
499       #'slow-hairy-data-vector-ref)
500     (define-reffers %%data-vector-setters%% define-setter
501       (progn)
502       #'slow-hairy-data-vector-set)
503     (define-reffers %%data-vector-reffers/check-bounds%% define-reffer
504       (%check-bound vector (length vector))
505       #'slow-hairy-data-vector-ref/check-bounds)
506     (define-reffers %%data-vector-setters/check-bounds%% define-setter
507       (%check-bound vector (length vector))
508       #'slow-hairy-data-vector-set/check-bounds)))
509
510 ;;; (Ordinary DATA-VECTOR-REF usage compiles into a vop, but
511 ;;; DATA-VECTOR-REF is also FOLDABLE, and this ordinary function
512 ;;; definition is needed for the compiler to use in constant folding.)
513 (defun data-vector-ref (array index)
514   (hairy-data-vector-ref array index))
515
516 (defun data-vector-ref-with-offset (array index offset)
517   (hairy-data-vector-ref array (+ index offset)))
518
519 (defun invalid-array-p (array)
520   (and (array-header-p array)
521        (consp (%array-displaced-p array))))
522
523 (declaim (ftype (function (array) nil) invalid-array-error))
524 (defun invalid-array-error (array)
525   (aver (array-header-p array))
526   ;; Array invalidation stashes the original dimensions here...
527   (let ((dims (%array-displaced-p array))
528         (et (array-element-type array)))
529     (error 'invalid-array-error
530            :datum array
531            :expected-type
532            (if (cdr dims)
533                `(array ,et ,dims)
534                `(vector ,et ,@dims)))))
535
536 (declaim (ftype (function (array integer integer &optional t) nil)
537                 invalid-array-index-error))
538 (defun invalid-array-index-error (array index bound &optional axis)
539   (if (invalid-array-p array)
540       (invalid-array-error array)
541       (error 'invalid-array-index-error
542              :array array
543              :axis axis
544              :datum index
545              :expected-type `(integer 0 (,bound)))))
546
547 ;;; SUBSCRIPTS has a dynamic-extent list structure and is destroyed
548 (defun %array-row-major-index (array subscripts
549                                      &optional (invalid-index-error-p t))
550   (declare (array array)
551            (list subscripts))
552   (let ((rank (array-rank array)))
553     (unless (= rank (length subscripts))
554       (error "wrong number of subscripts, ~W, for array of rank ~W"
555              (length subscripts) rank))
556     (if (array-header-p array)
557         (do ((subs (nreverse subscripts) (cdr subs))
558              (axis (1- (array-rank array)) (1- axis))
559              (chunk-size 1)
560              (result 0))
561             ((null subs) result)
562           (declare (list subs) (fixnum axis chunk-size result))
563           (let ((index (car subs))
564                 (dim (%array-dimension array axis)))
565             (declare (fixnum dim))
566             (unless (and (fixnump index) (< -1 index dim))
567               (if invalid-index-error-p
568                   (invalid-array-index-error array index dim axis)
569                   (return-from %array-row-major-index nil)))
570             (incf result (* chunk-size (the fixnum index)))
571             (setf chunk-size (* chunk-size dim))))
572         (let ((index (first subscripts))
573               (length (length (the (simple-array * (*)) array))))
574           (unless (and (fixnump index) (< -1 index length))
575             (if invalid-index-error-p
576                 (invalid-array-index-error array index length)
577                 (return-from %array-row-major-index nil)))
578           index))))
579
580 (defun array-in-bounds-p (array &rest subscripts)
581   #!+sb-doc
582   "Return T if the SUBSCRIPTS are in bounds for the ARRAY, NIL otherwise."
583   (if (%array-row-major-index array subscripts nil)
584       t))
585
586 (defun array-row-major-index (array &rest subscripts)
587   (declare (truly-dynamic-extent subscripts))
588   (%array-row-major-index array subscripts))
589
590 (defun aref (array &rest subscripts)
591   #!+sb-doc
592   "Return the element of the ARRAY specified by the SUBSCRIPTS."
593   (declare (truly-dynamic-extent subscripts))
594   (row-major-aref array (%array-row-major-index array subscripts)))
595
596 ;;; (setf aref/bit/sbit) are implemented using setf-functions,
597 ;;; because they have to work with (setf (apply #'aref array subscripts))
598 ;;; All other setfs can be done using setf-functions too, but I
599 ;;; haven't found technical advantages or disatvantages for either
600 ;;; scheme.
601 (defun (setf aref) (new-value array &rest subscripts)
602   (declare (truly-dynamic-extent subscripts)
603            (type array array))
604   (setf (row-major-aref array (%array-row-major-index array subscripts))
605         new-value))
606
607 (defun row-major-aref (array index)
608   #!+sb-doc
609   "Return the element of array corresponding to the row-major index. This is
610    SETFable."
611   (declare (optimize (safety 1)))
612   (row-major-aref array index))
613
614 (defun %set-row-major-aref (array index new-value)
615   (declare (optimize (safety 1)))
616   (setf (row-major-aref array index) new-value))
617
618 (defun svref (simple-vector index)
619   #!+sb-doc
620   "Return the INDEXth element of the given Simple-Vector."
621   (declare (optimize (safety 1)))
622   (aref simple-vector index))
623
624 (defun %svset (simple-vector index new)
625   (declare (optimize (safety 1)))
626   (setf (aref simple-vector index) new))
627
628 (defun bit (bit-array &rest subscripts)
629   #!+sb-doc
630   "Return the bit from the BIT-ARRAY at the specified SUBSCRIPTS."
631   (declare (type (array bit) bit-array)
632            (optimize (safety 1)))
633   (row-major-aref bit-array (%array-row-major-index bit-array subscripts)))
634
635 (defun (setf bit) (new-value bit-array &rest subscripts)
636   (declare (type (array bit) bit-array)
637            (type bit new-value)
638            (optimize (safety 1)))
639   (setf (row-major-aref bit-array
640                         (%array-row-major-index bit-array subscripts))
641         new-value))
642
643 (defun sbit (simple-bit-array &rest subscripts)
644   #!+sb-doc
645   "Return the bit from SIMPLE-BIT-ARRAY at the specified SUBSCRIPTS."
646   (declare (type (simple-array bit) simple-bit-array)
647            (optimize (safety 1)))
648   (row-major-aref simple-bit-array
649                   (%array-row-major-index simple-bit-array subscripts)))
650
651 (defun (setf sbit) (new-value bit-array &rest subscripts)
652   (declare (type (simple-array bit) bit-array)
653            (type bit new-value)
654            (optimize (safety 1)))
655   (setf (row-major-aref bit-array
656                         (%array-row-major-index bit-array subscripts))
657         new-value))
658 \f
659 ;;;; miscellaneous array properties
660
661 (defun array-element-type (array)
662   #!+sb-doc
663   "Return the type of the elements of the array"
664   (let ((widetag (widetag-of array)))
665     (macrolet ((pick-element-type (&rest stuff)
666                  `(cond ,@(mapcar (lambda (stuff)
667                                     (cons
668                                      (let ((item (car stuff)))
669                                        (cond ((eq item t)
670                                               t)
671                                              ((listp item)
672                                               (cons 'or
673                                                     (mapcar (lambda (x)
674                                                               `(= widetag ,x))
675                                                             item)))
676                                              (t
677                                               `(= widetag ,item))))
678                                      (cdr stuff)))
679                                   stuff))))
680       #.`(pick-element-type
681           ,@(map 'list
682                  (lambda (saetp)
683                    `(,(if (sb!vm:saetp-complex-typecode saetp)
684                           (list (sb!vm:saetp-typecode saetp)
685                                 (sb!vm:saetp-complex-typecode saetp))
686                           (sb!vm:saetp-typecode saetp))
687                      ',(sb!vm:saetp-specifier saetp)))
688                  sb!vm:*specialized-array-element-type-properties*)
689           ((sb!vm:simple-array-widetag
690             sb!vm:complex-vector-widetag
691             sb!vm:complex-array-widetag)
692            (with-array-data ((array array) (start) (end))
693              (declare (ignore start end))
694              (array-element-type array)))
695           (t
696            (error 'type-error :datum array :expected-type 'array))))))
697
698 (defun array-rank (array)
699   #!+sb-doc
700   "Return the number of dimensions of ARRAY."
701   (if (array-header-p array)
702       (%array-rank array)
703       1))
704
705 (defun array-dimension (array axis-number)
706   #!+sb-doc
707   "Return the length of dimension AXIS-NUMBER of ARRAY."
708   (declare (array array) (type index axis-number))
709   (cond ((not (array-header-p array))
710          (unless (= axis-number 0)
711            (error "Vector axis is not zero: ~S" axis-number))
712          (length (the (simple-array * (*)) array)))
713         ((>= axis-number (%array-rank array))
714          (error "Axis number ~W is too big; ~S only has ~D dimension~:P."
715                 axis-number array (%array-rank array)))
716         (t
717          (%array-dimension array axis-number))))
718
719 (defun array-dimensions (array)
720   #!+sb-doc
721   "Return a list whose elements are the dimensions of the array"
722   (declare (array array))
723   (if (array-header-p array)
724       (do ((results nil (cons (array-dimension array index) results))
725            (index (1- (array-rank array)) (1- index)))
726           ((minusp index) results))
727       (list (array-dimension array 0))))
728
729 (defun array-total-size (array)
730   #!+sb-doc
731   "Return the total number of elements in the Array."
732   (declare (array array))
733   (if (array-header-p array)
734       (%array-available-elements array)
735       (length (the vector array))))
736
737 (defun array-displacement (array)
738   #!+sb-doc
739   "Return the values of :DISPLACED-TO and :DISPLACED-INDEX-offset
740    options to MAKE-ARRAY, or NIL and 0 if not a displaced array."
741   (declare (type array array))
742   (if (and (array-header-p array) ; if unsimple and
743            (%array-displaced-p array)) ; displaced
744       (values (%array-data-vector array) (%array-displacement array))
745       (values nil 0)))
746
747 (defun adjustable-array-p (array)
748   #!+sb-doc
749   "Return T if (ADJUST-ARRAY ARRAY...) would return an array identical
750    to the argument, this happens for complex arrays."
751   (declare (array array))
752   ;; Note that this appears not to be a fundamental limitation.
753   ;; non-vector SIMPLE-ARRAYs are in fact capable of being adjusted,
754   ;; but in practice we test using ADJUSTABLE-ARRAY-P in ADJUST-ARRAY.
755   ;; -- CSR, 2004-03-01.
756   (not (typep array 'simple-array)))
757 \f
758 ;;;; fill pointer frobbing stuff
759
760 (declaim (inline array-has-fill-pointer-p))
761 (defun array-has-fill-pointer-p (array)
762   #!+sb-doc
763   "Return T if the given ARRAY has a fill pointer, or NIL otherwise."
764   (declare (array array))
765   (and (array-header-p array) (%array-fill-pointer-p array)))
766
767 (defun fill-pointer-error (vector arg)
768   (cond (arg
769          (aver (array-has-fill-pointer-p vector))
770          (let ((max (%array-available-elements vector)))
771            (error 'simple-type-error
772                   :datum arg
773                   :expected-type (list 'integer 0 max)
774                   :format-control "The new fill pointer, ~S, is larger than the length of the vector (~S.)"
775                   :format-arguments (list arg max))))
776         (t
777          (error 'simple-type-error
778                 :datum vector
779                 :expected-type '(and vector (satisfies array-has-fill-pointer-p))
780                 :format-control "~S is not an array with a fill pointer."
781                 :format-arguments (list vector)))))
782
783 (declaim (inline fill-pointer))
784 (defun fill-pointer (vector)
785   #!+sb-doc
786   "Return the FILL-POINTER of the given VECTOR."
787   (if (array-has-fill-pointer-p vector)
788       (%array-fill-pointer vector)
789       (fill-pointer-error vector nil)))
790
791 (defun %set-fill-pointer (vector new)
792   (flet ((oops (x)
793            (fill-pointer-error vector x)))
794     (if (array-has-fill-pointer-p vector)
795         (if (> new (%array-available-elements vector))
796             (oops new)
797             (setf (%array-fill-pointer vector) new))
798         (oops nil))))
799
800 ;;; FIXME: It'd probably make sense to use a MACROLET to share the
801 ;;; guts of VECTOR-PUSH between VECTOR-PUSH-EXTEND. Such a macro
802 ;;; should probably be based on the VECTOR-PUSH-EXTEND code (which is
803 ;;; new ca. sbcl-0.7.0) rather than the VECTOR-PUSH code (which dates
804 ;;; back to CMU CL).
805 (defun vector-push (new-element array)
806   #!+sb-doc
807   "Attempt to set the element of ARRAY designated by its fill pointer
808    to NEW-ELEMENT, and increment the fill pointer by one. If the fill pointer is
809    too large, NIL is returned, otherwise the index of the pushed element is
810    returned."
811   (let ((fill-pointer (fill-pointer array)))
812     (declare (fixnum fill-pointer))
813     (cond ((= fill-pointer (%array-available-elements array))
814            nil)
815           (t
816            (locally (declare (optimize (safety 0)))
817              (setf (aref array fill-pointer) new-element))
818            (setf (%array-fill-pointer array) (1+ fill-pointer))
819            fill-pointer))))
820
821 (defun vector-push-extend (new-element vector &optional min-extension)
822   (declare (type (or null fixnum) min-extension))
823   (let ((fill-pointer (fill-pointer vector)))
824     (declare (fixnum fill-pointer))
825     (when (= fill-pointer (%array-available-elements vector))
826       (let ((min-extension
827              (or min-extension
828                  (let ((length (length vector)))
829                    (min (1+ length)
830                         (- array-dimension-limit length))))))
831         (adjust-array vector (+ fill-pointer (max 1 min-extension)))))
832     ;; disable bounds checking
833     (locally (declare (optimize (safety 0)))
834       (setf (aref vector fill-pointer) new-element))
835     (setf (%array-fill-pointer vector) (1+ fill-pointer))
836     fill-pointer))
837
838 (defun vector-pop (array)
839   #!+sb-doc
840   "Decrease the fill pointer by 1 and return the element pointed to by the
841   new fill pointer."
842   (let ((fill-pointer (fill-pointer array)))
843     (declare (fixnum fill-pointer))
844     (if (zerop fill-pointer)
845         (error "There is nothing left to pop.")
846         ;; disable bounds checking (and any fixnum test)
847         (locally (declare (optimize (safety 0)))
848           (aref array
849                 (setf (%array-fill-pointer array)
850                       (1- fill-pointer)))))))
851
852 \f
853 ;;;; ADJUST-ARRAY
854
855 (defun adjust-array (array dimensions &key
856                            (element-type (array-element-type array) element-type-p)
857                            (initial-element nil initial-element-p)
858                            (initial-contents nil initial-contents-p)
859                            fill-pointer
860                            displaced-to displaced-index-offset)
861   #!+sb-doc
862   "Adjust ARRAY's dimensions to the given DIMENSIONS and stuff."
863   (when (invalid-array-p array)
864     (invalid-array-error array))
865   (let ((dimensions (if (listp dimensions) dimensions (list dimensions))))
866     (cond ((/= (the fixnum (length (the list dimensions)))
867                (the fixnum (array-rank array)))
868            (error "The number of dimensions not equal to rank of array."))
869           ((and element-type-p
870                 (not (subtypep element-type (array-element-type array))))
871            (error "The new element type, ~S, is incompatible with old type."
872                   element-type))
873           ((and fill-pointer (not (array-has-fill-pointer-p array)))
874            (error 'type-error
875                   :datum array
876                   :expected-type '(satisfies array-has-fill-pointer-p))))
877     (let ((array-rank (length (the list dimensions))))
878       (declare (fixnum array-rank))
879       (unless (= array-rank 1)
880         (when fill-pointer
881           (error "Only vectors can have fill pointers.")))
882       (cond (initial-contents-p
883              ;; array former contents replaced by INITIAL-CONTENTS
884              (if (or initial-element-p displaced-to)
885                  (error ":INITIAL-CONTENTS may not be specified with ~
886                          the :INITIAL-ELEMENT or :DISPLACED-TO option."))
887              (let* ((array-size (apply #'* dimensions))
888                     (array-data (data-vector-from-inits
889                                  dimensions array-size element-type nil nil
890                                  initial-contents initial-contents-p
891                                  initial-element initial-element-p)))
892                (if (adjustable-array-p array)
893                    (set-array-header array array-data array-size
894                                  (get-new-fill-pointer array array-size
895                                                        fill-pointer)
896                                  0 dimensions nil nil)
897                    (if (array-header-p array)
898                        ;; simple multidimensional or single dimensional array
899                        (make-array dimensions
900                                    :element-type element-type
901                                    :initial-contents initial-contents)
902                        array-data))))
903             (displaced-to
904              ;; We already established that no INITIAL-CONTENTS was supplied.
905              (when initial-element
906                (error "The :INITIAL-ELEMENT option may not be specified ~
907                        with :DISPLACED-TO."))
908              (unless (subtypep element-type (array-element-type displaced-to))
909                (error "can't displace an array of type ~S into another of ~
910                        type ~S"
911                       element-type (array-element-type displaced-to)))
912              (let ((displacement (or displaced-index-offset 0))
913                    (array-size (apply #'* dimensions)))
914                (declare (fixnum displacement array-size))
915                (if (< (the fixnum (array-total-size displaced-to))
916                       (the fixnum (+ displacement array-size)))
917                    (error "The :DISPLACED-TO array is too small."))
918                (if (adjustable-array-p array)
919                    ;; None of the original contents appear in adjusted array.
920                    (set-array-header array displaced-to array-size
921                                      (get-new-fill-pointer array array-size
922                                                            fill-pointer)
923                                      displacement dimensions t nil)
924                    ;; simple multidimensional or single dimensional array
925                    (make-array dimensions
926                                :element-type element-type
927                                :displaced-to displaced-to
928                                :displaced-index-offset
929                                displaced-index-offset))))
930             ((= array-rank 1)
931              (let ((old-length (array-total-size array))
932                    (new-length (car dimensions))
933                    new-data)
934                (declare (fixnum old-length new-length))
935                (with-array-data ((old-data array) (old-start)
936                                  (old-end old-length))
937                  (cond ((or (and (array-header-p array)
938                                  (%array-displaced-p array))
939                             (< old-length new-length))
940                         (setf new-data
941                               (data-vector-from-inits
942                                dimensions new-length element-type
943                                (widetag-of old-data) nil
944                                initial-contents initial-contents-p
945                                initial-element initial-element-p))
946                         ;; Provide :END1 to avoid full call to LENGTH
947                         ;; inside REPLACE.
948                         (replace new-data old-data
949                                  :end1 new-length
950                                  :start2 old-start :end2 old-end))
951                        (t (setf new-data
952                                 (shrink-vector old-data new-length))))
953                  (if (adjustable-array-p array)
954                      (set-array-header array new-data new-length
955                                        (get-new-fill-pointer array new-length
956                                                              fill-pointer)
957                                        0 dimensions nil nil)
958                      new-data))))
959             (t
960              (let ((old-length (%array-available-elements array))
961                    (new-length (apply #'* dimensions)))
962                (declare (fixnum old-length new-length))
963                (with-array-data ((old-data array) (old-start)
964                                  (old-end old-length))
965                  (declare (ignore old-end))
966                  (let ((new-data (if (or (and (array-header-p array)
967                                               (%array-displaced-p array))
968                                          (> new-length old-length))
969                                      (data-vector-from-inits
970                                       dimensions new-length
971                                       element-type
972                                       (widetag-of old-data) nil
973                                       () nil
974                                       initial-element initial-element-p)
975                                      old-data)))
976                    (if (or (zerop old-length) (zerop new-length))
977                        (when initial-element-p (fill new-data initial-element))
978                        (zap-array-data old-data (array-dimensions array)
979                                        old-start
980                                        new-data dimensions new-length
981                                        element-type initial-element
982                                        initial-element-p))
983                    (if (adjustable-array-p array)
984                        (set-array-header array new-data new-length
985                                          nil 0 dimensions nil nil)
986                        (let ((new-array
987                               (make-array-header
988                                sb!vm:simple-array-widetag array-rank)))
989                          (set-array-header new-array new-data new-length
990                                            nil 0 dimensions nil t)))))))))))
991
992
993 (defun get-new-fill-pointer (old-array new-array-size fill-pointer)
994   (cond ((not fill-pointer)
995          (when (array-has-fill-pointer-p old-array)
996            (when (> (%array-fill-pointer old-array) new-array-size)
997              (error "cannot ADJUST-ARRAY an array (~S) to a size (~S) that is ~
998                      smaller than its fill pointer (~S)"
999                     old-array new-array-size (fill-pointer old-array)))
1000            (%array-fill-pointer old-array)))
1001         ((not (array-has-fill-pointer-p old-array))
1002          (error "cannot supply a non-NIL value (~S) for :FILL-POINTER ~
1003                  in ADJUST-ARRAY unless the array (~S) was originally ~
1004                  created with a fill pointer"
1005                 fill-pointer
1006                 old-array))
1007         ((numberp fill-pointer)
1008          (when (> fill-pointer new-array-size)
1009            (error "can't supply a value for :FILL-POINTER (~S) that is larger ~
1010                    than the new length of the vector (~S)"
1011                   fill-pointer new-array-size))
1012          fill-pointer)
1013         ((eq fill-pointer t)
1014          new-array-size)
1015         (t
1016          (error "bogus value for :FILL-POINTER in ADJUST-ARRAY: ~S"
1017                 fill-pointer))))
1018
1019 ;;; Destructively alter VECTOR, changing its length to NEW-LENGTH,
1020 ;;; which must be less than or equal to its current length. This can
1021 ;;; be called on vectors without a fill pointer but it is extremely
1022 ;;; dangerous to do so: shrinking the size of an object (as viewed by
1023 ;;; the gc) makes bounds checking unreliable in the face of interrupts
1024 ;;; or multi-threading. Call it only on provably local vectors.
1025 (defun %shrink-vector (vector new-length)
1026   (declare (vector vector))
1027   (unless (array-header-p vector)
1028     (macrolet ((frob (name &rest things)
1029                  `(etypecase ,name
1030                     ((simple-array nil (*)) (error 'nil-array-accessed-error))
1031                     ,@(mapcar (lambda (thing)
1032                                 (destructuring-bind (type-spec fill-value)
1033                                     thing
1034                                   `(,type-spec
1035                                     (fill (truly-the ,type-spec ,name)
1036                                           ,fill-value
1037                                           :start new-length))))
1038                               things))))
1039       ;; Set the 'tail' of the vector to the appropriate type of zero,
1040       ;; "because in some cases we'll scavenge larger areas in one go,
1041       ;; like groups of pages that had triggered the write barrier, or
1042       ;; the whole static space" according to jsnell.
1043       #.`(frob vector
1044           ,@(map 'list
1045                  (lambda (saetp)
1046                    `((simple-array ,(sb!vm:saetp-specifier saetp) (*))
1047                      ,(if (or (eq (sb!vm:saetp-specifier saetp) 'character)
1048                               #!+sb-unicode
1049                               (eq (sb!vm:saetp-specifier saetp) 'base-char))
1050                           *default-init-char-form*
1051                           (sb!vm:saetp-initial-element-default saetp))))
1052                  (remove-if-not
1053                   #'sb!vm:saetp-specifier
1054                   sb!vm:*specialized-array-element-type-properties*)))))
1055   ;; Only arrays have fill-pointers, but vectors have their length
1056   ;; parameter in the same place.
1057   (setf (%array-fill-pointer vector) new-length)
1058   vector)
1059
1060 (defun shrink-vector (vector new-length)
1061   (declare (vector vector))
1062   (cond
1063     ((eq (length vector) new-length)
1064      vector)
1065     ((array-has-fill-pointer-p vector)
1066      (setf (%array-fill-pointer vector) new-length)
1067      vector)
1068     (t (subseq vector 0 new-length))))
1069
1070 ;;; BIG THREAD SAFETY NOTE
1071 ;;;
1072 ;;; ADJUST-ARRAY/SET-ARRAY-HEADER, and its callees are very
1073 ;;; thread unsafe. They are nonatomic, and can mess with parallel
1074 ;;; code using the same arrays.
1075 ;;;
1076 ;;; A likely seeming fix is an additional level of indirection:
1077 ;;; ARRAY-HEADER -> ARRAY-INFO -> ... where ARRAY-HEADER would
1078 ;;; hold nothing but the pointer to ARRAY-INFO, and ARRAY-INFO
1079 ;;; would hold everything ARRAY-HEADER now holds. This allows
1080 ;;; consing up a new ARRAY-INFO and replacing it atomically in
1081 ;;; the ARRAY-HEADER.
1082 ;;;
1083 ;;; %WALK-DISPLACED-ARRAY-BACKPOINTERS is an especially nasty
1084 ;;; one: not only is it needed extremely rarely, which makes
1085 ;;; any thread safety bugs involving it look like rare random
1086 ;;; corruption, but because it walks the chain *upwards*, which
1087 ;;; may violate user expectations.
1088
1089 (defun %save-displaced-array-backpointer (array data)
1090   (flet ((purge (pointers)
1091            (remove-if (lambda (value)
1092                         (or (not value) (eq array value)))
1093                       pointers
1094                       :key #'weak-pointer-value)))
1095     ;; Add backpointer to the new data vector if it has a header.
1096     (when (array-header-p data)
1097       (setf (%array-displaced-from data)
1098             (cons (make-weak-pointer array)
1099                   (purge (%array-displaced-from data)))))
1100     ;; Remove old backpointer, if any.
1101     (let ((old-data (%array-data-vector array)))
1102       (when (and (neq data old-data) (array-header-p old-data))
1103         (setf (%array-displaced-from old-data)
1104               (purge (%array-displaced-from old-data)))))))
1105
1106 (defun %walk-displaced-array-backpointers (array new-length)
1107   (dolist (p (%array-displaced-from array))
1108     (let ((from (weak-pointer-value p)))
1109       (when (and from (eq array (%array-data-vector from)))
1110         (let ((requires (+ (%array-available-elements from)
1111                            (%array-displacement from))))
1112           (unless (>= new-length requires)
1113             ;; ANSI sayeth (ADJUST-ARRAY dictionary entry):
1114             ;;
1115             ;;   "If A is displaced to B, the consequences are unspecified if B is
1116             ;;   adjusted in such a way that it no longer has enough elements to
1117             ;;   satisfy A.
1118             ;;
1119             ;; since we're hanging on a weak pointer here, we can't signal an
1120             ;; error right now: the array that we're looking at might be
1121             ;; garbage. Instead, we set all dimensions to zero so that next
1122             ;; safe access to the displaced array will trap. Additionally, we
1123             ;; save the original dimensions, so we can signal a more
1124             ;; understandable error when the time comes.
1125             (%walk-displaced-array-backpointers from 0)
1126             (setf (%array-fill-pointer from) 0
1127                   (%array-available-elements from) 0
1128                   (%array-displaced-p from) (array-dimensions array))
1129             (dotimes (i (%array-rank from))
1130               (setf (%array-dimension from i) 0))))))))
1131
1132 ;;; Fill in array header with the provided information, and return the array.
1133 (defun set-array-header (array data length fill-pointer displacement dimensions
1134                          displacedp newp)
1135   (if newp
1136       (setf (%array-displaced-from array) nil)
1137       (%walk-displaced-array-backpointers array length))
1138   (when displacedp
1139     (%save-displaced-array-backpointer array data))
1140   (setf (%array-data-vector array) data)
1141   (setf (%array-available-elements array) length)
1142   (cond (fill-pointer
1143          (setf (%array-fill-pointer array) fill-pointer)
1144          (setf (%array-fill-pointer-p array) t))
1145         (t
1146          (setf (%array-fill-pointer array) length)
1147          (setf (%array-fill-pointer-p array) nil)))
1148   (setf (%array-displacement array) displacement)
1149   (if (listp dimensions)
1150       (dotimes (axis (array-rank array))
1151         (declare (type index axis))
1152         (setf (%array-dimension array axis) (pop dimensions)))
1153       (setf (%array-dimension array 0) dimensions))
1154   (setf (%array-displaced-p array) displacedp)
1155   array)
1156
1157 ;;; User visible extension
1158 (declaim (ftype (function (array) (values (simple-array * (*)) &optional))
1159                 array-storage-vector))
1160 (defun array-storage-vector (array)
1161   "Returns the underlying storage vector of ARRAY, which must be a non-displaced array.
1162
1163 In SBCL, if ARRAY is a of type \(SIMPLE-ARRAY * \(*)), it is its own storage
1164 vector. Multidimensional arrays, arrays with fill pointers, and adjustable
1165 arrays have an underlying storage vector with the same ARRAY-ELEMENT-TYPE as
1166 ARRAY, which this function returns.
1167
1168 Important note: the underlying vector is an implementation detail. Even though
1169 this function exposes it, changes in the implementation may cause this
1170 function to be removed without further warning."
1171   ;; KLUDGE: Without TRULY-THE the system is not smart enough to figure out that
1172   ;; the return value is always of the known type.
1173   (truly-the (simple-array * (*))
1174              (if (array-header-p array)
1175                  (if (%array-displaced-p array)
1176                      (error "~S cannot be used with displaced arrays. Use ~S instead."
1177                             'array-storage-vector 'array-displacement)
1178                      (%array-data-vector array))
1179                  array)))
1180 \f
1181
1182 ;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY
1183
1184 ;;; This does the grinding work for ADJUST-ARRAY. It zaps the data
1185 ;;; from the OLD-DATA in an arrangement specified by the OLD-DIMS to
1186 ;;; the NEW-DATA in an arrangement specified by the NEW-DIMS. OFFSET
1187 ;;; is a displaced offset to be added to computed indices of OLD-DATA.
1188 (defun zap-array-data (old-data old-dims offset new-data new-dims new-length
1189                        element-type initial-element initial-element-p)
1190   (declare (list old-dims new-dims)
1191            (fixnum new-length))
1192   ;; OLD-DIMS comes from array-dimensions, which returns a fresh list
1193   ;; at least in SBCL.
1194   ;; NEW-DIMS comes from the user.
1195   (setf old-dims (nreverse old-dims)
1196         new-dims (reverse new-dims))
1197   (cond ((eq old-data new-data)
1198          ;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and
1199          ;; INITIAL-ELEMENT-P are used when OLD-DATA and NEW-DATA are
1200          ;; EQ; in this case, a temporary must be used and filled
1201          ;; appropriately. specified initial-element.
1202          (when initial-element-p
1203            ;; FIXME: transforming this TYPEP to someting a bit faster
1204            ;; would be a win...
1205            (unless (typep initial-element element-type)
1206              (error "~S can't be used to initialize an array of type ~S."
1207                     initial-element element-type)))
1208          (let ((temp (if initial-element-p
1209                          (make-array new-length :initial-element initial-element)
1210                          (make-array new-length))))
1211            (declare (simple-vector temp))
1212            (zap-array-data-aux old-data old-dims offset temp new-dims)
1213            (dotimes (i new-length)
1214              (setf (aref new-data i) (aref temp i)))
1215            ;; Kill the temporary vector to prevent garbage retention.
1216            (%shrink-vector temp 0)))
1217         (t
1218          ;; When OLD-DATA and NEW-DATA are not EQ, NEW-DATA has
1219          ;; already been filled with any
1220          (zap-array-data-aux old-data old-dims offset new-data new-dims))))
1221
1222 (defun zap-array-data-aux (old-data old-dims offset new-data new-dims)
1223   (declare (fixnum offset))
1224   (let ((limits (mapcar (lambda (x y)
1225                           (declare (fixnum x y))
1226                           (1- (the fixnum (min x y))))
1227                         old-dims new-dims)))
1228     (macrolet ((bump-index-list (index limits)
1229                  `(do ((subscripts ,index (cdr subscripts))
1230                        (limits ,limits (cdr limits)))
1231                       ((null subscripts) :eof)
1232                     (cond ((< (the fixnum (car subscripts))
1233                               (the fixnum (car limits)))
1234                            (rplaca subscripts
1235                                    (1+ (the fixnum (car subscripts))))
1236                            (return ,index))
1237                           (t (rplaca subscripts 0))))))
1238       (do ((index (make-list (length old-dims) :initial-element 0)
1239                   (bump-index-list index limits)))
1240           ((eq index :eof))
1241         (setf (aref new-data (row-major-index-from-dims index new-dims))
1242               (aref old-data
1243                     (+ (the fixnum (row-major-index-from-dims index old-dims))
1244                        offset)))))))
1245
1246 ;;; Figure out the row-major-order index of an array reference from a
1247 ;;; list of subscripts and a list of dimensions. This is for internal
1248 ;;; calls only, and the subscripts and dim-list variables are assumed
1249 ;;; to be reversed from what the user supplied.
1250 (defun row-major-index-from-dims (rev-subscripts rev-dim-list)
1251   (do ((rev-subscripts rev-subscripts (cdr rev-subscripts))
1252        (rev-dim-list rev-dim-list (cdr rev-dim-list))
1253        (chunk-size 1)
1254        (result 0))
1255       ((null rev-dim-list) result)
1256     (declare (fixnum chunk-size result))
1257     (setq result (+ result
1258                     (the fixnum (* (the fixnum (car rev-subscripts))
1259                                    chunk-size))))
1260     (setq chunk-size (* chunk-size (the fixnum (car rev-dim-list))))))
1261 \f
1262 ;;;; some bit stuff
1263
1264 (defun bit-array-same-dimensions-p (array1 array2)
1265   (declare (type (array bit) array1 array2))
1266   (and (= (array-rank array1)
1267           (array-rank array2))
1268        (dotimes (index (array-rank array1) t)
1269          (when (/= (array-dimension array1 index)
1270                    (array-dimension array2 index))
1271            (return nil)))))
1272
1273 (defun pick-result-array (result-bit-array bit-array-1)
1274   (case result-bit-array
1275     ((t) bit-array-1)
1276     ((nil) (make-array (array-dimensions bit-array-1)
1277                        :element-type 'bit
1278                        :initial-element 0))
1279     (t
1280      (unless (bit-array-same-dimensions-p bit-array-1
1281                                           result-bit-array)
1282        (error "~S and ~S don't have the same dimensions."
1283               bit-array-1 result-bit-array))
1284      result-bit-array)))
1285
1286 (defmacro def-bit-array-op (name function)
1287   `(defun ,name (bit-array-1 bit-array-2 &optional result-bit-array)
1288      #!+sb-doc
1289      ,(format nil
1290               "Perform a bit-wise ~A on the elements of BIT-ARRAY-1 and ~
1291                BIT-ARRAY-2,~%  putting the results in RESULT-BIT-ARRAY. ~
1292                If RESULT-BIT-ARRAY is T,~%  BIT-ARRAY-1 is used. If ~
1293                RESULT-BIT-ARRAY is NIL or omitted, a new array is~%  created. ~
1294                All the arrays must have the same rank and dimensions."
1295               (symbol-name function))
1296      (declare (type (array bit) bit-array-1 bit-array-2)
1297               (type (or (array bit) (member t nil)) result-bit-array))
1298      (unless (bit-array-same-dimensions-p bit-array-1 bit-array-2)
1299        (error "~S and ~S don't have the same dimensions."
1300               bit-array-1 bit-array-2))
1301      (let ((result-bit-array (pick-result-array result-bit-array bit-array-1)))
1302        (if (and (simple-bit-vector-p bit-array-1)
1303                 (simple-bit-vector-p bit-array-2)
1304                 (simple-bit-vector-p result-bit-array))
1305            (locally (declare (optimize (speed 3) (safety 0)))
1306              (,name bit-array-1 bit-array-2 result-bit-array))
1307            (with-array-data ((data1 bit-array-1) (start1) (end1))
1308              (declare (ignore end1))
1309              (with-array-data ((data2 bit-array-2) (start2) (end2))
1310                (declare (ignore end2))
1311                (with-array-data ((data3 result-bit-array) (start3) (end3))
1312                  (do ((index-1 start1 (1+ index-1))
1313                       (index-2 start2 (1+ index-2))
1314                       (index-3 start3 (1+ index-3)))
1315                      ((>= index-3 end3) result-bit-array)
1316                    (declare (type index index-1 index-2 index-3))
1317                    (setf (sbit data3 index-3)
1318                          (logand (,function (sbit data1 index-1)
1319                                             (sbit data2 index-2))
1320                                  1))))))))))
1321
1322 (def-bit-array-op bit-and logand)
1323 (def-bit-array-op bit-ior logior)
1324 (def-bit-array-op bit-xor logxor)
1325 (def-bit-array-op bit-eqv logeqv)
1326 (def-bit-array-op bit-nand lognand)
1327 (def-bit-array-op bit-nor lognor)
1328 (def-bit-array-op bit-andc1 logandc1)
1329 (def-bit-array-op bit-andc2 logandc2)
1330 (def-bit-array-op bit-orc1 logorc1)
1331 (def-bit-array-op bit-orc2 logorc2)
1332
1333 (defun bit-not (bit-array &optional result-bit-array)
1334   #!+sb-doc
1335   "Performs a bit-wise logical NOT on the elements of BIT-ARRAY,
1336   putting the results in RESULT-BIT-ARRAY. If RESULT-BIT-ARRAY is T,
1337   BIT-ARRAY is used. If RESULT-BIT-ARRAY is NIL or omitted, a new array is
1338   created. Both arrays must have the same rank and dimensions."
1339   (declare (type (array bit) bit-array)
1340            (type (or (array bit) (member t nil)) result-bit-array))
1341   (let ((result-bit-array (pick-result-array result-bit-array bit-array)))
1342     (if (and (simple-bit-vector-p bit-array)
1343              (simple-bit-vector-p result-bit-array))
1344         (locally (declare (optimize (speed 3) (safety 0)))
1345           (bit-not bit-array result-bit-array))
1346         (with-array-data ((src bit-array) (src-start) (src-end))
1347           (declare (ignore src-end))
1348           (with-array-data ((dst result-bit-array) (dst-start) (dst-end))
1349             (do ((src-index src-start (1+ src-index))
1350                  (dst-index dst-start (1+ dst-index)))
1351                 ((>= dst-index dst-end) result-bit-array)
1352               (declare (type index src-index dst-index))
1353               (setf (sbit dst dst-index)
1354                     (logxor (sbit src src-index) 1))))))))
1355
1356 ;;;; array type dispatching
1357
1358 ;;; Given DISPATCH-FOO as the DISPATCH-NAME argument (unevaluated),
1359 ;;; defines the functions
1360 ;;;
1361 ;;; DISPATCH-FOO/SIMPLE-BASE-STRING
1362 ;;; DISPATCH-FOO/SIMPLE-CHARACTER-STRING
1363 ;;; DISPATCH-FOO/SIMPLE-ARRAY-SINGLE-FLOAT
1364 ;;; ...
1365 ;;;
1366 ;;; PARAMS are the function parameters in the definition of each
1367 ;;; specializer function. The array being specialized must be the
1368 ;;; first parameter in PARAMS. A type declaration for this parameter
1369 ;;; is automatically inserted into the body of each function.
1370 ;;;
1371 ;;; The dispatch table %%FOO-FUNS%% is defined and populated by these
1372 ;;; functions. The table is padded by the function
1373 ;;; HAIRY-FOO-DISPATCH-ERROR, also defined by DEFINE-ARRAY-DISPATCH.
1374 ;;;
1375 ;;; Finally, the DISPATCH-FOO macro is defined which does the actual
1376 ;;; dispatching when called. It expects arguments that match PARAMS.
1377 ;;;
1378 (defmacro define-array-dispatch (dispatch-name params &body body)
1379   (let ((table-name (symbolicate "%%" dispatch-name "-FUNS%%"))
1380         (error-name (symbolicate "HAIRY-" dispatch-name "-ERROR")))
1381     `(progn
1382        (eval-when (:compile-toplevel :load-toplevel :execute)
1383          (defun ,error-name (&rest args)
1384            (error 'type-error
1385                   :datum (first args)
1386                   :expected-type '(simple-array * (*)))))
1387        (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)
1388                                           :initial-element #',error-name))
1389        ,@(loop for info across sb!vm:*specialized-array-element-type-properties*
1390                for typecode = (sb!vm:saetp-typecode info)
1391                for specifier = (sb!vm:saetp-specifier info)
1392                for primitive-type-name = (sb!vm:saetp-primitive-type-name info)
1393                collect (let ((fun-name (symbolicate (string dispatch-name)
1394                                                     "/" primitive-type-name)))
1395                          `(progn
1396                             (defun ,fun-name ,params
1397                               (declare (type (simple-array ,specifier (*))
1398                                              ,(first params)))
1399                               ,@body)
1400                             (setf (svref ,table-name ,typecode) #',fun-name))))
1401        (defmacro ,dispatch-name (&rest args)
1402          (check-type (first args) symbol)
1403          (let ((tag (gensym "TAG")))
1404            `(funcall
1405              (the function
1406                (let ((,tag 0))
1407                  (when (sb!vm::%other-pointer-p ,(first args))
1408                    (setf ,tag (%other-pointer-widetag ,(first args))))
1409                  (svref ,',table-name ,tag)))
1410              ,@args))))))