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