0.8.16.25:
[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 (defun %array-row-major-index (array subscripts
337                                      &optional (invalid-index-error-p t))
338   (declare (array array)
339            (list subscripts))
340   (let ((rank (array-rank array)))
341     (unless (= rank (length subscripts))
342       (error "wrong number of subscripts, ~W, for array of rank ~W"
343              (length subscripts) rank))
344     (if (array-header-p array)
345         (do ((subs (nreverse subscripts) (cdr subs))
346              (axis (1- (array-rank array)) (1- axis))
347              (chunk-size 1)
348              (result 0))
349             ((null subs) result)
350           (declare (list subs) (fixnum axis chunk-size result))
351           (let ((index (car subs))
352                 (dim (%array-dimension array axis)))
353             (declare (fixnum dim))
354             (unless (and (fixnump index) (< -1 index dim))
355               (if invalid-index-error-p
356                   (error 'simple-type-error
357                          :format-control "invalid index ~W~[~;~:; on axis ~:*~W~] in ~S"
358                          :format-arguments (list index axis array)
359                          :datum index
360                          :expected-type `(integer 0 (,dim)))
361                   (return-from %array-row-major-index nil)))
362             (incf result (* chunk-size (the fixnum index)))
363             (setf chunk-size (* chunk-size dim))))
364         (let ((index (first subscripts))
365               (length (length (the (simple-array * (*)) array))))
366           (unless (and (fixnump index) (< -1 index length))
367             (if invalid-index-error-p
368                 ;; FIXME: perhaps this should share a format-string
369                 ;; with INVALID-ARRAY-INDEX-ERROR or
370                 ;; INDEX-TOO-LARGE-ERROR?
371                 (error 'simple-type-error
372                        :format-control "invalid index ~W in ~S"
373                        :format-arguments (list index array)
374                        :datum index
375                        :expected-type `(integer 0 (,length)))
376                 (return-from %array-row-major-index nil)))
377           index))))
378
379 (defun array-in-bounds-p (array &rest subscripts)
380   #!+sb-doc
381   "Return T if the SUBSCIPTS are in bounds for the ARRAY, NIL otherwise."
382   (if (%array-row-major-index array subscripts nil)
383       t))
384
385 (defun array-row-major-index (array &rest subscripts)
386   (%array-row-major-index array subscripts))
387
388 (defun aref (array &rest subscripts)
389   #!+sb-doc
390   "Return the element of the ARRAY specified by the SUBSCRIPTS."
391   (row-major-aref array (%array-row-major-index array subscripts)))
392
393 (defun %aset (array &rest stuff)
394   (let ((subscripts (butlast stuff))
395         (new-value (car (last stuff))))
396     (setf (row-major-aref array (%array-row-major-index array subscripts))
397           new-value)))
398
399 ;;; FIXME: What's supposed to happen with functions
400 ;;; like AREF when we (DEFUN (SETF FOO) ..) when
401 ;;; DEFSETF FOO is also defined? It seems as though the logical
402 ;;; thing to do would be to nuke the macro definition for (SETF FOO)
403 ;;; and replace it with the (SETF FOO) function, issuing a warning,
404 ;;; just as for ordinary functions
405 ;;;  * (LISP-IMPLEMENTATION-VERSION)
406 ;;;  "18a+ release x86-linux 2.4.7 6 November 1998 cvs"
407 ;;;  * (DEFMACRO ZOO (X) `(+ ,X ,X))
408 ;;;  ZOO
409 ;;;  * (DEFUN ZOO (X) (* 3 X))
410 ;;;  Warning: ZOO previously defined as a macro.
411 ;;;  ZOO
412 ;;; But that doesn't seem to be what happens in CMU CL.
413 ;;;
414 ;;; KLUDGE: this is probably because ANSI, in its wisdom (CLHS
415 ;;; 5.1.2.5) requires implementations to support
416 ;;;   (SETF (APPLY #'AREF ...) ...)
417 ;;; [and also #'BIT and #'SBIT].  Yes, this is terrifying, and it's
418 ;;; also terrifying that this sequence of definitions causes it to
419 ;;; work.
420 ;;;
421 ;;; Also, it would be nice to make DESCRIBE FOO tell whether a symbol
422 ;;; has a setf expansion and/or a setf function defined.
423
424 #!-sb-fluid (declaim (inline (setf aref)))
425 (defun (setf aref) (new-value array &rest subscripts)
426   (declare (type array array))
427   (setf (row-major-aref array (%array-row-major-index array subscripts))
428         new-value))
429
430 (defun row-major-aref (array index)
431   #!+sb-doc
432   "Return the element of array corressponding to the row-major index. This is
433    SETF'able."
434   (declare (optimize (safety 1)))
435   (row-major-aref array index))
436
437 (defun %set-row-major-aref (array index new-value)
438   (declare (optimize (safety 1)))
439   (setf (row-major-aref array index) new-value))
440
441 (defun svref (simple-vector index)
442   #!+sb-doc
443   "Return the INDEX'th element of the given Simple-Vector."
444   (declare (optimize (safety 1)))
445   (aref simple-vector index))
446
447 (defun %svset (simple-vector index new)
448   (declare (optimize (safety 1)))
449   (setf (aref simple-vector index) new))
450
451 (defun bit (bit-array &rest subscripts)
452   #!+sb-doc
453   "Return the bit from the BIT-ARRAY at the specified SUBSCRIPTS."
454   (declare (type (array bit) bit-array) (optimize (safety 1)))
455   (row-major-aref bit-array (%array-row-major-index bit-array subscripts)))
456
457 (defun %bitset (bit-array &rest stuff)
458   (declare (type (array bit) bit-array) (optimize (safety 1)))
459   (let ((subscripts (butlast stuff))
460         (new-value (car (last stuff))))
461     (setf (row-major-aref bit-array
462                           (%array-row-major-index bit-array subscripts))
463           new-value)))
464
465 #!-sb-fluid (declaim (inline (setf bit)))
466 (defun (setf bit) (new-value bit-array &rest subscripts)
467   (declare (type (array bit) bit-array) (optimize (safety 1)))
468   (setf (row-major-aref bit-array
469                         (%array-row-major-index bit-array subscripts))
470         new-value))
471
472 (defun sbit (simple-bit-array &rest subscripts)
473   #!+sb-doc
474   "Return the bit from SIMPLE-BIT-ARRAY at the specified SUBSCRIPTS."
475   (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
476   (row-major-aref simple-bit-array
477                   (%array-row-major-index simple-bit-array subscripts)))
478
479 ;;; KLUDGE: Not all these things (%SET-ROW-MAJOR-AREF, %SET-FILL-POINTER,
480 ;;; %SET-FDEFINITION, %SCHARSET, %SBITSET..) seem to deserve separate names.
481 ;;; Could we just DEFUN (SETF SBIT) etc. and get rid of the non-ANSI names?
482 ;;; -- WHN 19990911
483 (defun %sbitset (simple-bit-array &rest stuff)
484   (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1)))
485   (let ((subscripts (butlast stuff))
486         (new-value (car (last stuff))))
487     (setf (row-major-aref simple-bit-array
488                           (%array-row-major-index simple-bit-array subscripts))
489           new-value)))
490
491 #!-sb-fluid (declaim (inline (setf sbit)))
492 (defun (setf sbit) (new-value bit-array &rest subscripts)
493   (declare (type (simple-array bit) bit-array) (optimize (safety 1)))
494   (setf (row-major-aref bit-array
495                         (%array-row-major-index bit-array subscripts))
496         new-value))
497 \f
498 ;;;; miscellaneous array properties
499
500 (defun array-element-type (array)
501   #!+sb-doc
502   "Return the type of the elements of the array"
503   (let ((widetag (widetag-of array)))
504     (macrolet ((pick-element-type (&rest stuff)
505                  `(cond ,@(mapcar (lambda (stuff)
506                                     (cons
507                                      (let ((item (car stuff)))
508                                        (cond ((eq item t)
509                                               t)
510                                              ((listp item)
511                                               (cons 'or
512                                                     (mapcar (lambda (x)
513                                                               `(= widetag ,x))
514                                                             item)))
515                                              (t
516                                               `(= widetag ,item))))
517                                      (cdr stuff)))
518                                   stuff))))
519       #.`(pick-element-type
520           ,@(map 'list
521                  (lambda (saetp)
522                    `(,(if (sb!vm:saetp-complex-typecode saetp)
523                           (list (sb!vm:saetp-typecode saetp)
524                                 (sb!vm:saetp-complex-typecode saetp))
525                           (sb!vm:saetp-typecode saetp))
526                      ',(sb!vm:saetp-specifier saetp)))
527                  sb!vm:*specialized-array-element-type-properties*)
528           ((sb!vm:simple-array-widetag
529             sb!vm:complex-vector-widetag
530             sb!vm:complex-array-widetag)
531            (with-array-data ((array array) (start) (end))
532              (declare (ignore start end))
533              (array-element-type array)))
534           (t
535            (error 'type-error :datum array :expected-type 'array))))))
536
537 (defun array-rank (array)
538   #!+sb-doc
539   "Return the number of dimensions of ARRAY."
540   (if (array-header-p array)
541       (%array-rank array)
542       1))
543
544 (defun array-dimension (array axis-number)
545   #!+sb-doc
546   "Return the length of dimension AXIS-NUMBER of ARRAY."
547   (declare (array array) (type index axis-number))
548   (cond ((not (array-header-p array))
549          (unless (= axis-number 0)
550            (error "Vector axis is not zero: ~S" axis-number))
551          (length (the (simple-array * (*)) array)))
552         ((>= axis-number (%array-rank array))
553          (error "Axis number ~W is too big; ~S only has ~D dimension~:P."
554                 axis-number array (%array-rank array)))
555         (t
556          ;; ANSI sayeth (ADJUST-ARRAY dictionary entry): 
557          ;; 
558          ;;   "If A is displaced to B, the consequences are
559          ;;   unspecified if B is adjusted in such a way that it no
560          ;;   longer has enough elements to satisfy A.
561          ;;
562          ;; In situations where this matters we should be doing a
563          ;; bounds-check, which in turn uses ARRAY-DIMENSION -- so
564          ;; this seems like a good place to signal an error.
565          (multiple-value-bind (target offset) (array-displacement array)
566            (when (and target 
567                       (> (array-total-size array)
568                          (- (array-total-size target) offset)))
569                (error 'displaced-to-array-too-small-error
570                       :format-control "~@<The displaced-to array is too small. ~S ~
571                                       elements after offset required, ~S available.~:@>"
572                       :format-arguments (list (array-total-size array) 
573                                               (- (array-total-size target) offset))))
574            (%array-dimension array axis-number)))))
575
576 (defun array-dimensions (array)
577   #!+sb-doc
578   "Return a list whose elements are the dimensions of the array"
579   (declare (array array))
580   (if (array-header-p array)
581       (do ((results nil (cons (array-dimension array index) results))
582            (index (1- (array-rank array)) (1- index)))
583           ((minusp index) results))
584       (list (array-dimension array 0))))
585
586 (defun array-total-size (array)
587   #!+sb-doc
588   "Return the total number of elements in the Array."
589   (declare (array array))
590   (if (array-header-p array)
591       (%array-available-elements array)
592       (length (the vector array))))
593
594 (defun array-displacement (array)
595   #!+sb-doc
596   "Return the values of :DISPLACED-TO and :DISPLACED-INDEX-offset
597    options to MAKE-ARRAY, or NIL and 0 if not a displaced array."
598   (declare (type array array))
599   (if (and (array-header-p array) ; if unsimple and
600            (%array-displaced-p array)) ; displaced
601       (values (%array-data-vector array) (%array-displacement array))
602       (values nil 0)))
603
604 (defun adjustable-array-p (array)
605   #!+sb-doc
606   "Return T if (ADJUST-ARRAY ARRAY...) would return an array identical
607    to the argument, this happens for complex arrays."
608   (declare (array array))
609   ;; Note that this appears not to be a fundamental limitation.
610   ;; non-vector SIMPLE-ARRAYs are in fact capable of being adjusted,
611   ;; but in practice we test using ADJUSTABLE-ARRAY-P in ADJUST-ARRAY.
612   ;; -- CSR, 2004-03-01.
613   (not (typep array 'simple-array)))
614 \f
615 ;;;; fill pointer frobbing stuff
616
617 (defun array-has-fill-pointer-p (array)
618   #!+sb-doc
619   "Return T if the given ARRAY has a fill pointer, or NIL otherwise."
620   (declare (array array))
621   (and (array-header-p array) (%array-fill-pointer-p array)))
622
623 (defun fill-pointer (vector)
624   #!+sb-doc
625   "Return the FILL-POINTER of the given VECTOR."
626   (declare (vector vector))
627   (if (and (array-header-p vector) (%array-fill-pointer-p vector))
628       (%array-fill-pointer vector)
629       (error 'simple-type-error
630              :datum vector
631              :expected-type '(and vector (satisfies array-has-fill-pointer-p))
632              :format-control "~S is not an array with a fill pointer."
633              :format-arguments (list vector))))
634
635 (defun %set-fill-pointer (vector new)
636   (declare (vector vector) (fixnum new))
637   (if (and (array-header-p vector) (%array-fill-pointer-p vector))
638       (if (> new (%array-available-elements vector))
639         (error
640          "The new fill pointer, ~S, is larger than the length of the vector."
641          new)
642         (setf (%array-fill-pointer vector) new))
643       (error 'simple-type-error
644              :datum vector
645              :expected-type '(and vector (satisfies array-has-fill-pointer-p))
646              :format-control "~S is not an array with a fill pointer."
647              :format-arguments (list vector))))
648
649 ;;; FIXME: It'd probably make sense to use a MACROLET to share the
650 ;;; guts of VECTOR-PUSH between VECTOR-PUSH-EXTEND. Such a macro
651 ;;; should probably be based on the VECTOR-PUSH-EXTEND code (which is
652 ;;; new ca. sbcl-0.7.0) rather than the VECTOR-PUSH code (which dates
653 ;;; back to CMU CL).
654 (defun vector-push (new-el array)
655   #!+sb-doc
656   "Attempt to set the element of ARRAY designated by its fill pointer
657    to NEW-EL, and increment the fill pointer by one. If the fill pointer is
658    too large, NIL is returned, otherwise the index of the pushed element is
659    returned."
660   (declare (vector array))
661   (let ((fill-pointer (fill-pointer array)))
662     (declare (fixnum fill-pointer))
663     (cond ((= fill-pointer (%array-available-elements array))
664            nil)
665           (t
666            (setf (aref array fill-pointer) new-el)
667            (setf (%array-fill-pointer array) (1+ fill-pointer))
668            fill-pointer))))
669
670 (defun vector-push-extend (new-element
671                            vector
672                            &optional
673                            (extension (1+ (length vector))))
674   (declare (vector vector) (fixnum extension))
675   (let ((fill-pointer (fill-pointer vector)))
676     (declare (fixnum fill-pointer))
677     (when (= fill-pointer (%array-available-elements vector))
678       (adjust-array vector (+ fill-pointer extension)))
679     ;; disable bounds checking
680     (locally (declare (optimize (safety 0)))
681       (setf (aref vector fill-pointer) new-element))
682     (setf (%array-fill-pointer vector) (1+ fill-pointer))
683     fill-pointer))
684
685 (defun vector-pop (array)
686   #!+sb-doc
687   "Decrease the fill pointer by 1 and return the element pointed to by the
688   new fill pointer."
689   (declare (vector array))
690   (let ((fill-pointer (fill-pointer array)))
691     (declare (fixnum fill-pointer))
692     (if (zerop fill-pointer)
693         (error "There is nothing left to pop.")
694         ;; disable bounds checking (and any fixnum test)
695         (locally (declare (optimize (safety 0)))
696           (aref array
697                 (setf (%array-fill-pointer array)
698                       (1- fill-pointer)))))))
699
700 \f
701 ;;;; ADJUST-ARRAY
702
703 (defun adjust-array (array dimensions &key
704                            (element-type (array-element-type array))
705                            (initial-element nil initial-element-p)
706                            (initial-contents nil initial-contents-p)
707                            fill-pointer
708                            displaced-to displaced-index-offset)
709   #!+sb-doc
710   "Adjust ARRAY's dimensions to the given DIMENSIONS and stuff."
711   (let ((dimensions (if (listp dimensions) dimensions (list dimensions))))
712     (cond ((/= (the fixnum (length (the list dimensions)))
713                (the fixnum (array-rank array)))
714            (error "The number of dimensions not equal to rank of array."))
715           ((not (subtypep element-type (array-element-type array)))
716            (error "The new element type, ~S, is incompatible with old type."
717                   element-type)))
718     (let ((array-rank (length (the list dimensions))))
719       (declare (fixnum array-rank))
720       (unless (= array-rank 1)
721         (when fill-pointer
722           (error "Only vectors can have fill pointers.")))
723       (cond (initial-contents-p
724              ;; array former contents replaced by INITIAL-CONTENTS
725              (if (or initial-element-p displaced-to)
726                  (error "INITIAL-CONTENTS may not be specified with ~
727                          the :INITIAL-ELEMENT or :DISPLACED-TO option."))
728              (let* ((array-size (apply #'* dimensions))
729                     (array-data (data-vector-from-inits
730                                  dimensions array-size element-type
731                                  initial-contents initial-contents-p
732                                  initial-element initial-element-p)))
733                (if (adjustable-array-p array)
734                    (set-array-header array array-data array-size
735                                  (get-new-fill-pointer array array-size
736                                                        fill-pointer)
737                                  0 dimensions nil)
738                    (if (array-header-p array)
739                        ;; simple multidimensional or single dimensional array
740                        (make-array dimensions
741                                    :element-type element-type
742                                    :initial-contents initial-contents)
743                        array-data))))
744             (displaced-to
745              ;; We already established that no INITIAL-CONTENTS was supplied.
746              (when initial-element
747                (error "The :INITIAL-ELEMENT option may not be specified ~
748                        with :DISPLACED-TO."))
749              (unless (subtypep element-type (array-element-type displaced-to))
750                (error "can't displace an array of type ~S into another of ~
751                        type ~S"
752                       element-type (array-element-type displaced-to)))
753              (let ((displacement (or displaced-index-offset 0))
754                    (array-size (apply #'* dimensions)))
755                (declare (fixnum displacement array-size))
756                (if (< (the fixnum (array-total-size displaced-to))
757                       (the fixnum (+ displacement array-size)))
758                    (error "The :DISPLACED-TO array is too small."))
759                (if (adjustable-array-p array)
760                    ;; None of the original contents appear in adjusted array.
761                    (set-array-header array displaced-to array-size
762                                      (get-new-fill-pointer array array-size
763                                                            fill-pointer)
764                                      displacement dimensions t)
765                    ;; simple multidimensional or single dimensional array
766                    (make-array dimensions
767                                :element-type element-type
768                                :displaced-to displaced-to
769                                :displaced-index-offset
770                                displaced-index-offset))))
771             ((= array-rank 1)
772              (let ((old-length (array-total-size array))
773                    (new-length (car dimensions))
774                    new-data)
775                (declare (fixnum old-length new-length))
776                (with-array-data ((old-data array) (old-start)
777                                  (old-end old-length))
778                  (cond ((or (%array-displaced-p array)
779                             (< old-length new-length))
780                         (setf new-data
781                               (data-vector-from-inits
782                                dimensions new-length element-type
783                                initial-contents initial-contents-p
784                                initial-element initial-element-p))
785                         (replace new-data old-data
786                                  :start2 old-start :end2 old-end))
787                        (t (setf new-data
788                                 (shrink-vector old-data new-length))))
789                  (if (adjustable-array-p array)
790                      (set-array-header array new-data new-length
791                                        (get-new-fill-pointer array new-length
792                                                              fill-pointer)
793                                        0 dimensions nil)
794                      new-data))))
795             (t
796              (let ((old-length (%array-available-elements array))
797                    (new-length (apply #'* dimensions)))
798                (declare (fixnum old-length new-length))
799                (with-array-data ((old-data array) (old-start)
800                                  (old-end old-length))
801                  (declare (ignore old-end))
802                  (let ((new-data (if (or (%array-displaced-p array)
803                                          (> new-length old-length))
804                                      (data-vector-from-inits
805                                       dimensions new-length
806                                       element-type () nil
807                                       initial-element initial-element-p)
808                                      old-data)))
809                    (if (or (zerop old-length) (zerop new-length))
810                        (when initial-element-p (fill new-data initial-element))
811                        (zap-array-data old-data (array-dimensions array)
812                                        old-start
813                                        new-data dimensions new-length
814                                        element-type initial-element
815                                        initial-element-p))
816                    (if (adjustable-array-p array)
817                        (set-array-header array new-data new-length
818                                          new-length 0 dimensions nil)
819                        (let ((new-array
820                               (make-array-header
821                                sb!vm:simple-array-widetag array-rank)))
822                          (set-array-header new-array new-data new-length
823                                            new-length 0 dimensions nil)))))))))))
824   
825
826 (defun get-new-fill-pointer (old-array new-array-size fill-pointer)
827   (cond ((not fill-pointer)
828          (when (array-has-fill-pointer-p old-array)
829            (when (> (%array-fill-pointer old-array) new-array-size)
830              (error "cannot ADJUST-ARRAY an array (~S) to a size (~S) that is ~
831                      smaller than its fill pointer (~S)"
832                     old-array new-array-size (fill-pointer old-array)))
833            (%array-fill-pointer old-array)))
834         ((not (array-has-fill-pointer-p old-array))
835          (error "cannot supply a non-NIL value (~S) for :FILL-POINTER ~
836                  in ADJUST-ARRAY unless the array (~S) was originally ~
837                  created with a fill pointer"
838                 fill-pointer
839                 old-array))
840         ((numberp fill-pointer)
841          (when (> fill-pointer new-array-size)
842            (error "can't supply a value for :FILL-POINTER (~S) that is larger ~
843                    than the new length of the vector (~S)"
844                   fill-pointer new-array-size))
845          fill-pointer)
846         ((eq fill-pointer t)
847          new-array-size)
848         (t
849          (error "bogus value for :FILL-POINTER in ADJUST-ARRAY: ~S"
850                 fill-pointer))))
851
852 ;;; Destructively alter VECTOR, changing its length to NEW-LENGTH,
853 ;;; which must be less than or equal to its current length.
854 (defun shrink-vector (vector new-length)
855   (declare (vector vector))
856   (unless (array-header-p vector)
857     (macrolet ((frob (name &rest things)
858                  `(etypecase ,name
859                     ((simple-array nil (*)) (error 'nil-array-accessed-error))
860                     ,@(mapcar (lambda (thing)
861                                 (destructuring-bind (type-spec fill-value)
862                                     thing
863                                   `(,type-spec
864                                     (fill (truly-the ,type-spec ,name)
865                                           ,fill-value
866                                           :start new-length))))
867                               things))))
868       #.`(frob vector
869           ,@(map 'list
870                  (lambda (saetp)
871                    `((simple-array ,(sb!vm:saetp-specifier saetp) (*))
872                      ,(if (or (eq (sb!vm:saetp-specifier saetp) 'character)
873                               #!+sb-unicode
874                               (eq (sb!vm:saetp-specifier saetp) 'base-char))
875                           *default-init-char-form*
876                           (sb!vm:saetp-initial-element-default saetp))))
877                  (remove-if-not
878                   #'sb!vm:saetp-specifier
879                   sb!vm:*specialized-array-element-type-properties*)))))
880   ;; Only arrays have fill-pointers, but vectors have their length
881   ;; parameter in the same place.
882   (setf (%array-fill-pointer vector) new-length)
883   vector)
884
885 ;;; Fill in array header with the provided information, and return the array.
886 (defun set-array-header (array data length fill-pointer displacement dimensions
887                          &optional displacedp)
888   (setf (%array-data-vector array) data)
889   (setf (%array-available-elements array) length)
890   (cond (fill-pointer
891          (setf (%array-fill-pointer array) fill-pointer)
892          (setf (%array-fill-pointer-p array) t))
893         (t
894          (setf (%array-fill-pointer array) length)
895          (setf (%array-fill-pointer-p array) nil)))
896   (setf (%array-displacement array) displacement)
897   (if (listp dimensions)
898       (dotimes (axis (array-rank array))
899         (declare (type index axis))
900         (setf (%array-dimension array axis) (pop dimensions)))
901       (setf (%array-dimension array 0) dimensions))
902   (setf (%array-displaced-p array) displacedp)
903   array)
904 \f
905 ;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY
906
907 ;;; a temporary to be used when OLD-DATA and NEW-DATA are EQ.
908 ;;; KLUDGE: Boy, DYNAMIC-EXTENT would be nice.
909 (defvar *zap-array-data-temp* (make-array 1000 :initial-element t))
910
911 (defun zap-array-data-temp (length element-type initial-element
912                             initial-element-p)
913   (declare (fixnum length))
914   (when (> length (the fixnum (length *zap-array-data-temp*)))
915     (setf *zap-array-data-temp*
916           (make-array length :initial-element t)))
917   (when initial-element-p
918     (unless (typep initial-element element-type)
919       (error "~S can't be used to initialize an array of type ~S."
920              initial-element element-type))
921     (fill (the simple-vector *zap-array-data-temp*) initial-element
922           :end length))
923   *zap-array-data-temp*)
924
925 ;;; This does the grinding work for ADJUST-ARRAY. It zaps the data
926 ;;; from the OLD-DATA in an arrangement specified by the OLD-DIMS to
927 ;;; the NEW-DATA in an arrangement specified by the NEW-DIMS. OFFSET
928 ;;; is a displaced offset to be added to computed indices of OLD-DATA.
929 ;;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and INITIAL-ELEMENT-P
930 ;;; are used when OLD-DATA and NEW-DATA are EQ; in this case, a
931 ;;; temporary must be used and filled appropriately. When OLD-DATA and
932 ;;; NEW-DATA are not EQ, NEW-DATA has already been filled with any
933 ;;; specified initial-element.
934 (defun zap-array-data (old-data old-dims offset new-data new-dims new-length
935                        element-type initial-element initial-element-p)
936   (declare (list old-dims new-dims))
937   (setq old-dims (nreverse old-dims))
938   (setq new-dims (reverse new-dims))
939   (if (eq old-data new-data)
940       (let ((temp (zap-array-data-temp new-length element-type
941                                        initial-element initial-element-p)))
942         (zap-array-data-aux old-data old-dims offset temp new-dims)
943         (dotimes (i new-length) (setf (aref new-data i) (aref temp i))))
944       (zap-array-data-aux old-data old-dims offset new-data new-dims)))
945
946 (defun zap-array-data-aux (old-data old-dims offset new-data new-dims)
947   (declare (fixnum offset))
948   (let ((limits (mapcar (lambda (x y)
949                           (declare (fixnum x y))
950                           (1- (the fixnum (min x y))))
951                         old-dims new-dims)))
952     (macrolet ((bump-index-list (index limits)
953                  `(do ((subscripts ,index (cdr subscripts))
954                        (limits ,limits (cdr limits)))
955                       ((null subscripts) :eof)
956                     (cond ((< (the fixnum (car subscripts))
957                               (the fixnum (car limits)))
958                            (rplaca subscripts
959                                    (1+ (the fixnum (car subscripts))))
960                            (return ,index))
961                           (t (rplaca subscripts 0))))))
962       (do ((index (make-list (length old-dims) :initial-element 0)
963                   (bump-index-list index limits)))
964           ((eq index :eof))
965         (setf (aref new-data (row-major-index-from-dims index new-dims))
966               (aref old-data
967                     (+ (the fixnum (row-major-index-from-dims index old-dims))
968                        offset)))))))
969
970 ;;; Figure out the row-major-order index of an array reference from a
971 ;;; list of subscripts and a list of dimensions. This is for internal
972 ;;; calls only, and the subscripts and dim-list variables are assumed
973 ;;; to be reversed from what the user supplied.
974 (defun row-major-index-from-dims (rev-subscripts rev-dim-list)
975   (do ((rev-subscripts rev-subscripts (cdr rev-subscripts))
976        (rev-dim-list rev-dim-list (cdr rev-dim-list))
977        (chunk-size 1)
978        (result 0))
979       ((null rev-dim-list) result)
980     (declare (fixnum chunk-size result))
981     (setq result (+ result
982                     (the fixnum (* (the fixnum (car rev-subscripts))
983                                    chunk-size))))
984     (setq chunk-size (* chunk-size (the fixnum (car rev-dim-list))))))
985 \f
986 ;;;; some bit stuff
987
988 (defun bit-array-same-dimensions-p (array1 array2)
989   (declare (type (array bit) array1 array2))
990   (and (= (array-rank array1)
991           (array-rank array2))
992        (dotimes (index (array-rank array1) t)
993          (when (/= (array-dimension array1 index)
994                    (array-dimension array2 index))
995            (return nil)))))
996
997 (defun pick-result-array (result-bit-array bit-array-1)
998   (case result-bit-array
999     ((t) bit-array-1)
1000     ((nil) (make-array (array-dimensions bit-array-1)
1001                        :element-type 'bit
1002                        :initial-element 0))
1003     (t
1004      (unless (bit-array-same-dimensions-p bit-array-1
1005                                           result-bit-array)
1006        (error "~S and ~S don't have the same dimensions."
1007               bit-array-1 result-bit-array))
1008      result-bit-array)))
1009
1010 (defmacro def-bit-array-op (name function)
1011   `(defun ,name (bit-array-1 bit-array-2 &optional result-bit-array)
1012      #!+sb-doc
1013      ,(format nil
1014               "Perform a bit-wise ~A on the elements of BIT-ARRAY-1 and ~
1015                BIT-ARRAY-2,~%  putting the results in RESULT-BIT-ARRAY. ~
1016                If RESULT-BIT-ARRAY is T,~%  BIT-ARRAY-1 is used. If ~
1017                RESULT-BIT-ARRAY is NIL or omitted, a new array is~%  created. ~
1018                All the arrays must have the same rank and dimensions."
1019               (symbol-name function))
1020      (declare (type (array bit) bit-array-1 bit-array-2)
1021               (type (or (array bit) (member t nil)) result-bit-array))
1022      (unless (bit-array-same-dimensions-p bit-array-1 bit-array-2)
1023        (error "~S and ~S don't have the same dimensions."
1024               bit-array-1 bit-array-2))
1025      (let ((result-bit-array (pick-result-array result-bit-array bit-array-1)))
1026        (if (and (simple-bit-vector-p bit-array-1)
1027                 (simple-bit-vector-p bit-array-2)
1028                 (simple-bit-vector-p result-bit-array))
1029            (locally (declare (optimize (speed 3) (safety 0)))
1030              (,name bit-array-1 bit-array-2 result-bit-array))
1031            (with-array-data ((data1 bit-array-1) (start1) (end1))
1032              (declare (ignore end1))
1033              (with-array-data ((data2 bit-array-2) (start2) (end2))
1034                (declare (ignore end2))
1035                (with-array-data ((data3 result-bit-array) (start3) (end3))
1036                  (do ((index-1 start1 (1+ index-1))
1037                       (index-2 start2 (1+ index-2))
1038                       (index-3 start3 (1+ index-3)))
1039                      ((>= index-3 end3) result-bit-array)
1040                    (declare (type index index-1 index-2 index-3))
1041                    (setf (sbit data3 index-3)
1042                          (logand (,function (sbit data1 index-1)
1043                                             (sbit data2 index-2))
1044                                  1))))))))))
1045
1046 (def-bit-array-op bit-and logand)
1047 (def-bit-array-op bit-ior logior)
1048 (def-bit-array-op bit-xor logxor)
1049 (def-bit-array-op bit-eqv logeqv)
1050 (def-bit-array-op bit-nand lognand)
1051 (def-bit-array-op bit-nor lognor)
1052 (def-bit-array-op bit-andc1 logandc1)
1053 (def-bit-array-op bit-andc2 logandc2)
1054 (def-bit-array-op bit-orc1 logorc1)
1055 (def-bit-array-op bit-orc2 logorc2)
1056
1057 (defun bit-not (bit-array &optional result-bit-array)
1058   #!+sb-doc
1059   "Performs a bit-wise logical NOT on the elements of BIT-ARRAY,
1060   putting the results in RESULT-BIT-ARRAY. If RESULT-BIT-ARRAY is T,
1061   BIT-ARRAY is used. If RESULT-BIT-ARRAY is NIL or omitted, a new array is
1062   created. Both arrays must have the same rank and dimensions."
1063   (declare (type (array bit) bit-array)
1064            (type (or (array bit) (member t nil)) result-bit-array))
1065   (let ((result-bit-array (pick-result-array result-bit-array bit-array)))
1066     (if (and (simple-bit-vector-p bit-array)
1067              (simple-bit-vector-p result-bit-array))
1068         (locally (declare (optimize (speed 3) (safety 0)))
1069           (bit-not bit-array result-bit-array))
1070         (with-array-data ((src bit-array) (src-start) (src-end))
1071           (declare (ignore src-end))
1072           (with-array-data ((dst result-bit-array) (dst-start) (dst-end))
1073             (do ((src-index src-start (1+ src-index))
1074                  (dst-index dst-start (1+ dst-index)))
1075                 ((>= dst-index dst-end) result-bit-array)
1076               (declare (type index src-index dst-index))
1077               (setf (sbit dst dst-index)
1078                     (logxor (sbit src src-index) 1))))))))