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