1224c8508a50aaeebc2f785e9b33582a3df036c4
[sbcl.git] / src / compiler / array-tran.lisp
1 ;;;; array-specific optimizers and transforms
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!C")
13 \f
14 ;;;; utilities for optimizing array operations
15
16 ;;; Return UPGRADED-ARRAY-ELEMENT-TYPE for CONTINUATION, or do
17 ;;; GIVE-UP-IR1-TRANSFORM if the upgraded element type can't be
18 ;;; determined.
19 (defun upgraded-element-type-specifier-or-give-up (continuation)
20   (let* ((element-ctype (extract-upgraded-element-type continuation))
21          (element-type-specifier (type-specifier element-ctype)))
22     (if (eq element-type-specifier '*)
23         (give-up-ir1-transform
24          "upgraded array element type not known at compile time")
25         element-type-specifier)))
26
27 ;;; Array access functions return an object from the array, hence its
28 ;;; type will be asserted to be array element type.
29 (defun extract-element-type (array)
30   (let ((type (continuation-type array)))
31     (if (array-type-p type)
32         (array-type-element-type type)
33         *universal-type*)))
34
35 ;;; Array access functions return an object from the array, hence its
36 ;;; type is going to be the array upgraded element type.
37 (defun extract-upgraded-element-type (array)
38   (let ((type (continuation-type array)))
39     (if (array-type-p type)
40         (array-type-specialized-element-type type)
41         *universal-type*)))
42
43 ;;; The ``new-value'' for array setters must fit in the array, and the
44 ;;; return type is going to be the same as the new-value for SETF
45 ;;; functions.
46 (defun assert-new-value-type (new-value array)
47   (let ((type (continuation-type array)))
48     (when (array-type-p type)
49       (assert-continuation-type new-value (array-type-element-type type))))
50   (continuation-type new-value))
51
52 ;;; Return true if Arg is NIL, or is a constant-continuation whose
53 ;;; value is NIL, false otherwise.
54 (defun unsupplied-or-nil (arg)
55   (declare (type (or continuation null) arg))
56   (or (not arg)
57       (and (constant-continuation-p arg)
58            (not (continuation-value arg)))))
59 \f
60 ;;;; DERIVE-TYPE optimizers
61
62 ;;; Array operations that use a specific number of indices implicitly
63 ;;; assert that the array is of that rank.
64 (defun assert-array-rank (array rank)
65   (assert-continuation-type
66    array
67    (specifier-type `(array * ,(make-list rank :initial-element '*)))))
68
69 (defoptimizer (array-in-bounds-p derive-type) ((array &rest indices))
70   (assert-array-rank array (length indices))
71   *universal-type*)
72
73 (defoptimizer (aref derive-type) ((array &rest indices) node)
74   (assert-array-rank array (length indices))
75   ;; If the node continuation has a single use then assert its type.
76   (let ((cont (node-cont node)))
77     (when (= (length (find-uses cont)) 1)
78       (assert-continuation-type cont (extract-element-type array))))
79   (extract-upgraded-element-type array))
80
81 (defoptimizer (%aset derive-type) ((array &rest stuff))
82   (assert-array-rank array (1- (length stuff)))
83   (assert-new-value-type (car (last stuff)) array))
84
85 (defoptimizer (hairy-data-vector-ref derive-type) ((array index))
86   (extract-upgraded-element-type array))
87 (defoptimizer (data-vector-ref derive-type) ((array index))
88   (extract-upgraded-element-type array))
89
90 (defoptimizer (data-vector-set derive-type) ((array index new-value))
91   (assert-new-value-type new-value array))
92 (defoptimizer (hairy-data-vector-set derive-type) ((array index new-value))
93   (assert-new-value-type new-value array))
94
95 ;;; Figure out the type of the data vector if we know the argument
96 ;;; element type.
97 (defoptimizer (%with-array-data derive-type) ((array start end))
98   (let ((atype (continuation-type array)))
99     (when (array-type-p atype)
100       (values-specifier-type
101        `(values (simple-array ,(type-specifier
102                                 (array-type-element-type atype))
103                               (*))
104                 index index index)))))
105
106 (defoptimizer (array-row-major-index derive-type) ((array &rest indices))
107   (assert-array-rank array (length indices))
108   *universal-type*)
109
110 (defoptimizer (row-major-aref derive-type) ((array index))
111   (extract-upgraded-element-type array))
112
113 (defoptimizer (%set-row-major-aref derive-type) ((array index new-value))
114   (assert-new-value-type new-value array))
115
116 (defoptimizer (make-array derive-type)
117               ((dims &key initial-element element-type initial-contents
118                 adjustable fill-pointer displaced-index-offset displaced-to))
119   (let ((simple (and (unsupplied-or-nil adjustable)
120                      (unsupplied-or-nil displaced-to)
121                      (unsupplied-or-nil fill-pointer))))
122     (specifier-type
123      `(,(if simple 'simple-array 'array)
124        ,(cond ((not element-type) t)
125               ((constant-continuation-p element-type)
126                (continuation-value element-type))
127               (t
128                '*))
129        ,(cond ((not simple)
130                '*)
131               ((constant-continuation-p dims)
132                (let ((val (continuation-value dims)))
133                  (if (listp val) val (list val))))
134               ((csubtypep (continuation-type dims)
135                           (specifier-type 'integer))
136                '(*))
137               (t
138                '*))))))
139 \f
140 ;;;; constructors
141
142 ;;; Convert VECTOR into a MAKE-ARRAY followed by SETFs of all the
143 ;;; elements.
144 (def-source-transform vector (&rest elements)
145   (if (byte-compiling)
146       (values nil t)
147       (let ((len (length elements))
148             (n -1))
149         (once-only ((n-vec `(make-array ,len)))
150           `(progn
151              ,@(mapcar #'(lambda (el)
152                            (once-only ((n-val el))
153                              `(locally (declare (optimize (safety 0)))
154                                        (setf (svref ,n-vec ,(incf n))
155                                              ,n-val))))
156                        elements)
157              ,n-vec)))))
158
159 ;;; Just convert it into a MAKE-ARRAY.
160 (def-source-transform make-string (length &key
161                                           (element-type ''base-char)
162                                           (initial-element
163                                            '#.*default-init-char-form*))
164   (if (byte-compiling)
165       (values nil t)
166       `(make-array (the index ,length)
167                    :element-type ,element-type
168                    :initial-element ,initial-element)))
169
170 (defstruct (specialized-array-element-type-properties
171             (:conc-name saetp-)
172             (:constructor !make-saetp (ctype
173                                        initial-element-default
174                                        n-bits
175                                        typecode
176                                        &key
177                                        (n-pad-elements 0)))
178             (:copier nil))
179   ;; the element type, e.g. #<BUILT-IN-CLASS BASE-CHAR (sealed)> or
180   ;; #<SB-KERNEL:NUMERIC-TYPE (UNSIGNED-BYTE 4)>
181   (ctype (required-argument) :type ctype :read-only t)
182   ;; what we get when the low-level vector-creation logic zeroes all
183   ;; the bits (which also serves as the default value of MAKE-ARRAY's
184   ;; :INITIAL-ELEMENT keyword)
185   (initial-element-default (required-argument) :read-only t)
186   ;; how many bits per element
187   (n-bits (required-argument) :type index :read-only t)
188   ;; the low-level type code
189   (typecode (required-argument) :type index :read-only t)
190   ;; the number of extra elements we use at the end of the array for
191   ;; low level hackery (e.g., one element for arrays of BASE-CHAR,
192   ;; which is used for a fixed #\NULL so that when we call out to C
193   ;; we don't need to cons a new copy)
194   (n-pad-elements (required-argument) :type index :read-only t))
195
196 (defparameter *specialized-array-element-type-properties*
197   (map 'simple-vector
198        (lambda (args)
199          (destructuring-bind (type-spec &rest rest) args
200            (let ((ctype (specifier-type type-spec)))
201              (apply #'!make-saetp ctype rest))))
202        `((base-char ,(code-char 0) 8 ,sb!vm:simple-string-type
203                     ;; (SIMPLE-STRINGs are stored with an extra trailing
204                     ;; #\NULL for convenience in calling out to C.)
205                     :n-pad-elements 1)
206          (single-float 0.0s0 32 ,sb!vm:simple-array-single-float-type)
207          (double-float 0.0d0 64 ,sb!vm:simple-array-double-float-type)
208          #!+long-float (long-float 0.0L0 #!+x86 96 #!+sparc 128
209                                    ,sb!vm:simple-array-long-float-type)
210          (bit 0 1 ,sb!vm:simple-bit-vector-type)
211          ((unsigned-byte 2) 0 2 ,sb!vm:simple-array-unsigned-byte-2-type)
212          ((unsigned-byte 4) 0 4 ,sb!vm:simple-array-unsigned-byte-4-type)
213          ((unsigned-byte 8) 0 8 ,sb!vm:simple-array-unsigned-byte-8-type)
214          ((unsigned-byte 16) 0 16 ,sb!vm:simple-array-unsigned-byte-16-type)
215          ((unsigned-byte 32) 0 32 ,sb!vm:simple-array-unsigned-byte-32-type)
216          ((signed-byte 8) 0 8 ,sb!vm:simple-array-signed-byte-8-type)
217          ((signed-byte 16) 0 16 ,sb!vm:simple-array-signed-byte-16-type)
218          ((signed-byte 30) 0 32 ,sb!vm:simple-array-signed-byte-30-type)
219          ((signed-byte 32) 0 32 ,sb!vm:simple-array-signed-byte-32-type)
220          ((complex single-float) #C(0.0s0 0.0s0) 64
221           ,sb!vm:simple-array-complex-single-float-type)
222          ((complex double-float) #C(0.0d0 0.0d0) 128
223           ,sb!vm:simple-array-complex-double-float-type)
224          #!+long-float ((complex long-float) #C(0.0L0 0.0L0)
225                         #!+x86 192 #!+sparc 256
226                         ,sb!vm:simple-array-complex-long-float-type)
227          (t 0 32 ,sb!vm:simple-vector-type))))
228
229 ;;; The integer type restriction on the length ensures that it will be
230 ;;; a vector. The lack of :ADJUSTABLE, :FILL-POINTER, and
231 ;;; :DISPLACED-TO keywords ensures that it will be simple.
232 (deftransform make-array ((length &key initial-element element-type)
233                           (integer &rest *))
234   (let* ((eltype (cond ((not element-type) t)
235                        ((not (constant-continuation-p element-type))
236                         (give-up-ir1-transform
237                          "ELEMENT-TYPE is not constant."))
238                        (t
239                         (continuation-value element-type))))
240          (len (if (constant-continuation-p length)
241                   (continuation-value length)
242                   '*))
243          (result-type-spec `(simple-array ,eltype (,len)))
244          (eltype-type (specifier-type eltype))
245          (saetp (find-if (lambda (saetp)
246                            (csubtypep eltype-type (saetp-ctype saetp)))
247                          *specialized-array-element-type-properties*)))
248     (unless saetp
249       (give-up-ir1-transform
250        "cannot open-code creation of ~S" spec))
251
252     (let* ((initial-element-default (saetp-initial-element-default saetp))
253            (n-bits-per-element (saetp-n-bits saetp))
254            (typecode (saetp-typecode saetp))
255            (n-pad-elements (saetp-n-pad-elements saetp))
256            (padded-length-form (if (zerop n-pad-elements)
257                                    'length
258                                    `(+ length ,n-pad-elements)))
259            (n-words-form
260             (if (>= n-bits-per-element sb!vm:word-bits)
261                 `(* ,padded-length-form
262                     (the fixnum ; i.e., not RATIO
263                       ,(/ n-bits-per-element sb!vm:word-bits)))
264                 (let ((n-elements-per-word (/ sb!vm:word-bits
265                                               n-bits-per-element)))
266                   (declare (type index n-elements-per-word)) ; i.e., not RATIO
267                   `(ceiling ,padded-length-form ,n-elements-per-word))))
268            (bare-constructor-form
269             `(truly-the ,result-type-spec
270                         (allocate-vector ,typecode length ,n-words-form)))
271            (initial-element-form (if initial-element
272                                      'initial-element
273                                      initial-element-default)))
274       (values
275        (cond (;; Can we skip the FILL step?
276               (or (null initial-element)
277                   (and (constant-continuation-p initial-element)
278                        (eql (continuation-value initial-element)
279                             initial-element-default)))
280               (unless (csubtypep (ctype-of initial-element-default)
281                                  eltype-type)
282                 ;; This situation arises e.g. in
283                 ;;   (MAKE-ARRAY 4 :ELEMENT-TYPE '(INTEGER 1 5))
284                 ;; ANSI's definition of MAKE-ARRAY says "If
285                 ;; INITIAL-ELEMENT is not supplied, the consequences
286                 ;; of later reading an uninitialized element of
287                 ;; new-array are undefined," so this could be legal
288                 ;; code as long as the user plans to write before he
289                 ;; reads, and if he doesn't we're free to do anything
290                 ;; we like. But in case the user doesn't know to write
291                 ;; elements before he reads elements (or to read
292                 ;; manuals before he writes code:-), we'll signal a
293                 ;; STYLE-WARNING in case he didn't realize this.
294                 (compiler-note "The default initial element ~S is not a ~S."
295                                initial-element-default
296                                eltype))
297               bare-constructor-form)
298              (t
299               `(truly-the ,result-type-spec
300                           (fill ,bare-constructor-form
301                                 ,initial-element-form))))
302        '((declare (type index length)))))))
303
304 ;;; The list type restriction does not ensure that the result will be a
305 ;;; multi-dimensional array. But the lack of adjustable, fill-pointer,
306 ;;; and displaced-to keywords ensures that it will be simple.
307 (deftransform make-array ((dims &key initial-element element-type)
308                           (list &rest *))
309   (unless (or (null element-type) (constant-continuation-p element-type))
310     (give-up-ir1-transform
311      "The element-type is not constant; cannot open code array creation."))
312   (unless (constant-continuation-p dims)
313     (give-up-ir1-transform
314      "The dimension list is not constant; cannot open code array creation."))
315   (let ((dims (continuation-value dims)))
316     (unless (every #'integerp dims)
317       (give-up-ir1-transform
318        "The dimension list contains something other than an integer: ~S"
319        dims))
320     (if (= (length dims) 1)
321         `(make-array ',(car dims)
322                      ,@(when initial-element
323                          '(:initial-element initial-element))
324                      ,@(when element-type
325                          '(:element-type element-type)))
326         (let* ((total-size (reduce #'* dims))
327                (rank (length dims))
328                (spec `(simple-array
329                        ,(cond ((null element-type) t)
330                               ((constant-continuation-p element-type)
331                                (continuation-value element-type))
332                               (t '*))
333                            ,(make-list rank :initial-element '*))))
334           `(let ((header (make-array-header sb!vm:simple-array-type ,rank)))
335              (setf (%array-fill-pointer header) ,total-size)
336              (setf (%array-fill-pointer-p header) nil)
337              (setf (%array-available-elements header) ,total-size)
338              (setf (%array-data-vector header)
339                    (make-array ,total-size
340                                ,@(when element-type
341                                    '(:element-type element-type))
342                                ,@(when initial-element
343                                    '(:initial-element initial-element))))
344              (setf (%array-displaced-p header) nil)
345              ,@(let ((axis -1))
346                  (mapcar #'(lambda (dim)
347                              `(setf (%array-dimension header ,(incf axis))
348                                     ,dim))
349                          dims))
350              (truly-the ,spec header))))))
351 \f
352 ;;;; miscellaneous properties of arrays
353
354 ;;; Transforms for various array properties. If the property is know
355 ;;; at compile time because of a type spec, use that constant value.
356
357 ;;; If we can tell the rank from the type info, use it instead.
358 (deftransform array-rank ((array))
359   (let ((array-type (continuation-type array)))
360     (unless (array-type-p array-type)
361       (give-up-ir1-transform))
362     (let ((dims (array-type-dimensions array-type)))
363       (if (not (listp dims))
364           (give-up-ir1-transform
365            "The array rank is not known at compile time: ~S"
366            dims)
367           (length dims)))))
368
369 ;;; If we know the dimensions at compile time, just use it. Otherwise,
370 ;;; if we can tell that the axis is in bounds, convert to
371 ;;; %ARRAY-DIMENSION (which just indirects the array header) or length
372 ;;; (if it's simple and a vector).
373 (deftransform array-dimension ((array axis)
374                                (array index))
375   (unless (constant-continuation-p axis)
376     (give-up-ir1-transform "The axis is not constant."))
377   (let ((array-type (continuation-type array))
378         (axis (continuation-value axis)))
379     (unless (array-type-p array-type)
380       (give-up-ir1-transform))
381     (let ((dims (array-type-dimensions array-type)))
382       (unless (listp dims)
383         (give-up-ir1-transform
384          "The array dimensions are unknown; must call ARRAY-DIMENSION at runtime."))
385       (unless (> (length dims) axis)
386         (abort-ir1-transform "The array has dimensions ~S, ~D is too large."
387                              dims
388                              axis))
389       (let ((dim (nth axis dims)))
390         (cond ((integerp dim)
391                dim)
392               ((= (length dims) 1)
393                (ecase (array-type-complexp array-type)
394                  ((t)
395                   '(%array-dimension array 0))
396                  ((nil)
397                   '(length array))
398                  ((:maybe)
399                   (give-up-ir1-transform
400                    "can't tell whether array is simple"))))
401               (t
402                '(%array-dimension array axis)))))))
403
404 ;;; If the length has been declared and it's simple, just return it.
405 (deftransform length ((vector)
406                       ((simple-array * (*))))
407   (let ((type (continuation-type vector)))
408     (unless (array-type-p type)
409       (give-up-ir1-transform))
410     (let ((dims (array-type-dimensions type)))
411       (unless (and (listp dims) (integerp (car dims)))
412         (give-up-ir1-transform
413          "Vector length is unknown, must call LENGTH at runtime."))
414       (car dims))))
415
416 ;;; All vectors can get their length by using VECTOR-LENGTH. If it's
417 ;;; simple, it will extract the length slot from the vector. It it's
418 ;;; complex, it will extract the fill pointer slot from the array
419 ;;; header.
420 (deftransform length ((vector) (vector))
421   '(vector-length vector))
422
423 ;;; If a simple array with known dimensions, then VECTOR-LENGTH is a
424 ;;; compile-time constant.
425 (deftransform vector-length ((vector) ((simple-array * (*))))
426   (let ((vtype (continuation-type vector)))
427     (if (array-type-p vtype)
428         (let ((dim (first (array-type-dimensions vtype))))
429           (when (eq dim '*) (give-up-ir1-transform))
430           dim)
431         (give-up-ir1-transform))))
432
433 ;;; Again, if we can tell the results from the type, just use it.
434 ;;; Otherwise, if we know the rank, convert into a computation based
435 ;;; on array-dimension. We can wrap a TRULY-THE INDEX around the
436 ;;; multiplications because we know that the total size must be an
437 ;;; INDEX.
438 (deftransform array-total-size ((array)
439                                 (array))
440   (let ((array-type (continuation-type array)))
441     (unless (array-type-p array-type)
442       (give-up-ir1-transform))
443     (let ((dims (array-type-dimensions array-type)))
444       (unless (listp dims)
445         (give-up-ir1-transform "can't tell the rank at compile time"))
446       (if (member '* dims)
447           (do ((form 1 `(truly-the index
448                                    (* (array-dimension array ,i) ,form)))
449                (i 0 (1+ i)))
450               ((= i (length dims)) form))
451           (reduce #'* dims)))))
452
453 ;;; Only complex vectors have fill pointers.
454 (deftransform array-has-fill-pointer-p ((array))
455   (let ((array-type (continuation-type array)))
456     (unless (array-type-p array-type)
457       (give-up-ir1-transform))
458     (let ((dims (array-type-dimensions array-type)))
459       (if (and (listp dims) (not (= (length dims) 1)))
460           nil
461           (ecase (array-type-complexp array-type)
462             ((t)
463              t)
464             ((nil)
465              nil)
466             ((:maybe)
467              (give-up-ir1-transform
468               "The array type is ambiguous; must call ~
469               ARRAY-HAS-FILL-POINTER-P at runtime.")))))))
470
471 ;;; Primitive used to verify indices into arrays. If we can tell at
472 ;;; compile-time or we are generating unsafe code, don't bother with
473 ;;; the VOP.
474 (deftransform %check-bound ((array dimension index))
475   (unless (constant-continuation-p dimension)
476     (give-up-ir1-transform))
477   (let ((dim (continuation-value dimension)))
478     `(the (integer 0 ,dim) index)))
479 (deftransform %check-bound ((array dimension index) * *
480                             :policy (and (> speed safety) (= safety 0)))
481   'index)
482 \f
483 ;;;; WITH-ARRAY-DATA
484
485 ;;; This checks to see whether the array is simple and the start and
486 ;;; end are in bounds. If so, it proceeds with those values.
487 ;;; Otherwise, it calls %WITH-ARRAY-DATA. Note that %WITH-ARRAY-DATA
488 ;;; may be further optimized.
489 ;;;
490 ;;; Given any ARRAY, bind DATA-VAR to the array's data vector and
491 ;;; START-VAR and END-VAR to the start and end of the designated
492 ;;; portion of the data vector. SVALUE and EVALUE are any start and
493 ;;; end specified to the original operation, and are factored into the
494 ;;; bindings of START-VAR and END-VAR. OFFSET-VAR is the cumulative
495 ;;; offset of all displacements encountered, and does not include
496 ;;; SVALUE.
497 ;;;
498 ;;; When FORCE-INLINE is set, the underlying %WITH-ARRAY-DATA form is
499 ;;; forced to be inline, overriding the ordinary judgment of the
500 ;;; %WITH-ARRAY-DATA DEFTRANSFORMs. Ordinarily the DEFTRANSFORMs are
501 ;;; fairly picky about their arguments, figuring that if you haven't
502 ;;; bothered to get all your ducks in a row, you probably don't care
503 ;;; that much about speed anyway! But in some cases it makes sense to
504 ;;; do type testing inside %WITH-ARRAY-DATA instead of outside, and
505 ;;; the DEFTRANSFORM can't tell that that's going on, so it can make
506 ;;; sense to use FORCE-INLINE option in that case.
507 (def!macro with-array-data (((data-var array &key offset-var)
508                              (start-var &optional (svalue 0))
509                              (end-var &optional (evalue nil))
510                              &key force-inline)
511                             &body forms)
512   (once-only ((n-array array)
513               (n-svalue `(the index ,svalue))
514               (n-evalue `(the (or index null) ,evalue)))
515     `(multiple-value-bind (,data-var
516                            ,start-var
517                            ,end-var
518                            ,@(when offset-var `(,offset-var)))
519          (if (not (array-header-p ,n-array))
520              (let ((,n-array ,n-array))
521                (declare (type (simple-array * (*)) ,n-array))
522                ,(once-only ((n-len `(length ,n-array))
523                             (n-end `(or ,n-evalue ,n-len)))
524                   `(if (<= ,n-svalue ,n-end ,n-len)
525                        ;; success
526                        (values ,n-array ,n-svalue ,n-end 0)
527                        ;; failure: Make a NOTINLINE call to
528                        ;; %WITH-ARRAY-DATA with our bad data
529                        ;; to cause the error to be signalled.
530                        (locally
531                          (declare (notinline %with-array-data))
532                          (%with-array-data ,n-array ,n-svalue ,n-evalue)))))
533              (,(if force-inline '%with-array-data-macro '%with-array-data)
534               ,n-array ,n-svalue ,n-evalue))
535        ,@forms)))
536
537 ;;; This is the fundamental definition of %WITH-ARRAY-DATA, for use in
538 ;;; DEFTRANSFORMs and DEFUNs.
539 (def!macro %with-array-data-macro (array
540                                    start
541                                    end
542                                    &key
543                                    (element-type '*)
544                                    unsafe?
545                                    fail-inline?)
546   (let ((size (gensym "SIZE-"))
547         (defaulted-end (gensym "DEFAULTED-END-"))
548         (data (gensym "DATA-"))
549         (cumulative-offset (gensym "CUMULATIVE-OFFSET-")))
550     `(let* ((,size (array-total-size ,array))
551             (,defaulted-end
552               (cond (,end
553                      (unless (or ,unsafe? (<= ,end ,size))
554                        ,(if fail-inline?
555                             `(error "End ~D is greater than total size ~D."
556                                     ,end ,size)
557                             `(failed-%with-array-data ,array ,start ,end)))
558                      ,end)
559                     (t ,size))))
560        (unless (or ,unsafe? (<= ,start ,defaulted-end))
561          ,(if fail-inline?
562               `(error "Start ~D is greater than end ~D." ,start ,defaulted-end)
563               `(failed-%with-array-data ,array ,start ,end)))
564        (do ((,data ,array (%array-data-vector ,data))
565             (,cumulative-offset 0
566                                 (+ ,cumulative-offset
567                                    (%array-displacement ,data))))
568            ((not (array-header-p ,data))
569             (values (the (simple-array ,element-type 1) ,data)
570                     (the index (+ ,cumulative-offset ,start))
571                     (the index (+ ,cumulative-offset ,defaulted-end))
572                     (the index ,cumulative-offset)))
573          (declare (type index ,cumulative-offset))))))
574
575 (deftransform %with-array-data ((array start end)
576                                 ;; Note: This transform is limited to
577                                 ;; VECTOR only because I happened to
578                                 ;; create it in order to get sequence
579                                 ;; function operations to be more
580                                 ;; efficient. It might very well be
581                                 ;; reasonable to allow general ARRAY
582                                 ;; here, I just haven't tried to
583                                 ;; understand the performance issues
584                                 ;; involved. -- WHN
585                                 (vector index (or index null))
586                                 *
587                                 :important t
588                                 :node node
589                                 :policy (> speed space))
590   "inline non-SIMPLE-vector-handling logic"
591   (let ((element-type (upgraded-element-type-specifier-or-give-up array)))
592     `(%with-array-data-macro array start end
593                              :unsafe? ,(policy node (= safety 0))
594                              :element-type ,element-type)))
595 \f
596 ;;;; array accessors
597
598 ;;; We convert all typed array accessors into AREF and %ASET with type
599 ;;; assertions on the array.
600 (macrolet ((define-frob (reffer setter type)
601              `(progn
602                 (def-source-transform ,reffer (a &rest i)
603                   (if (byte-compiling)
604                       (values nil t)
605                       `(aref (the ,',type ,a) ,@i)))
606                 (def-source-transform ,setter (a &rest i)
607                   (if (byte-compiling)
608                       (values nil t)
609                       `(%aset (the ,',type ,a) ,@i))))))
610   (define-frob svref %svset simple-vector)
611   (define-frob schar %scharset simple-string)
612   (define-frob char %charset string)
613   (define-frob sbit %sbitset (simple-array bit))
614   (define-frob bit %bitset (array bit)))
615
616 (macrolet (;; This is a handy macro for computing the row-major index
617            ;; given a set of indices. We wrap each index with a call
618            ;; to %CHECK-BOUND to ensure that everything works out
619            ;; correctly. We can wrap all the interior arithmetic with
620            ;; TRULY-THE INDEX because we know the the resultant
621            ;; row-major index must be an index.
622            (with-row-major-index ((array indices index &optional new-value)
623                                   &rest body)
624              `(let (n-indices dims)
625                 (dotimes (i (length ,indices))
626                   (push (make-symbol (format nil "INDEX-~D" i)) n-indices)
627                   (push (make-symbol (format nil "DIM-~D" i)) dims))
628                 (setf n-indices (nreverse n-indices))
629                 (setf dims (nreverse dims))
630                 `(lambda (,',array ,@n-indices
631                                    ,@',(when new-value (list new-value)))
632                    (let* (,@(let ((,index -1))
633                               (mapcar (lambda (name)
634                                         `(,name (array-dimension
635                                                  ,',array
636                                                  ,(incf ,index))))
637                                       dims))
638                             (,',index
639                              ,(if (null dims)
640                                   0
641                                 (do* ((dims dims (cdr dims))
642                                       (indices n-indices (cdr indices))
643                                       (last-dim nil (car dims))
644                                       (form `(%check-bound ,',array
645                                                            ,(car dims)
646                                                            ,(car indices))
647                                             `(truly-the
648                                               index
649                                               (+ (truly-the index
650                                                             (* ,form
651                                                                ,last-dim))
652                                                  (%check-bound
653                                                   ,',array
654                                                   ,(car dims)
655                                                   ,(car indices))))))
656                                     ((null (cdr dims)) form)))))
657                      ,',@body)))))
658
659   ;; Just return the index after computing it.
660   (deftransform array-row-major-index ((array &rest indices))
661     (with-row-major-index (array indices index)
662       index))
663
664   ;; Convert AREF and %ASET into a HAIRY-DATA-VECTOR-REF (or
665   ;; HAIRY-DATA-VECTOR-SET) with the set of indices replaced with the an
666   ;; expression for the row major index.
667   (deftransform aref ((array &rest indices))
668     (with-row-major-index (array indices index)
669       (hairy-data-vector-ref array index)))
670   (deftransform %aset ((array &rest stuff))
671     (let ((indices (butlast stuff)))
672       (with-row-major-index (array indices index new-value)
673         (hairy-data-vector-set array index new-value)))))
674
675 ;;; Just convert into a HAIRY-DATA-VECTOR-REF (or
676 ;;; HAIRY-DATA-VECTOR-SET) after checking that the index is inside the
677 ;;; array total size.
678 (deftransform row-major-aref ((array index))
679   `(hairy-data-vector-ref array
680                           (%check-bound array (array-total-size array) index)))
681 (deftransform %set-row-major-aref ((array index new-value))
682   `(hairy-data-vector-set array
683                           (%check-bound array (array-total-size array) index)
684                           new-value))
685 \f
686 ;;;; bit-vector array operation canonicalization
687 ;;;;
688 ;;;; We convert all bit-vector operations to have the result array
689 ;;;; specified. This allows any result allocation to be open-coded,
690 ;;;; and eliminates the need for any VM-dependent transforms to handle
691 ;;;; these cases.
692
693 (dolist (fun '(bit-and bit-ior bit-xor bit-eqv bit-nand bit-nor bit-andc1
694                        bit-andc2 bit-orc1 bit-orc2))
695   ;; Make a result array if result is NIL or unsupplied.
696   (deftransform fun ((bit-array-1 bit-array-2 &optional result-bit-array)
697                      '(bit-vector bit-vector &optional null) '*
698                      :eval-name t
699                      :policy (>= speed space))
700     `(,fun bit-array-1 bit-array-2
701            (make-array (length bit-array-1) :element-type 'bit)))
702   ;; If result is T, make it the first arg.
703   (deftransform fun ((bit-array-1 bit-array-2 result-bit-array)
704                      '(bit-vector bit-vector (member t)) '*
705                      :eval-name t)
706     `(,fun bit-array-1 bit-array-2 bit-array-1)))
707
708 ;;; Similar for BIT-NOT, but there is only one arg...
709 (deftransform bit-not ((bit-array-1 &optional result-bit-array)
710                        (bit-vector &optional null) *
711                        :policy (>= speed space))
712   '(bit-not bit-array-1
713             (make-array (length bit-array-1) :element-type 'bit)))
714 (deftransform bit-not ((bit-array-1 result-bit-array)
715                        (bit-vector (constant-argument t)))
716   '(bit-not bit-array-1 bit-array-1))
717 ;;; FIXME: What does (CONSTANT-ARGUMENT T) mean? Is it the same thing
718 ;;; as (CONSTANT-ARGUMENT (MEMBER T)), or does it mean any constant
719 ;;; value?
720 \f
721 ;;; Pick off some constant cases.
722 (deftransform array-header-p ((array) (array))
723   (let ((type (continuation-type array)))
724     (declare (optimize (safety 3)))
725     (unless (array-type-p type)
726       (give-up-ir1-transform))
727     (let ((dims (array-type-dimensions type)))
728       (cond ((csubtypep type (specifier-type '(simple-array * (*))))
729              ;; No array header.
730              nil)
731             ((and (listp dims) (> (length dims) 1))
732              ;; Multi-dimensional array, will have a header.
733              t)
734             (t
735              (give-up-ir1-transform))))))