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