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