rename SB-SIMPLE-STREAMS utility function
[sbcl.git] / src / compiler / array-tran.lisp
blobd70cdb536e065660d887a0f35a5e6558e083ef65
1 ;;;; array-specific optimizers and transforms
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.
12 (in-package "SB!C")
14 ;;;; utilities for optimizing array operations
16 ;;; Return UPGRADED-ARRAY-ELEMENT-TYPE for LVAR, 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 (lvar)
20 (let ((element-type-specifier (upgraded-element-type-specifier lvar)))
21 (if (eq element-type-specifier '*)
22 (give-up-ir1-transform
23 "upgraded array element type not known at compile time")
24 element-type-specifier)))
26 (defun upgraded-element-type-specifier (lvar)
27 (type-specifier (array-type-upgraded-element-type (lvar-type lvar))))
29 ;;; Array access functions return an object from the array, hence its type is
30 ;;; going to be the array upgraded element type. Secondary return value is the
31 ;;; known supertype of the upgraded-array-element-type, if if the exact
32 ;;; U-A-E-T is not known. (If it is NIL, the primary return value is as good
33 ;;; as it gets.)
34 (defun array-type-upgraded-element-type (type)
35 (typecase type
36 ;; Note that this IF mightn't be satisfied even if the runtime
37 ;; value is known to be a subtype of some specialized ARRAY, because
38 ;; we can have values declared e.g. (AND SIMPLE-VECTOR UNKNOWN-TYPE),
39 ;; which are represented in the compiler as INTERSECTION-TYPE, not
40 ;; array type.
41 (array-type
42 (values (array-type-specialized-element-type type) nil))
43 ;; Deal with intersection types (bug #316078)
44 (intersection-type
45 (let ((intersection-types (intersection-type-types type))
46 (element-type *wild-type*)
47 (element-supertypes nil))
48 (dolist (intersection-type intersection-types)
49 (multiple-value-bind (cur-type cur-supertype)
50 (array-type-upgraded-element-type intersection-type)
51 ;; According to ANSI, an array may have only one specialized
52 ;; element type - e.g. '(and (array foo) (array bar))
53 ;; is not a valid type unless foo and bar upgrade to the
54 ;; same element type.
55 (cond
56 ((eq cur-type *wild-type*)
57 nil)
58 ((eq element-type *wild-type*)
59 (setf element-type cur-type))
60 ((or (not (csubtypep cur-type element-type))
61 (not (csubtypep element-type cur-type)))
62 ;; At least two different element types where given, the array
63 ;; is valid iff they represent the same type.
65 ;; FIXME: TYPE-INTERSECTION already takes care of disjoint array
66 ;; types, so I believe this code should be unreachable. Maybe
67 ;; signal a warning / error instead?
68 (setf element-type *empty-type*)))
69 (push (or cur-supertype (type-*-to-t cur-type))
70 element-supertypes)))
71 (values element-type
72 (when (and (eq *wild-type* element-type) element-supertypes)
73 (apply #'type-intersection element-supertypes)))))
74 (union-type
75 (let ((union-types (union-type-types type))
76 (element-type nil)
77 (element-supertypes nil))
78 (dolist (union-type union-types)
79 (multiple-value-bind (cur-type cur-supertype)
80 (array-type-upgraded-element-type union-type)
81 (cond
82 ((eq element-type *wild-type*)
83 nil)
84 ((eq element-type nil)
85 (setf element-type cur-type))
86 ((or (eq cur-type *wild-type*)
87 ;; If each of the two following tests fail, it is not
88 ;; possible to determine the element-type of the array
89 ;; because more than one kind of element-type was provided
90 ;; like in '(or (array foo) (array bar)) although a
91 ;; supertype (or foo bar) may be provided as the second
92 ;; returned value returned. See also the KLUDGE below.
93 (not (csubtypep cur-type element-type))
94 (not (csubtypep element-type cur-type)))
95 (setf element-type *wild-type*)))
96 (push (or cur-supertype (type-*-to-t cur-type))
97 element-supertypes)))
98 (values element-type
99 (when (eq *wild-type* element-type)
100 (apply #'type-union element-supertypes)))))
101 (member-type
102 ;; Convert member-type to an union-type.
103 (array-type-upgraded-element-type
104 (apply #'type-union (mapcar #'ctype-of (member-type-members type)))))
106 ;; KLUDGE: there is no good answer here, but at least
107 ;; *wild-type* won't cause HAIRY-DATA-VECTOR-{REF,SET} to be
108 ;; erroneously optimized (see generic/vm-tran.lisp) -- CSR,
109 ;; 2002-08-21
110 (values *wild-type* nil))))
112 (defun array-type-declared-element-type (type)
113 (if (array-type-p type)
114 (array-type-element-type type)
115 *wild-type*))
117 ;;; The ``new-value'' for array setters must fit in the array, and the
118 ;;; return type is going to be the same as the new-value for SETF
119 ;;; functions.
120 (defun assert-new-value-type (new-value array)
121 (let ((type (lvar-type array)))
122 (when (array-type-p type)
123 (assert-lvar-type
124 new-value
125 (array-type-specialized-element-type type)
126 (lexenv-policy (node-lexenv (lvar-dest new-value))))))
127 (lvar-type new-value))
129 ;;; Return true if ARG is NIL, or is a constant-lvar whose
130 ;;; value is NIL, false otherwise.
131 (defun unsupplied-or-nil (arg)
132 (declare (type (or lvar null) arg))
133 (or (not arg)
134 (and (constant-lvar-p arg)
135 (not (lvar-value arg)))))
137 (defun supplied-and-true (arg)
138 (and arg
139 (constant-lvar-p arg)
140 (lvar-value arg)
143 ;;;; DERIVE-TYPE optimizers
145 ;;; Array operations that use a specific number of indices implicitly
146 ;;; assert that the array is of that rank.
147 (defun assert-array-rank (array rank)
148 (assert-lvar-type
149 array
150 (specifier-type `(array * ,(make-list rank :initial-element '*)))
151 (lexenv-policy (node-lexenv (lvar-dest array)))))
153 (defun derive-aref-type (array)
154 (multiple-value-bind (uaet other)
155 (array-type-upgraded-element-type (lvar-type array))
156 (or other uaet)))
158 (defoptimizer (array-in-bounds-p derive-type) ((array &rest indices))
159 (assert-array-rank array (length indices))
160 *universal-type*)
162 (deftransform array-in-bounds-p ((array &rest subscripts))
163 (flet ((give-up ()
164 (give-up-ir1-transform
165 "~@<lower array bounds unknown or negative and upper bounds not ~
166 negative~:@>"))
167 (bound-known-p (x)
168 (integerp x))) ; might be NIL or *
169 (block nil
170 (let ((dimensions (array-type-dimensions-or-give-up
171 (lvar-conservative-type array))))
172 ;; Might be *. (Note: currently this is never true, because the type
173 ;; derivation infers the rank from the call to ARRAY-IN-BOUNDS-P, but
174 ;; let's keep this future proof.)
175 (when (eq '* dimensions)
176 (give-up-ir1-transform "array bounds unknown"))
177 ;; shortcut for zero dimensions
178 (when (some (lambda (dim)
179 (and (bound-known-p dim) (zerop dim)))
180 dimensions)
181 (return nil))
182 ;; we first collect the subscripts LVARs' bounds and see whether
183 ;; we can already decide on the result of the optimization without
184 ;; even taking a look at the dimensions.
185 (flet ((subscript-bounds (subscript)
186 (let* ((type1 (lvar-type subscript))
187 (type2 (if (csubtypep type1 (specifier-type 'integer))
188 (weaken-integer-type type1 :range-only t)
189 (give-up)))
190 (low (if (integer-type-p type2)
191 (numeric-type-low type2)
192 (give-up)))
193 (high (numeric-type-high type2)))
194 (cond
195 ((and (or (not (bound-known-p low)) (minusp low))
196 (or (not (bound-known-p high)) (not (minusp high))))
197 ;; can't be sure about the lower bound and the upper bound
198 ;; does not give us a definite clue either.
199 (give-up))
200 ((and (bound-known-p high) (minusp high))
201 (return nil)) ; definitely below lower bound (zero).
203 (cons low high))))))
204 (let* ((subscripts-bounds (mapcar #'subscript-bounds subscripts))
205 (subscripts-lower-bound (mapcar #'car subscripts-bounds))
206 (subscripts-upper-bound (mapcar #'cdr subscripts-bounds))
207 (in-bounds 0))
208 (mapcar (lambda (low high dim)
209 (cond
210 ;; first deal with infinite bounds
211 ((some (complement #'bound-known-p) (list low high dim))
212 (when (and (bound-known-p dim) (bound-known-p low) (<= dim low))
213 (return nil)))
214 ;; now we know all bounds
215 ((>= low dim)
216 (return nil))
217 ((< high dim)
218 (aver (not (minusp low)))
219 (incf in-bounds))
221 (give-up))))
222 subscripts-lower-bound
223 subscripts-upper-bound
224 dimensions)
225 (if (eql in-bounds (length dimensions))
227 (give-up))))))))
229 (defoptimizer (aref derive-type) ((array &rest indices) node)
230 (assert-array-rank array (length indices))
231 (derive-aref-type array))
233 (defoptimizer (%aset derive-type) ((array &rest stuff))
234 (assert-array-rank array (1- (length stuff)))
235 (assert-new-value-type (car (last stuff)) array))
237 (macrolet ((define (name)
238 `(defoptimizer (,name derive-type) ((array index))
239 (derive-aref-type array))))
240 (define hairy-data-vector-ref)
241 (define hairy-data-vector-ref/check-bounds)
242 (define data-vector-ref))
244 #!+(or x86 x86-64)
245 (defoptimizer (data-vector-ref-with-offset derive-type) ((array index offset))
246 (derive-aref-type array))
248 (macrolet ((define (name)
249 `(defoptimizer (,name derive-type) ((array index new-value))
250 (assert-new-value-type new-value array))))
251 (define hairy-data-vector-set)
252 (define hairy-data-vector-set/check-bounds)
253 (define data-vector-set))
255 #!+(or x86 x86-64)
256 (defoptimizer (data-vector-set-with-offset derive-type) ((array index offset new-value))
257 (assert-new-value-type new-value array))
259 ;;; Figure out the type of the data vector if we know the argument
260 ;;; element type.
261 (defun derive-%with-array-data/mumble-type (array)
262 (let ((atype (lvar-type array)))
263 (when (array-type-p atype)
264 (specifier-type
265 `(simple-array ,(type-specifier
266 (array-type-specialized-element-type atype))
267 (*))))))
268 (defoptimizer (%with-array-data derive-type) ((array start end))
269 (derive-%with-array-data/mumble-type array))
270 (defoptimizer (%with-array-data/fp derive-type) ((array start end))
271 (derive-%with-array-data/mumble-type array))
273 (defoptimizer (array-row-major-index derive-type) ((array &rest indices))
274 (assert-array-rank array (length indices))
275 *universal-type*)
277 (defoptimizer (row-major-aref derive-type) ((array index))
278 (derive-aref-type array))
280 (defoptimizer (%set-row-major-aref derive-type) ((array index new-value))
281 (assert-new-value-type new-value array))
283 (defoptimizer (make-array derive-type)
284 ((dims &key initial-element element-type initial-contents
285 adjustable fill-pointer displaced-index-offset displaced-to))
286 (let* ((simple (and (unsupplied-or-nil adjustable)
287 (unsupplied-or-nil displaced-to)
288 (unsupplied-or-nil fill-pointer)))
289 (spec
290 (or `(,(if simple 'simple-array 'array)
291 ,(cond ((not element-type) t)
292 ((constant-lvar-p element-type)
293 (let ((ctype (careful-specifier-type
294 (lvar-value element-type))))
295 (cond
296 ((or (null ctype) (unknown-type-p ctype)) '*)
297 (t (sb!xc:upgraded-array-element-type
298 (lvar-value element-type))))))
300 '*))
301 ,(cond ((constant-lvar-p dims)
302 (let* ((val (lvar-value dims))
303 (cdims (if (listp val) val (list val))))
304 (if simple
305 cdims
306 (length cdims))))
307 ((csubtypep (lvar-type dims)
308 (specifier-type 'integer))
309 '(*))
311 '*)))
312 'array)))
313 (if (and (not simple)
314 (or (supplied-and-true adjustable)
315 (supplied-and-true displaced-to)
316 (supplied-and-true fill-pointer)))
317 (careful-specifier-type `(and ,spec (not simple-array)))
318 (careful-specifier-type spec))))
320 ;;;; constructors
322 ;;; Convert VECTOR into a MAKE-ARRAY.
323 (define-source-transform vector (&rest elements)
324 `(make-array ,(length elements) :initial-contents (list ,@elements)))
326 ;;; Just convert it into a MAKE-ARRAY.
327 (deftransform make-string ((length &key
328 (element-type 'character)
329 (initial-element
330 #.*default-init-char-form*)))
331 `(the simple-string (make-array (the index length)
332 :element-type element-type
333 ,@(when initial-element
334 '(:initial-element initial-element)))))
336 (defun rewrite-initial-contents (rank initial-contents env)
337 (if (plusp rank)
338 (if (and (consp initial-contents)
339 (member (car initial-contents) '(list vector sb!impl::backq-list)))
340 `(list ,@(mapcar (lambda (dim)
341 (rewrite-initial-contents (1- rank) dim env))
342 (cdr initial-contents)))
343 initial-contents)
344 ;; This is the important bit: once we are past the level of
345 ;; :INITIAL-CONTENTS that relates to the array structure, reinline LIST
346 ;; and VECTOR so that nested DX isn't screwed up.
347 `(locally (declare (inline list vector))
348 ,initial-contents)))
350 ;;; Prevent open coding DIMENSION and :INITIAL-CONTENTS arguments, so that we
351 ;;; can pick them apart in the DEFTRANSFORMS, and transform '(3) style
352 ;;; dimensions to integer args directly.
353 (define-source-transform make-array (dimensions &rest keyargs &environment env)
354 (if (or (and (fun-lexically-notinline-p 'list)
355 (fun-lexically-notinline-p 'vector))
356 (oddp (length keyargs)))
357 (values nil t)
358 (multiple-value-bind (new-dimensions rank)
359 (flet ((constant-dims (dimensions)
360 (let* ((dims (constant-form-value dimensions env))
361 (canon (if (listp dims) dims (list dims)))
362 (rank (length canon)))
363 (values (if (= rank 1)
364 (list 'quote (car canon))
365 (list 'quote canon))
366 rank))))
367 (cond ((sb!xc:constantp dimensions env)
368 (constant-dims dimensions))
369 ((and (consp dimensions) (eq 'list dimensions))
370 (values dimensions (length (cdr dimensions))))
372 (values dimensions nil))))
373 (let ((initial-contents (getf keyargs :initial-contents)))
374 (when (and initial-contents rank)
375 (setf keyargs (copy-list keyargs)
376 (getf keyargs :initial-contents)
377 (rewrite-initial-contents rank initial-contents env))))
378 `(locally (declare (notinline list vector))
379 (make-array ,new-dimensions ,@keyargs)))))
381 ;;; This baby is a bit of a monster, but it takes care of any MAKE-ARRAY
382 ;;; call which creates a vector with a known element type -- and tries
383 ;;; to do a good job with all the different ways it can happen.
384 (defun transform-make-array-vector (length element-type initial-element
385 initial-contents call)
386 (aver (or (not element-type) (constant-lvar-p element-type)))
387 (let* ((c-length (when (constant-lvar-p length)
388 (lvar-value length)))
389 (elt-spec (if element-type
390 (lvar-value element-type)
392 (elt-ctype (ir1-transform-specifier-type elt-spec))
393 (saetp (if (unknown-type-p elt-ctype)
394 (give-up-ir1-transform "~S is an unknown type: ~S"
395 :element-type elt-spec)
396 (find-saetp-by-ctype elt-ctype)))
397 (default-initial-element (sb!vm:saetp-initial-element-default saetp))
398 (n-bits (sb!vm:saetp-n-bits saetp))
399 (typecode (sb!vm:saetp-typecode saetp))
400 (n-pad-elements (sb!vm:saetp-n-pad-elements saetp))
401 (n-words-form
402 (if c-length
403 (ceiling (* (+ c-length n-pad-elements) n-bits)
404 sb!vm:n-word-bits)
405 (let ((padded-length-form (if (zerop n-pad-elements)
406 'length
407 `(+ length ,n-pad-elements))))
408 (cond
409 ((= n-bits 0) 0)
410 ((>= n-bits sb!vm:n-word-bits)
411 `(* ,padded-length-form
412 ;; i.e., not RATIO
413 ,(the fixnum (/ n-bits sb!vm:n-word-bits))))
415 (let ((n-elements-per-word (/ sb!vm:n-word-bits n-bits)))
416 (declare (type index n-elements-per-word)) ; i.e., not RATIO
417 `(ceiling ,padded-length-form ,n-elements-per-word)))))))
418 (result-spec
419 `(simple-array ,(sb!vm:saetp-specifier saetp) (,(or c-length '*))))
420 (alloc-form
421 `(truly-the ,result-spec
422 (allocate-vector ,typecode (the index length) ,n-words-form))))
423 (cond ((and initial-element initial-contents)
424 (abort-ir1-transform "Both ~S and ~S specified."
425 :initial-contents :initial-element))
426 ;; :INITIAL-CONTENTS (LIST ...), (VECTOR ...) and `(1 1 ,x) with a
427 ;; constant LENGTH.
428 ((and initial-contents c-length
429 (lvar-matches initial-contents
430 :fun-names '(list vector sb!impl::backq-list)
431 :arg-count c-length))
432 (let ((parameters (eliminate-keyword-args
433 call 1 '((:element-type element-type)
434 (:initial-contents initial-contents))))
435 (elt-vars (make-gensym-list c-length))
436 (lambda-list '(length)))
437 (splice-fun-args initial-contents :any c-length)
438 (dolist (p parameters)
439 (setf lambda-list
440 (append lambda-list
441 (if (eq p 'initial-contents)
442 elt-vars
443 (list p)))))
444 `(lambda ,lambda-list
445 (declare (type ,elt-spec ,@elt-vars)
446 (ignorable ,@lambda-list))
447 (truly-the ,result-spec
448 (initialize-vector ,alloc-form ,@elt-vars)))))
449 ;; constant :INITIAL-CONTENTS and LENGTH
450 ((and initial-contents c-length (constant-lvar-p initial-contents))
451 (let ((contents (lvar-value initial-contents)))
452 (unless (= c-length (length contents))
453 (abort-ir1-transform "~S has ~S elements, vector length is ~S."
454 :initial-contents (length contents) c-length))
455 (let ((parameters (eliminate-keyword-args
456 call 1 '((:element-type element-type)
457 (:initial-contents initial-contents)))))
458 `(lambda (length ,@parameters)
459 (declare (ignorable ,@parameters))
460 (truly-the ,result-spec
461 (initialize-vector ,alloc-form
462 ,@(map 'list (lambda (elt)
463 `(the ,elt-spec ',elt))
464 contents)))))))
465 ;; any other :INITIAL-CONTENTS
466 (initial-contents
467 (let ((parameters (eliminate-keyword-args
468 call 1 '((:element-type element-type)
469 (:initial-contents initial-contents)))))
470 `(lambda (length ,@parameters)
471 (declare (ignorable ,@parameters))
472 (unless (= length (length initial-contents))
473 (error "~S has ~S elements, vector length is ~S."
474 :initial-contents (length initial-contents) length))
475 (truly-the ,result-spec
476 (replace ,alloc-form initial-contents)))))
477 ;; :INITIAL-ELEMENT, not EQL to the default
478 ((and initial-element
479 (or (not (constant-lvar-p initial-element))
480 (not (eql default-initial-element (lvar-value initial-element)))))
481 (let ((parameters (eliminate-keyword-args
482 call 1 '((:element-type element-type)
483 (:initial-element initial-element))))
484 (init (if (constant-lvar-p initial-element)
485 (list 'quote (lvar-value initial-element))
486 'initial-element)))
487 `(lambda (length ,@parameters)
488 (declare (ignorable ,@parameters))
489 (truly-the ,result-spec
490 (fill ,alloc-form (the ,elt-spec ,init))))))
491 ;; just :ELEMENT-TYPE, or maybe with :INITIAL-ELEMENT EQL to the
492 ;; default
494 #-sb-xc-host
495 (unless (ctypep default-initial-element elt-ctype)
496 ;; This situation arises e.g. in (MAKE-ARRAY 4 :ELEMENT-TYPE
497 ;; '(INTEGER 1 5)) ANSI's definition of MAKE-ARRAY says "If
498 ;; INITIAL-ELEMENT is not supplied, the consequences of later
499 ;; reading an uninitialized element of new-array are undefined,"
500 ;; so this could be legal code as long as the user plans to
501 ;; write before he reads, and if he doesn't we're free to do
502 ;; anything we like. But in case the user doesn't know to write
503 ;; elements before he reads elements (or to read manuals before
504 ;; he writes code:-), we'll signal a STYLE-WARNING in case he
505 ;; didn't realize this.
506 (if initial-element
507 (compiler-warn "~S ~S is not a ~S"
508 :initial-element default-initial-element
509 elt-spec)
510 (compiler-style-warn "The default initial element ~S is not a ~S."
511 default-initial-element
512 elt-spec)))
513 (let ((parameters (eliminate-keyword-args
514 call 1 '((:element-type element-type)
515 (:initial-element initial-element)))))
516 `(lambda (length ,@parameters)
517 (declare (ignorable ,@parameters))
518 ,alloc-form))))))
520 ;;; IMPORTANT: The order of these three MAKE-ARRAY forms matters: the least
521 ;;; specific must come first, otherwise suboptimal transforms will result for
522 ;;; some forms.
524 (deftransform make-array ((dims &key initial-element element-type
525 adjustable fill-pointer)
526 (t &rest *))
527 (when (null initial-element)
528 (give-up-ir1-transform))
529 (let* ((eltype (cond ((not element-type) t)
530 ((not (constant-lvar-p element-type))
531 (give-up-ir1-transform
532 "ELEMENT-TYPE is not constant."))
534 (lvar-value element-type))))
535 (eltype-type (ir1-transform-specifier-type eltype))
536 (saetp (find-if (lambda (saetp)
537 (csubtypep eltype-type (sb!vm:saetp-ctype saetp)))
538 sb!vm:*specialized-array-element-type-properties*))
539 (creation-form `(make-array dims
540 :element-type ',(type-specifier (sb!vm:saetp-ctype saetp))
541 ,@(when fill-pointer
542 '(:fill-pointer fill-pointer))
543 ,@(when adjustable
544 '(:adjustable adjustable)))))
546 (unless saetp
547 (give-up-ir1-transform "ELEMENT-TYPE not found in *SAETP*: ~S" eltype))
549 (cond ((and (constant-lvar-p initial-element)
550 (eql (lvar-value initial-element)
551 (sb!vm:saetp-initial-element-default saetp)))
552 creation-form)
554 ;; error checking for target, disabled on the host because
555 ;; (CTYPE-OF #\Null) is not possible.
556 #-sb-xc-host
557 (when (constant-lvar-p initial-element)
558 (let ((value (lvar-value initial-element)))
559 (cond
560 ((not (ctypep value (sb!vm:saetp-ctype saetp)))
561 ;; this case will cause an error at runtime, so we'd
562 ;; better WARN about it now.
563 (warn 'array-initial-element-mismatch
564 :format-control "~@<~S is not a ~S (which is the ~
565 ~S of ~S).~@:>"
566 :format-arguments
567 (list
568 value
569 (type-specifier (sb!vm:saetp-ctype saetp))
570 'upgraded-array-element-type
571 eltype)))
572 ((not (ctypep value eltype-type))
573 ;; this case will not cause an error at runtime, but
574 ;; it's still worth STYLE-WARNing about.
575 (compiler-style-warn "~S is not a ~S."
576 value eltype)))))
577 `(let ((array ,creation-form))
578 (multiple-value-bind (vector)
579 (%data-vector-and-index array 0)
580 (fill vector (the ,(sb!vm:saetp-specifier saetp) initial-element)))
581 array)))))
583 ;;; The list type restriction does not ensure that the result will be a
584 ;;; multi-dimensional array. But the lack of adjustable, fill-pointer,
585 ;;; and displaced-to keywords ensures that it will be simple.
587 ;;; FIXME: should we generalize this transform to non-simple (though
588 ;;; non-displaced-to) arrays, given that we have %WITH-ARRAY-DATA to
589 ;;; deal with those? Maybe when the DEFTRANSFORM
590 ;;; %DATA-VECTOR-AND-INDEX in the VECTOR case problem is solved? --
591 ;;; CSR, 2002-07-01
592 (deftransform make-array ((dims &key
593 element-type initial-element initial-contents)
594 (list &key
595 (:element-type (constant-arg *))
596 (:initial-element *)
597 (:initial-contents *))
599 :node call)
600 (block make-array
601 (when (lvar-matches dims :fun-names '(list) :arg-count 1)
602 (let ((length (car (splice-fun-args dims :any 1))))
603 (return-from make-array
604 (transform-make-array-vector length
605 element-type
606 initial-element
607 initial-contents
608 call))))
609 (unless (constant-lvar-p dims)
610 (give-up-ir1-transform
611 "The dimension list is not constant; cannot open code array creation."))
612 (let ((dims (lvar-value dims))
613 (element-type-ctype (and (constant-lvar-p element-type)
614 (ir1-transform-specifier-type
615 (lvar-value element-type)))))
616 (when (unknown-type-p element-type-ctype)
617 (give-up-ir1-transform))
618 (unless (every #'integerp dims)
619 (give-up-ir1-transform
620 "The dimension list contains something other than an integer: ~S"
621 dims))
622 (if (= (length dims) 1)
623 `(make-array ',(car dims)
624 ,@(when element-type
625 '(:element-type element-type))
626 ,@(when initial-element
627 '(:initial-element initial-element))
628 ,@(when initial-contents
629 '(:initial-contents initial-contents)))
630 (let* ((total-size (reduce #'* dims))
631 (rank (length dims))
632 (spec `(simple-array
633 ,(cond ((null element-type) t)
634 (element-type-ctype
635 (sb!xc:upgraded-array-element-type
636 (lvar-value element-type)))
637 (t '*))
638 ,(make-list rank :initial-element '*))))
639 `(let ((header (make-array-header sb!vm:simple-array-widetag ,rank))
640 (data (make-array ,total-size
641 ,@(when element-type
642 '(:element-type element-type))
643 ,@(when initial-element
644 '(:initial-element initial-element)))))
645 ,@(when initial-contents
646 ;; FIXME: This is could be open coded at least a bit too
647 `((sb!impl::fill-data-vector data ',dims initial-contents)))
648 (setf (%array-fill-pointer header) ,total-size)
649 (setf (%array-fill-pointer-p header) nil)
650 (setf (%array-available-elements header) ,total-size)
651 (setf (%array-data-vector header) data)
652 (setf (%array-displaced-p header) nil)
653 (setf (%array-displaced-from header) nil)
654 ,@(let ((axis -1))
655 (mapcar (lambda (dim)
656 `(setf (%array-dimension header ,(incf axis))
657 ,dim))
658 dims))
659 (truly-the ,spec header)))))))
661 (deftransform make-array ((dims &key element-type initial-element initial-contents)
662 (integer &key
663 (:element-type (constant-arg *))
664 (:initial-element *)
665 (:initial-contents *))
667 :node call)
668 (transform-make-array-vector dims
669 element-type
670 initial-element
671 initial-contents
672 call))
674 ;;;; miscellaneous properties of arrays
676 ;;; Transforms for various array properties. If the property is know
677 ;;; at compile time because of a type spec, use that constant value.
679 ;;; Most of this logic may end up belonging in code/late-type.lisp;
680 ;;; however, here we also need the -OR-GIVE-UP for the transforms, and
681 ;;; maybe this is just too sloppy for actual type logic. -- CSR,
682 ;;; 2004-02-18
683 (defun array-type-dimensions-or-give-up (type)
684 (labels ((maybe-array-type-dimensions (type)
685 (typecase type
686 (array-type
687 (array-type-dimensions type))
688 (union-type
689 (let* ((types (remove nil (mapcar #'maybe-array-type-dimensions
690 (union-type-types type))))
691 (result (car types)))
692 (dolist (other (cdr types) result)
693 (unless (equal result other)
694 (give-up-ir1-transform
695 "~@<dimensions of arrays in union type ~S do not match~:@>"
696 (type-specifier type))))))
697 (intersection-type
698 (let* ((types (remove nil (mapcar #'maybe-array-type-dimensions
699 (intersection-type-types type))))
700 (result (car types)))
701 (dolist (other (cdr types) result)
702 (unless (equal result other)
703 (abort-ir1-transform
704 "~@<dimensions of arrays in intersection type ~S do not match~:@>"
705 (type-specifier type)))))))))
706 (or (maybe-array-type-dimensions type)
707 (give-up-ir1-transform
708 "~@<don't know how to extract array dimensions from type ~S~:@>"
709 (type-specifier type)))))
711 (defun conservative-array-type-complexp (type)
712 (typecase type
713 (array-type (array-type-complexp type))
714 (union-type
715 (let ((types (union-type-types type)))
716 (aver (> (length types) 1))
717 (let ((result (conservative-array-type-complexp (car types))))
718 (dolist (type (cdr types) result)
719 (unless (eq (conservative-array-type-complexp type) result)
720 (return-from conservative-array-type-complexp :maybe))))))
721 ;; FIXME: intersection type
722 (t :maybe)))
724 ;;; If we can tell the rank from the type info, use it instead.
725 (deftransform array-rank ((array))
726 (let ((array-type (lvar-type array)))
727 (let ((dims (array-type-dimensions-or-give-up array-type)))
728 (cond ((listp dims)
729 (length dims))
730 ((eq t (array-type-complexp array-type))
731 '(%array-rank array))
733 `(if (array-header-p array)
734 (%array-rank array)
735 1))))))
737 ;;; If we know the dimensions at compile time, just use it. Otherwise,
738 ;;; if we can tell that the axis is in bounds, convert to
739 ;;; %ARRAY-DIMENSION (which just indirects the array header) or length
740 ;;; (if it's simple and a vector).
741 (deftransform array-dimension ((array axis)
742 (array index))
743 (unless (constant-lvar-p axis)
744 (give-up-ir1-transform "The axis is not constant."))
745 ;; Dimensions may change thanks to ADJUST-ARRAY, so we need the
746 ;; conservative type.
747 (let ((array-type (lvar-conservative-type array))
748 (axis (lvar-value axis)))
749 (let ((dims (array-type-dimensions-or-give-up array-type)))
750 (unless (listp dims)
751 (give-up-ir1-transform
752 "The array dimensions are unknown; must call ARRAY-DIMENSION at runtime."))
753 (unless (> (length dims) axis)
754 (abort-ir1-transform "The array has dimensions ~S, ~W is too large."
755 dims
756 axis))
757 (let ((dim (nth axis dims)))
758 (cond ((integerp dim)
759 dim)
760 ((= (length dims) 1)
761 (ecase (conservative-array-type-complexp array-type)
762 ((t)
763 '(%array-dimension array 0))
764 ((nil)
765 '(vector-length array))
766 ((:maybe)
767 `(if (array-header-p array)
768 (%array-dimension array axis)
769 (vector-length array)))))
771 '(%array-dimension array axis)))))))
773 ;;; If the length has been declared and it's simple, just return it.
774 (deftransform length ((vector)
775 ((simple-array * (*))))
776 (let ((type (lvar-type vector)))
777 (let ((dims (array-type-dimensions-or-give-up type)))
778 (unless (and (listp dims) (integerp (car dims)))
779 (give-up-ir1-transform
780 "Vector length is unknown, must call LENGTH at runtime."))
781 (car dims))))
783 ;;; All vectors can get their length by using VECTOR-LENGTH. If it's
784 ;;; simple, it will extract the length slot from the vector. It it's
785 ;;; complex, it will extract the fill pointer slot from the array
786 ;;; header.
787 (deftransform length ((vector) (vector))
788 '(vector-length vector))
790 ;;; If a simple array with known dimensions, then VECTOR-LENGTH is a
791 ;;; compile-time constant.
792 (deftransform vector-length ((vector))
793 (let ((vtype (lvar-type vector)))
794 (let ((dim (first (array-type-dimensions-or-give-up vtype))))
795 (when (eq dim '*)
796 (give-up-ir1-transform))
797 (when (conservative-array-type-complexp vtype)
798 (give-up-ir1-transform))
799 dim)))
801 ;;; Again, if we can tell the results from the type, just use it.
802 ;;; Otherwise, if we know the rank, convert into a computation based
803 ;;; on array-dimension. We can wrap a TRULY-THE INDEX around the
804 ;;; multiplications because we know that the total size must be an
805 ;;; INDEX.
806 (deftransform array-total-size ((array)
807 (array))
808 (let ((array-type (lvar-type array)))
809 (let ((dims (array-type-dimensions-or-give-up array-type)))
810 (unless (listp dims)
811 (give-up-ir1-transform "can't tell the rank at compile time"))
812 (if (member '* dims)
813 (do ((form 1 `(truly-the index
814 (* (array-dimension array ,i) ,form)))
815 (i 0 (1+ i)))
816 ((= i (length dims)) form))
817 (reduce #'* dims)))))
819 ;;; Only complex vectors have fill pointers.
820 (deftransform array-has-fill-pointer-p ((array))
821 (let ((array-type (lvar-type array)))
822 (let ((dims (array-type-dimensions-or-give-up array-type)))
823 (if (and (listp dims) (not (= (length dims) 1)))
825 (ecase (conservative-array-type-complexp array-type)
826 ((t)
828 ((nil)
829 nil)
830 ((:maybe)
831 (give-up-ir1-transform
832 "The array type is ambiguous; must call ~
833 ARRAY-HAS-FILL-POINTER-P at runtime.")))))))
835 ;;; Primitive used to verify indices into arrays. If we can tell at
836 ;;; compile-time or we are generating unsafe code, don't bother with
837 ;;; the VOP.
838 (deftransform %check-bound ((array dimension index) * * :node node)
839 (cond ((policy node (= insert-array-bounds-checks 0))
840 'index)
841 ((not (constant-lvar-p dimension))
842 (give-up-ir1-transform))
844 (let ((dim (lvar-value dimension)))
845 ;; FIXME: Can SPEED > SAFETY weaken this check to INTEGER?
846 `(the (integer 0 (,dim)) index)))))
848 ;;;; WITH-ARRAY-DATA
850 ;;; This checks to see whether the array is simple and the start and
851 ;;; end are in bounds. If so, it proceeds with those values.
852 ;;; Otherwise, it calls %WITH-ARRAY-DATA. Note that %WITH-ARRAY-DATA
853 ;;; may be further optimized.
855 ;;; Given any ARRAY, bind DATA-VAR to the array's data vector and
856 ;;; START-VAR and END-VAR to the start and end of the designated
857 ;;; portion of the data vector. SVALUE and EVALUE are any start and
858 ;;; end specified to the original operation, and are factored into the
859 ;;; bindings of START-VAR and END-VAR. OFFSET-VAR is the cumulative
860 ;;; offset of all displacements encountered, and does not include
861 ;;; SVALUE.
863 ;;; When FORCE-INLINE is set, the underlying %WITH-ARRAY-DATA form is
864 ;;; forced to be inline, overriding the ordinary judgment of the
865 ;;; %WITH-ARRAY-DATA DEFTRANSFORMs. Ordinarily the DEFTRANSFORMs are
866 ;;; fairly picky about their arguments, figuring that if you haven't
867 ;;; bothered to get all your ducks in a row, you probably don't care
868 ;;; that much about speed anyway! But in some cases it makes sense to
869 ;;; do type testing inside %WITH-ARRAY-DATA instead of outside, and
870 ;;; the DEFTRANSFORM can't tell that that's going on, so it can make
871 ;;; sense to use FORCE-INLINE option in that case.
872 (def!macro with-array-data (((data-var array &key offset-var)
873 (start-var &optional (svalue 0))
874 (end-var &optional (evalue nil))
875 &key force-inline check-fill-pointer)
876 &body forms
877 &environment env)
878 (once-only ((n-array array)
879 (n-svalue `(the index ,svalue))
880 (n-evalue `(the (or index null) ,evalue)))
881 (let ((check-bounds (policy env (plusp insert-array-bounds-checks))))
882 `(multiple-value-bind (,data-var
883 ,start-var
884 ,end-var
885 ,@(when offset-var `(,offset-var)))
886 (if (not (array-header-p ,n-array))
887 (let ((,n-array ,n-array))
888 (declare (type (simple-array * (*)) ,n-array))
889 ,(once-only ((n-len (if check-fill-pointer
890 `(length ,n-array)
891 `(array-total-size ,n-array)))
892 (n-end `(or ,n-evalue ,n-len)))
893 (if check-bounds
894 `(if (<= 0 ,n-svalue ,n-end ,n-len)
895 (values ,n-array ,n-svalue ,n-end 0)
896 ,(if check-fill-pointer
897 `(sequence-bounding-indices-bad-error ,n-array ,n-svalue ,n-evalue)
898 `(array-bounding-indices-bad-error ,n-array ,n-svalue ,n-evalue)))
899 `(values ,n-array ,n-svalue ,n-end 0))))
900 ,(if force-inline
901 `(%with-array-data-macro ,n-array ,n-svalue ,n-evalue
902 :check-bounds ,check-bounds
903 :check-fill-pointer ,check-fill-pointer)
904 (if check-fill-pointer
905 `(%with-array-data/fp ,n-array ,n-svalue ,n-evalue)
906 `(%with-array-data ,n-array ,n-svalue ,n-evalue))))
907 ,@forms))))
909 ;;; This is the fundamental definition of %WITH-ARRAY-DATA, for use in
910 ;;; DEFTRANSFORMs and DEFUNs.
911 (def!macro %with-array-data-macro (array
912 start
914 &key
915 (element-type '*)
916 check-bounds
917 check-fill-pointer)
918 (with-unique-names (size defaulted-end data cumulative-offset)
919 `(let* ((,size ,(if check-fill-pointer
920 `(length ,array)
921 `(array-total-size ,array)))
922 (,defaulted-end (or ,end ,size)))
923 ,@(when check-bounds
924 `((unless (<= ,start ,defaulted-end ,size)
925 ,(if check-fill-pointer
926 `(sequence-bounding-indices-bad-error ,array ,start ,end)
927 `(array-bounding-indices-bad-error ,array ,start ,end)))))
928 (do ((,data ,array (%array-data-vector ,data))
929 (,cumulative-offset 0
930 (+ ,cumulative-offset
931 (%array-displacement ,data))))
932 ((not (array-header-p ,data))
933 (values (the (simple-array ,element-type 1) ,data)
934 (the index (+ ,cumulative-offset ,start))
935 (the index (+ ,cumulative-offset ,defaulted-end))
936 (the index ,cumulative-offset)))
937 (declare (type index ,cumulative-offset))))))
939 (defun transform-%with-array-data/muble (array node check-fill-pointer)
940 (let ((element-type (upgraded-element-type-specifier-or-give-up array))
941 (type (lvar-type array))
942 (check-bounds (policy node (plusp insert-array-bounds-checks))))
943 (if (and (array-type-p type)
944 (not (array-type-complexp type))
945 (listp (array-type-dimensions type))
946 (not (null (cdr (array-type-dimensions type)))))
947 ;; If it's a simple multidimensional array, then just return
948 ;; its data vector directly rather than going through
949 ;; %WITH-ARRAY-DATA-MACRO. SBCL doesn't generally generate
950 ;; code that would use this currently, but we have encouraged
951 ;; users to use WITH-ARRAY-DATA and we may use it ourselves at
952 ;; some point in the future for optimized libraries or
953 ;; similar.
954 (if check-bounds
955 `(let* ((data (truly-the (simple-array ,element-type (*))
956 (%array-data-vector array)))
957 (len (length data))
958 (real-end (or end len)))
959 (unless (<= 0 start data-end lend)
960 (sequence-bounding-indices-bad-error array start end))
961 (values data 0 real-end 0))
962 `(let ((data (truly-the (simple-array ,element-type (*))
963 (%array-data-vector array))))
964 (values data 0 (or end (length data)) 0)))
965 `(%with-array-data-macro array start end
966 :check-fill-pointer ,check-fill-pointer
967 :check-bounds ,check-bounds
968 :element-type ,element-type))))
970 ;; It might very well be reasonable to allow general ARRAY here, I
971 ;; just haven't tried to understand the performance issues involved.
972 ;; -- WHN, and also CSR 2002-05-26
973 (deftransform %with-array-data ((array start end)
974 ((or vector simple-array) index (or index null) t)
976 :node node
977 :policy (> speed space))
978 "inline non-SIMPLE-vector-handling logic"
979 (transform-%with-array-data/muble array node nil))
980 (deftransform %with-array-data/fp ((array start end)
981 ((or vector simple-array) index (or index null) t)
983 :node node
984 :policy (> speed space))
985 "inline non-SIMPLE-vector-handling logic"
986 (transform-%with-array-data/muble array node t))
988 ;;;; array accessors
990 ;;; We convert all typed array accessors into AREF and %ASET with type
991 ;;; assertions on the array.
992 (macrolet ((define-bit-frob (reffer setter simplep)
993 `(progn
994 (define-source-transform ,reffer (a &rest i)
995 `(aref (the (,',(if simplep 'simple-array 'array)
997 ,(mapcar (constantly '*) i))
998 ,a) ,@i))
999 (define-source-transform ,setter (a &rest i)
1000 `(%aset (the (,',(if simplep 'simple-array 'array)
1002 ,(cdr (mapcar (constantly '*) i)))
1003 ,a) ,@i)))))
1004 (define-bit-frob sbit %sbitset t)
1005 (define-bit-frob bit %bitset nil))
1006 (macrolet ((define-frob (reffer setter type)
1007 `(progn
1008 (define-source-transform ,reffer (a i)
1009 `(aref (the ,',type ,a) ,i))
1010 (define-source-transform ,setter (a i v)
1011 `(%aset (the ,',type ,a) ,i ,v)))))
1012 (define-frob schar %scharset simple-string)
1013 (define-frob char %charset string))
1015 ;;; We transform SVREF and %SVSET directly into DATA-VECTOR-REF/SET: this is
1016 ;;; around 100 times faster than going through the general-purpose AREF
1017 ;;; transform which ends up doing a lot of work -- and introducing many
1018 ;;; intermediate lambdas, each meaning a new trip through the compiler -- to
1019 ;;; get the same result.
1021 ;;; FIXME: [S]CHAR, and [S]BIT above would almost certainly benefit from a similar
1022 ;;; treatment.
1023 (define-source-transform svref (vector index)
1024 (let ((elt-type (or (when (symbolp vector)
1025 (let ((var (lexenv-find vector vars)))
1026 (when (lambda-var-p var)
1027 (type-specifier
1028 (array-type-declared-element-type (lambda-var-type var))))))
1029 t)))
1030 (with-unique-names (n-vector)
1031 `(let ((,n-vector ,vector))
1032 (the ,elt-type (data-vector-ref
1033 (the simple-vector ,n-vector)
1034 (%check-bound ,n-vector (length ,n-vector) ,index)))))))
1036 (define-source-transform %svset (vector index value)
1037 (let ((elt-type (or (when (symbolp vector)
1038 (let ((var (lexenv-find vector vars)))
1039 (when (lambda-var-p var)
1040 (type-specifier
1041 (array-type-declared-element-type (lambda-var-type var))))))
1042 t)))
1043 (with-unique-names (n-vector)
1044 `(let ((,n-vector ,vector))
1045 (truly-the ,elt-type (data-vector-set
1046 (the simple-vector ,n-vector)
1047 (%check-bound ,n-vector (length ,n-vector) ,index)
1048 (the ,elt-type ,value)))))))
1050 (macrolet (;; This is a handy macro for computing the row-major index
1051 ;; given a set of indices. We wrap each index with a call
1052 ;; to %CHECK-BOUND to ensure that everything works out
1053 ;; correctly. We can wrap all the interior arithmetic with
1054 ;; TRULY-THE INDEX because we know the resultant
1055 ;; row-major index must be an index.
1056 (with-row-major-index ((array indices index &optional new-value)
1057 &rest body)
1058 `(let (n-indices dims)
1059 (dotimes (i (length ,indices))
1060 (push (make-symbol (format nil "INDEX-~D" i)) n-indices)
1061 (push (make-symbol (format nil "DIM-~D" i)) dims))
1062 (setf n-indices (nreverse n-indices))
1063 (setf dims (nreverse dims))
1064 `(lambda (,',array ,@n-indices
1065 ,@',(when new-value (list new-value)))
1066 (let* (,@(let ((,index -1))
1067 (mapcar (lambda (name)
1068 `(,name (array-dimension
1069 ,',array
1070 ,(incf ,index))))
1071 dims))
1072 (,',index
1073 ,(if (null dims)
1075 (do* ((dims dims (cdr dims))
1076 (indices n-indices (cdr indices))
1077 (last-dim nil (car dims))
1078 (form `(%check-bound ,',array
1079 ,(car dims)
1080 ,(car indices))
1081 `(truly-the
1082 index
1083 (+ (truly-the index
1084 (* ,form
1085 ,last-dim))
1086 (%check-bound
1087 ,',array
1088 ,(car dims)
1089 ,(car indices))))))
1090 ((null (cdr dims)) form)))))
1091 ,',@body)))))
1093 ;; Just return the index after computing it.
1094 (deftransform array-row-major-index ((array &rest indices))
1095 (with-row-major-index (array indices index)
1096 index))
1098 ;; Convert AREF and %ASET into a HAIRY-DATA-VECTOR-REF (or
1099 ;; HAIRY-DATA-VECTOR-SET) with the set of indices replaced with the an
1100 ;; expression for the row major index.
1101 (deftransform aref ((array &rest indices))
1102 (with-row-major-index (array indices index)
1103 (hairy-data-vector-ref array index)))
1105 (deftransform %aset ((array &rest stuff))
1106 (let ((indices (butlast stuff)))
1107 (with-row-major-index (array indices index new-value)
1108 (hairy-data-vector-set array index new-value)))))
1110 ;; For AREF of vectors we do the bounds checking in the callee. This
1111 ;; lets us do a significantly more efficient check for simple-arrays
1112 ;; without bloating the code. If we already know the type of the array
1113 ;; with sufficient precision, skip directly to DATA-VECTOR-REF.
1114 (deftransform aref ((array index) (t t) * :node node)
1115 (let* ((type (lvar-type array))
1116 (element-ctype (array-type-upgraded-element-type type)))
1117 (cond
1118 ((and (array-type-p type)
1119 (null (array-type-complexp type))
1120 (not (eql element-ctype *wild-type*))
1121 (eql (length (array-type-dimensions type)) 1))
1122 (let* ((declared-element-ctype (array-type-declared-element-type type))
1123 (bare-form
1124 `(data-vector-ref array
1125 (%check-bound array (array-dimension array 0) index))))
1126 (if (type= declared-element-ctype element-ctype)
1127 bare-form
1128 `(the ,(type-specifier declared-element-ctype) ,bare-form))))
1129 ((policy node (zerop insert-array-bounds-checks))
1130 `(hairy-data-vector-ref array index))
1131 (t `(hairy-data-vector-ref/check-bounds array index)))))
1133 (deftransform %aset ((array index new-value) (t t t) * :node node)
1134 (if (policy node (zerop insert-array-bounds-checks))
1135 `(hairy-data-vector-set array index new-value)
1136 `(hairy-data-vector-set/check-bounds array index new-value)))
1138 ;;; But if we find out later that there's some useful type information
1139 ;;; available, switch back to the normal one to give other transforms
1140 ;;; a stab at it.
1141 (macrolet ((define (name transform-to extra extra-type)
1142 (declare (ignore extra-type))
1143 `(deftransform ,name ((array index ,@extra))
1144 (let* ((type (lvar-type array))
1145 (element-type (array-type-upgraded-element-type type))
1146 (declared-type (type-specifier
1147 (array-type-declared-element-type type))))
1148 ;; If an element type has been declared, we want to
1149 ;; use that information it for type checking (even
1150 ;; if the access can't be optimized due to the array
1151 ;; not being simple).
1152 (when (and (eql element-type *wild-type*)
1153 ;; This type logic corresponds to the special
1154 ;; case for strings in HAIRY-DATA-VECTOR-REF
1155 ;; (generic/vm-tran.lisp)
1156 (not (csubtypep type (specifier-type 'simple-string))))
1157 (when (or (not (array-type-p type))
1158 ;; If it's a simple array, we might be able
1159 ;; to inline the access completely.
1160 (not (null (array-type-complexp type))))
1161 (give-up-ir1-transform
1162 "Upgraded element type of array is not known at compile time.")))
1163 ,(if extra
1164 ``(truly-the ,declared-type
1165 (,',transform-to array
1166 (%check-bound array
1167 (array-dimension array 0)
1168 index)
1169 (the ,declared-type ,@',extra)))
1170 ``(the ,declared-type
1171 (,',transform-to array
1172 (%check-bound array
1173 (array-dimension array 0)
1174 index))))))))
1175 (define hairy-data-vector-ref/check-bounds
1176 hairy-data-vector-ref nil nil)
1177 (define hairy-data-vector-set/check-bounds
1178 hairy-data-vector-set (new-value) (*)))
1180 ;;; Just convert into a HAIRY-DATA-VECTOR-REF (or
1181 ;;; HAIRY-DATA-VECTOR-SET) after checking that the index is inside the
1182 ;;; array total size.
1183 (deftransform row-major-aref ((array index))
1184 `(hairy-data-vector-ref array
1185 (%check-bound array (array-total-size array) index)))
1186 (deftransform %set-row-major-aref ((array index new-value))
1187 `(hairy-data-vector-set array
1188 (%check-bound array (array-total-size array) index)
1189 new-value))
1191 ;;;; bit-vector array operation canonicalization
1192 ;;;;
1193 ;;;; We convert all bit-vector operations to have the result array
1194 ;;;; specified. This allows any result allocation to be open-coded,
1195 ;;;; and eliminates the need for any VM-dependent transforms to handle
1196 ;;;; these cases.
1198 (macrolet ((def (fun)
1199 `(progn
1200 (deftransform ,fun ((bit-array-1 bit-array-2
1201 &optional result-bit-array)
1202 (bit-vector bit-vector &optional null) *
1203 :policy (>= speed space))
1204 `(,',fun bit-array-1 bit-array-2
1205 (make-array (array-dimension bit-array-1 0) :element-type 'bit)))
1206 ;; If result is T, make it the first arg.
1207 (deftransform ,fun ((bit-array-1 bit-array-2 result-bit-array)
1208 (bit-vector bit-vector (eql t)) *)
1209 `(,',fun bit-array-1 bit-array-2 bit-array-1)))))
1210 (def bit-and)
1211 (def bit-ior)
1212 (def bit-xor)
1213 (def bit-eqv)
1214 (def bit-nand)
1215 (def bit-nor)
1216 (def bit-andc1)
1217 (def bit-andc2)
1218 (def bit-orc1)
1219 (def bit-orc2))
1221 ;;; Similar for BIT-NOT, but there is only one arg...
1222 (deftransform bit-not ((bit-array-1 &optional result-bit-array)
1223 (bit-vector &optional null) *
1224 :policy (>= speed space))
1225 '(bit-not bit-array-1
1226 (make-array (array-dimension bit-array-1 0) :element-type 'bit)))
1227 (deftransform bit-not ((bit-array-1 result-bit-array)
1228 (bit-vector (eql t)))
1229 '(bit-not bit-array-1 bit-array-1))
1231 ;;; Pick off some constant cases.
1232 (defoptimizer (array-header-p derive-type) ((array))
1233 (let ((type (lvar-type array)))
1234 (cond ((not (array-type-p type))
1235 ;; FIXME: use analogue of ARRAY-TYPE-DIMENSIONS-OR-GIVE-UP
1236 nil)
1238 (let ((dims (array-type-dimensions type)))
1239 (cond ((csubtypep type (specifier-type '(simple-array * (*))))
1240 ;; no array header
1241 (specifier-type 'null))
1242 ((and (listp dims) (/= (length dims) 1))
1243 ;; multi-dimensional array, will have a header
1244 (specifier-type '(eql t)))
1245 ((eql (array-type-complexp type) t)
1246 (specifier-type '(eql t)))
1248 nil)))))))