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