change-test-based-on-item: check for characters.
[sbcl.git] / src / compiler / seqtran.lisp
blobb9274ad1f51ba39885d551e1a8f13ac1cda8f161
1 ;;;; optimizers for list and sequence functions
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 ;;; Regarding several reader-conditionalized MUFFLE-CONDITION declarations
15 ;;; throughout this file, here's why: Transforms produce sexprs that as far
16 ;;; as the compiler is concerned could have been user-supplied.
17 ;;; In as much as the forms mention a type-name, that name had best be
18 ;;; recognized, or else it's a style-warning (or worse).
19 ;;; And in cross-compilation, COMPILER-NOTE isn't known early enough for
20 ;;; the transforms in this file to refer to a known type.
21 ;;; But mysteriously the xc would report a style-warning about COMPILER-NOTE
22 ;;; - or any descendant - being unknown, and then go on with life.
23 ;;; How was this possible? Well, it's only trying to _parse_ the type
24 ;;; on account of the declarations saying to muffle things of that type.
25 ;;; Indeed the declaration merits a warning.
26 ;;; But this is an extremely sad and confusing state of affairs,
27 ;;; because while we expect some CODE-DELETION-NOTEs, we don't expect to see
28 ;;; that CODE-DELETION-NOTE is an undefined type.
29 ;;; Alternatively, we could invent DEFINE!-CONDITION which would cause
30 ;;; the cross-compiler to be born knowing all the required types.
31 ;;; Moreover, it would be nice if some of the declarations were commented
32 ;;; with their reason for existence.
35 ;;;; mapping onto lists: the MAPFOO functions
37 ;; This expander allows a compiler-macro for FN to take effect by eliding
38 ;; a LET binding of it. Attempting to self-optimize like that isn't the usual
39 ;; SBCL way, however this is a countermeasure to an inhibition of a later
40 ;; optimization, and it is not an onerous change to the expander.
41 ;; We've gone to the trouble of inlining MAPfoo, but the inlined code
42 ;; prevented use of a compiler-macro because %FUNCALL (as opposed to FUNCALL)
43 ;; is not recognized. "Fixing" the compiler to understand %FUNCALL being
44 ;; the same isn't enough: the funarg must be a literal form because we can't
45 ;; know that a variable arg is a never-modified binding of 'F or #'F
46 ;; until IR1 has figured that out, at which point it is too late.
47 ;; [However, see lp# 632368 which asks for something like that.]
49 ;; Also, you might think there to be a subtle difference in behavior from
50 ;; delaying the reference to #'F versus referencing it once. But there is no
51 ;; difference - either way will use the #<fdefn> of F in the call.
52 ;; Of course, it would be ridiculously unportable to to rely on the
53 ;; fact that F can be changed (for its next call) while funcalling it.
55 (defun mapfoo-transform (fn arglists accumulate take-car)
56 (collect ((do-clauses)
57 (args-to-fn)
58 (tests))
59 (let ((n-first (gensym)))
60 (dolist (a (if accumulate
61 arglists
62 `(,n-first ,@(rest arglists))))
63 (let ((v (gensym)))
64 (do-clauses `(,v (the* (list :use-annotations t :source-form ,a) ,a)
65 (cdr ,v)))
66 (tests `(endp ,v))
67 (args-to-fn (if take-car `(car ,v) v))))
69 (binding* (((fn-binding call) (funarg-bind/call-forms fn (args-to-fn)))
70 (endtest `(or ,@(tests))))
71 `(let ,fn-binding
72 ,(ecase accumulate
73 (:nconc
74 (let ((last (gensym "LAST"))
75 (map-result (gensym)))
76 `(let ((,map-result
77 ;; MUFFLE- is not injected when cross-compiling.
78 ;; See top of file for explanation.
79 (locally
80 #-sb-xc-host
81 (declare (muffle-conditions compiler-note))
82 (list nil))))
83 (declare (dynamic-extent ,map-result))
84 (do-anonymous ((,last ,map-result) . ,(do-clauses))
85 (,endtest (cdr ,map-result))
86 (let ((result ,call))
87 (when result
88 (psetf ,last result
89 (cdr (last ,last)) result)))))))
90 (:list
91 (let ((temp (gensym))
92 (map-result (gensym)))
93 `(let ((,map-result
94 ;; MUFFLE- is not injected when cross-compiling.
95 ;; See top of file for explanation.
96 (locally
97 #-sb-xc-host
98 (declare (muffle-conditions compiler-note))
99 (unaligned-dx-cons nil))))
100 (declare (dynamic-extent ,map-result))
101 (do-anonymous ((,temp ,map-result) . ,(do-clauses))
102 (,endtest
103 (%rplacd ,temp nil) ;; replace the 0
104 (truly-the list (cdr ,map-result)))
105 ;; Accumulate using %RPLACD. RPLACD becomes (SETF CDR)
106 ;; which becomes %RPLACD but relies on "defsetfs".
107 ;; This is for effect, not value, so makes no difference.
108 (%rplacd ,temp (setq ,temp
109 ;; 0 is not written to the heap
110 (cons ,call 0)))))))
111 ((nil)
112 `(let ((,n-first ,(first arglists)))
113 (do-anonymous ,(do-clauses)
114 (,endtest (truly-the list ,n-first))
115 ,call)))))))))
117 (define-source-transform mapc (function list &rest more-lists)
118 (mapfoo-transform function (cons list more-lists) nil t))
120 (define-source-transform mapcar (function list &rest more-lists)
121 (mapfoo-transform function (cons list more-lists) :list t))
123 (define-source-transform mapcan (function list &rest more-lists)
124 (mapfoo-transform function (cons list more-lists) :nconc t))
126 (define-source-transform mapl (function list &rest more-lists)
127 (mapfoo-transform function (cons list more-lists) nil nil))
129 (define-source-transform maplist (function list &rest more-lists)
130 (mapfoo-transform function (cons list more-lists) :list nil))
132 (define-source-transform mapcon (function list &rest more-lists)
133 (mapfoo-transform function (cons list more-lists) :nconc nil))
135 ;;;; mapping onto sequences: the MAP function
137 ;;; MAP is %MAP plus a check to make sure that any length specified in
138 ;;; the result type matches the actual result. We also wrap it in a
139 ;;; TRULY-THE for the most specific type we can determine.
140 (deftransform map ((result-type-arg fun seq &rest seqs) * * :node node)
141 (let* ((seq-names (make-gensym-list (length seqs)))
142 (constant-result-type-arg-p (constant-lvar-p result-type-arg))
143 (nil-p)
144 ;; what we know about the type of the result. (Note that the
145 ;; "result type" argument is not necessarily the type of the
146 ;; result, since NIL means the result has NULL type.)
147 (result-type (if constant-result-type-arg-p
148 (let ((result-type-arg-value
149 (lvar-value result-type-arg)))
150 (cond (result-type-arg-value)
152 (setf nil-p t)
153 'null)))
154 'consed-sequence))
155 (result-ctype (ir1-transform-specifier-type result-type)))
156 `(lambda (result-type-arg fun seq ,@seq-names)
157 (the* (,result-type :context map)
158 (truly-the
159 ,(cond (nil-p
160 'null)
161 ((csubtypep result-ctype (specifier-type 'vector))
162 (strip-array-dimensions-and-complexity result-ctype t))
163 ((csubtypep result-ctype (specifier-type 'list))
164 'list)
167 (%map result-type-arg fun seq ,@seq-names))))))
169 ;;; Return a DO loop, mapping a function FUN to elements of
170 ;;; sequences. SEQS is a list of lvars, SEQ-NAMES - list of variables,
171 ;;; bound to sequences, INTO - a variable, which is used in
172 ;;; MAP-INTO. RESULT and BODY are forms, which can use variables
173 ;;; FUNCALL-RESULT, containing the result of application of FUN, and
174 ;;; INDEX, containing the current position in sequences.
175 (defun build-sequence-iterator (seqs seq-names &key result into body fast)
176 (declare (type list seqs seq-names)
177 (type symbol into))
178 (collect ((bindings)
179 (declarations)
180 (vector-lengths)
181 (tests)
182 (places)
183 (around))
184 (let ((found-vector-p nil))
185 (flet ((process-vector (length)
186 (unless found-vector-p
187 (setq found-vector-p t)
188 (bindings `(index 0 (1+ index)))
189 (declarations `(type index index)))
190 (vector-lengths length)))
191 (loop for seq of-type lvar in seqs
192 for seq-name in seq-names
193 for type = (lvar-type seq)
194 do (cond ((csubtypep type (specifier-type 'list))
195 (with-unique-names (index)
196 (bindings `(,index ,seq-name (cdr ,index)))
197 (declarations `(type list ,index))
198 (places `(car ,index))
199 (tests `(endp ,index))))
200 ((or (csubtypep type (specifier-type '(simple-array * 1)))
201 (and (not fast)
202 (csubtypep type (specifier-type 'vector))))
203 (process-vector `(length ,seq-name))
204 (places `(locally (declare (optimize (insert-array-bounds-checks 0)))
205 (aref ,seq-name index))))
206 ((csubtypep type (specifier-type 'vector))
207 (let ((data (gensym "DATA"))
208 (start (gensym "START"))
209 (end (gensym "END")))
210 (around `(with-array-data ((,data ,seq-name)
211 (,start)
212 (,end (length ,seq-name)))))
213 (process-vector `(- ,end ,start))
214 (places `(locally (declare (optimize (insert-array-bounds-checks 0)))
215 (aref ,data (truly-the index (+ index ,start)))))))
217 (give-up-ir1-transform
218 "can't determine sequence argument type"))))
219 (when into
220 (process-vector `(array-dimension ,into 0))))
221 (when found-vector-p
222 (bindings `(length (min ,@(vector-lengths))))
223 (tests `(>= index length)))
224 (let ((body `(do (,@(bindings))
225 ((or ,@(tests)) ,result)
226 (declare ,@(declarations))
227 (let ((funcall-result (funcall fun ,@(places))))
228 (declare (ignorable funcall-result))
229 ,body))))
230 (if (around)
231 (reduce (lambda (wrap body) (append wrap (list body)))
232 (around)
233 :from-end t
234 :initial-value body)
235 body)))))
237 ;;; Try to compile %MAP efficiently when we can determine sequence
238 ;;; argument types at compile time.
239 (deftransform %map ((result-type fun seq &rest seqs) * *
240 :node node :policy (>= speed space))
241 "open code"
242 (unless (constant-lvar-p result-type)
243 (give-up-ir1-transform "RESULT-TYPE argument not constant"))
244 (flet ( ;; 1-valued SUBTYPEP, fails unless second value of SUBTYPEP is true
245 (1subtypep (x y)
246 (multiple-value-bind (subtype-p valid-p)
247 (csubtypep x (specifier-type y))
248 (if valid-p
249 subtype-p
250 (give-up-ir1-transform
251 "can't analyze sequence type relationship")))))
252 (let* ((result-type-value (lvar-value result-type))
253 (result-type-ctype (ir1-transform-specifier-type result-type-value))
254 (result-supertype (cond ((null result-type-value) 'null)
255 ((1subtypep result-type-ctype 'vector)
256 'vector)
257 ((1subtypep result-type-ctype 'list)
258 'list)
260 (give-up-ir1-transform
261 "result type unsuitable")))))
262 (cond ((and (eq result-supertype 'list) (null seqs))
263 ;; The consing arity-1 cases can be implemented
264 ;; reasonably efficiently as function calls, and the cost
265 ;; of consing should be significantly larger than
266 ;; function call overhead, so we always compile these
267 ;; cases as full calls regardless of speed-versus-space
268 ;; optimization policy.
269 '(%map-to-list-arity-1 fun seq))
270 ;; (We use the same idiom, of returning a LAMBDA from
271 ;; DEFTRANSFORM, as is used in the DEFTRANSFORMs for
272 ;; FUNCALL and ALIEN-FUNCALL, and for the same
273 ;; reason: we need to get the runtime values of each
274 ;; of the &REST vars.)
275 ((eq result-supertype 'vector)
276 (let* ((all-seqs (cons seq seqs))
277 (seq-args (make-gensym-list (length all-seqs))))
278 `(lambda (result-type fun ,@seq-args)
279 (map-into (locally
280 #-sb-xc-host
281 (declare (muffle-conditions array-initial-element-mismatch))
282 (make-sequence result-type
283 ,(if (cdr seq-args)
284 `(min ,@(loop for arg in seq-args
285 collect `(length ,arg)))
286 `(length ,(car seq-args)))))
287 fun ,@seq-args))))
289 (let* ((all-seqs (cons seq seqs))
290 (seq-args (make-gensym-list (length all-seqs))))
291 (multiple-value-bind (push-dacc result)
292 (ecase result-supertype
293 (null (values nil nil))
294 (list (values `(push funcall-result acc)
295 `(nreverse acc))))
296 (catch-give-up-ir1-transform
297 (`(lambda (result-type fun ,@seq-args)
298 (declare (ignore result-type))
299 (let ((fun (%coerce-callable-to-fun fun))
300 (acc nil))
301 (declare (type list acc))
302 (declare (ignorable acc))
303 ,(build-sequence-iterator
304 all-seqs seq-args
305 :result result
306 :body push-dacc
307 :fast (policy node (> speed space))))))
308 (if (and (null result-type-value) (null seqs))
309 '(%map-for-effect-arity-1 fun seq)
310 (%give-up))))))))))
312 ;;; MAP-INTO
313 (defmacro mapper-from-typecode (typecode)
314 #+sb-xc-host
315 `(svref ,(let ((a (make-array 256)))
316 (dovector (info sb-vm:*specialized-array-element-type-properties* a)
317 (setf (aref a (sb-vm:saetp-typecode info))
318 (package-symbolicate "SB-IMPL" "VECTOR-MAP-INTO/"
319 (sb-vm:saetp-primitive-type-name info)))))
320 ,typecode)
321 #-sb-xc-host
322 `(%fun-name (svref sb-impl::%%vector-map-into-funs%% ,typecode)))
324 (deftransform map-into ((result fun &rest seqs)
325 (vector t &rest t)
326 * :node node)
327 "open code"
328 (let* ((seqs-names (make-gensym-list (length seqs)))
329 (result-type (lvar-type result))
330 (non-complex-vector-type-p (csubtypep result-type
331 (specifier-type '(simple-array * 1)))))
332 (catch-give-up-ir1-transform
333 (`(lambda (result fun ,@seqs-names)
334 ,(if (and (policy node (> speed space))
335 (not non-complex-vector-type-p))
336 (let ((data (gensym "DATA"))
337 (start (gensym "START"))
338 (end (gensym "END")))
339 `(with-array-data ((,data result)
340 (,start)
341 (,end))
342 (declare (ignore ,end))
343 ,(build-sequence-iterator
344 seqs seqs-names
345 :result '(when (array-has-fill-pointer-p result)
346 (setf (fill-pointer result) index))
347 :into 'result
348 :body `(locally (declare (optimize (insert-array-bounds-checks 0)))
349 (setf (aref ,data (truly-the index (+ index ,start)))
350 funcall-result))
351 :fast t)))
352 (build-sequence-iterator
353 seqs seqs-names
354 :result '(when (array-has-fill-pointer-p result)
355 (setf (fill-pointer result) index))
356 :into 'result
357 :body '(locally (declare (optimize (insert-array-bounds-checks 0)))
358 (setf (aref result index) funcall-result))))
359 result))
360 (cond ((and non-complex-vector-type-p
361 (array-type-p result-type)
362 (not (eq (array-type-specialized-element-type result-type)
363 *wild-type*)))
364 (let ((saetp (find-saetp-by-ctype (array-type-specialized-element-type result-type))))
365 (unless saetp
366 (give-up-ir1-transform "Uknown upgraded array element type of the result"))
367 `(lambda (result fun ,@seqs-names)
368 (,(mapper-from-typecode (sb-vm:saetp-typecode saetp))
369 result 0 (length result) (%coerce-callable-to-fun fun) ,@seqs-names)
370 result)))
372 (%give-up))))))
374 (deftransform map-into ((result fun &rest sequences)
375 (list &rest t)
376 * :policy (>= speed space))
377 (if sequences
378 (let ((seqs-names (make-gensym-list (length sequences))))
379 `(lambda (result fun ,@seqs-names)
380 (let ((node result))
381 (block nil
382 (%map nil (lambda (,@seqs-names)
383 (when (endp node)
384 (return))
385 (setf (car node) (funcall fun ,@seqs-names))
386 (setf node (cdr node)))
387 ,@seqs-names))
388 result)))
389 `(let ((node result))
390 (loop (when (endp node)
391 (return))
392 (setf (car node) (funcall fun))
393 (setf node (cdr node)))
394 result)))
397 ;;; FIXME: once the confusion over doing transforms with known-complex
398 ;;; arrays is over, we should also transform the calls to (AND (ARRAY
399 ;;; * (*)) (NOT (SIMPLE-ARRAY * (*)))) objects.
400 (deftransform elt ((s i) ((simple-array * (*)) t) *)
401 '(aref s i))
403 (deftransform elt ((s i) (list t) * :policy (< safety 3))
404 '(nth i s))
406 (deftransform %setelt ((s i v) ((simple-array * (*)) t t) *)
407 '(setf (aref s i) v))
409 (deftransform %setelt ((s i v) (list t t) * :policy (< safety 3))
410 '(setf (car (nthcdr i s)) v))
412 (deftransform %check-vector-sequence-bounds ((vector start end)
413 (vector t t) *
414 :node node)
415 (if (policy node (= 0 insert-array-bounds-checks))
416 '(or end (length vector))
417 '(let ((length (length vector)))
418 (if (<= 0 start (or end length) length)
419 (or end length)
420 (sequence-bounding-indices-bad-error vector start end)))))
422 (sb-xc:deftype eq-comparable-type ()
423 '(or fixnum #+64-bit single-float (not number)))
425 ;;; True if EQL comparisons involving type can be simplified to EQ.
426 (defun eq-comparable-type-p (type)
427 (csubtypep type (specifier-type 'eq-comparable-type)))
429 (defun specialized-list-seek-function-name (function-name key-functions &optional variant)
430 (or (find-symbol (%with-output-to-string (s)
431 ;; Write "%NAME-FUN1-FUN2-FUN3", etc. Not only is
432 ;; this ever so slightly faster then FORMAT, this
433 ;; way we are also proof against *PRINT-CASE*
434 ;; frobbing and such.
435 (write-char #\% s)
436 (write-string (symbol-name function-name) s)
437 (dolist (f key-functions)
438 (write-char #\- s)
439 (write-string (symbol-name f) s))
440 (when variant
441 (write-char #\- s)
442 (write-string (symbol-name variant) s)))
443 #.(find-package "SB-KERNEL"))
444 (bug "Unknown list item seek transform: name=~S, key-functions=~S variant=~S"
445 function-name key-functions variant)))
447 (defparameter *list-open-code-limit* 128)
449 (defun transform-list-item-seek (name item list key test test-not node)
450 (when (and test test-not)
451 (abort-ir1-transform "Both ~S and ~S supplied to ~S." :test :test-not name))
452 ;; If TEST is EQL, drop it.
453 (when (and test (lvar-fun-is test '(eql)))
454 (setf test nil))
455 ;; Ditto for KEY IDENTITY.
456 (when (and key (lvar-fun-is key '(identity)))
457 (setf key nil))
459 (when (and (member name '(member assoc rassoc))
460 ;; If the test was EQL, we've already changed it to NIL.
461 (or (not test) (lvar-fun-is test '(eq)))
462 (not test-not) ; keep it simple, no other keywords allowed
463 (not key)
464 (constant-lvar-p list))
465 (let ((items (lvar-value list)))
466 ;; spec says MEMBER "Should be prepared to signal an error of type type-error
467 ;; if list is not a proper list." This optimization can't do that.
468 ;; TRY-mumble will figure out based on what function it is trying to transform
469 ;; whether all keys are acceptable.
470 (when (proper-list-p items)
471 (let* ((conditional (if-p (node-dest node)))
472 (expr (try-perfect-find/position-map
473 name
474 (if conditional ''(t)) ; returned value if present in the mapping
475 (lvar-type item) items nil node)))
476 (when expr
477 ;; The value delivered to an IF node must be a list because MEMBER and MEMQ
478 ;; are declared in fndb to return a list. If it were just the symbol T,
479 ;; then type inference would get all whacky on you.
480 (when conditional
481 (derive-node-type node (specifier-type 'list) :from-scratch t)) ; erase any cons types
482 (return-from transform-list-item-seek expr))))))
484 ;; Key can legally be NIL, but if it's NIL for sure we pretend it's
485 ;; not there at all. If it might be NIL, make up a form to that
486 ;; ensures it is a function.
487 (multiple-value-bind (key key-form)
488 (when key
489 (let ((key-type (lvar-type key))
490 (null-type (specifier-type 'null)))
491 (cond ((csubtypep key-type null-type)
492 (values nil nil))
493 ((types-equal-or-intersect null-type key-type)
494 (values key '(if key
495 (%coerce-callable-to-fun key)
496 #'identity)))
498 (values key (ensure-lvar-fun-form key 'key))))))
499 (let* ((c-test (cond ((and test (lvar-fun-is test '(eq)))
500 (setf test nil)
501 'eq)
502 ((and (not test) (not test-not))
503 (when (cond ((or (neq name 'adjoin)
504 (not key))
505 (eq-comparable-type-p (lvar-type item)))
507 (let ((type (lvar-fun-type key t t)))
508 (when (fun-type-p type)
509 (eq-comparable-type-p
510 (single-value-type (fun-type-returns type)))))))
511 'eq))))
512 (funs (delete nil (list (when key (list key 'key))
513 (when test (list test 'test))
514 (when test-not (list test-not 'test-not)))))
515 (target-expr (if key '(%funcall key target) 'target))
516 (test-expr (cond (test `(%funcall test item ,target-expr))
517 (test-not `(not (%funcall test-not item ,target-expr)))
518 (c-test `(,c-test item ,target-expr))
519 (t `(eql item ,target-expr)))))
520 (labels ((open-code (tail)
521 (when tail
522 `(if (let ((this ',(car tail)))
523 ,(ecase name
524 ((assoc rassoc)
525 (let ((cxx (if (eq name 'assoc) 'car 'cdr)))
526 `(and this (let ((target (,cxx this)))
527 ,test-expr))))
528 (member
529 `(let ((target this))
530 ,test-expr))))
531 ',(ecase name
532 ((assoc rassoc) (car tail))
533 (member tail))
534 ,(open-code (cdr tail)))))
535 (ensure-fun (args)
536 (if (eq 'key (second args))
537 key-form
538 (apply #'ensure-lvar-fun-form args))))
539 (let* ((cp (constant-lvar-p list))
540 (c-list (when cp (lvar-value list))))
541 (cond ((not (proper-list-p c-list))
542 (abort-ir1-transform "Argument to ~a is not a proper list." name))
543 ((and cp c-list (member name '(assoc rassoc member))
544 (policy node (>= speed space))
545 (not (nthcdr *list-open-code-limit* c-list)))
546 `(let ,(mapcar (lambda (fun) `(,(second fun) ,(ensure-fun fun))) funs)
547 ,(open-code c-list)))
548 ((and cp (not c-list))
549 ;; constant nil list
550 (if (eq name 'adjoin)
551 '(list item)
552 nil))
554 ;; specialized out-of-line version
555 `(,(specialized-list-seek-function-name name (mapcar #'second funs) c-test)
556 item list ,@(mapcar #'ensure-fun funs)))))))))
558 (defun transform-list-pred-seek (name pred list key node)
559 ;; If KEY is IDENTITY, drop it.
560 (when (and key (lvar-fun-is key '(identity)))
561 (setf key nil))
562 ;; Key can legally be NIL, but if it's NIL for sure we pretend it's
563 ;; not there at all. If it might be NIL, make up a form to that
564 ;; ensures it is a function.
565 (multiple-value-bind (key key-form)
566 (when key
567 (let ((key-type (lvar-type key))
568 (null-type (specifier-type 'null)))
569 (cond ((csubtypep key-type null-type)
570 (values nil nil))
571 ((types-equal-or-intersect null-type key-type)
572 (values key '(if key
573 (%coerce-callable-to-fun key)
574 #'identity)))
576 (values key (ensure-lvar-fun-form key 'key))))))
577 (let ((test-expr `(%funcall pred ,(if key '(%funcall key target) 'target)))
578 (pred-expr (ensure-lvar-fun-form pred 'pred)))
579 (when (member name '(member-if-not assoc-if-not rassoc-if-not))
580 (setf test-expr `(not ,test-expr)))
581 (labels ((open-code (tail)
582 (when tail
583 `(if (let ((this ',(car tail)))
584 ,(ecase name
585 ((assoc-if assoc-if-not rassoc-if rassoc-if-not)
586 (let ((cxx (if (member name '(assoc-if assoc-if-not)) 'car 'cdr)))
587 `(and this (let ((target (,cxx this)))
588 ,test-expr))))
589 ((member-if member-if-not)
590 `(let ((target this))
591 ,test-expr))))
592 ',(ecase name
593 ((assoc-if assoc-if-not rassoc-if rassoc-if-not)
594 (car tail))
595 ((member-if member-if-not)
596 tail))
597 ,(open-code (cdr tail))))))
598 (let* ((cp (constant-lvar-p list))
599 (c-list (when cp (lvar-value list))))
600 (cond ((and cp c-list
601 (proper-list-p c-list)
602 (policy node (>= speed space))
603 (not (nthcdr *list-open-code-limit* c-list)))
604 `(let ((pred ,pred-expr)
605 ,@(when key `((key ,key-form))))
606 ,(open-code c-list)))
607 ((and cp (not c-list))
608 ;; constant nil list -- nothing to find!
609 nil)
611 ;; specialized out-of-line version
612 `(,(specialized-list-seek-function-name name (when key '(key)))
613 ,pred-expr list ,@(when key (list key-form))))))))))
615 (defun change-test-based-on-item (test item)
617 (and (neq item *universal-type*)
618 (neq item *wild-type*)
619 (case test
620 (eql
621 (when (csubtypep item (specifier-type 'eq-comparable-type))
622 'eq))
623 (equal
624 (when (csubtypep item (specifier-type '(not (or
625 cons
626 bit-vector
627 string
628 pathname))))
629 (change-test-based-on-item 'eql item)))
630 (equalp
631 (cond ((csubtypep item (specifier-type '(not (or number
632 character
633 cons
634 array
635 pathname
636 instance
637 hash-table))))
638 (change-test-based-on-item 'eql item))
639 ((multiple-value-bind (p value) (type-singleton-p item)
640 (when (and p
641 (characterp value)
642 (not (both-case-p value)))
643 (change-test-based-on-item 'eq item))))))
644 (char-equal
645 (multiple-value-bind (p value) (type-singleton-p item)
646 (when (and p
647 (characterp value)
648 (not (both-case-p value)))
649 'char=)))))
650 test))
652 (defun change-test-lvar-based-on-item (test item)
653 (let ((test (if test
654 (lvar-fun-is test '(eql equal equalp char-equal))
655 'eql)))
656 (when test
657 (unless (eq (shiftf test (change-test-based-on-item test (lvar-type item)))
658 test)
659 test))))
661 (macrolet ((def (name &optional if/if-not)
662 (let ((basic (symbolicate "%" name))
663 (basic-eq (symbolicate "%" name "-EQ"))
664 (basic-key (symbolicate "%" name "-KEY"))
665 (basic-key-eq (symbolicate "%" name "-KEY-EQ"))
666 (test (symbolicate "%" name "-TEST"))
667 (key-test (symbolicate "%" name "-KEY-TEST")))
668 `(progn
669 (deftransform ,name ((item list &key key test test-not) * * :node node)
670 (transform-list-item-seek ',name item list key test test-not node))
671 (deftransform ,basic ((item list) (eq-comparable-type t) * :important nil)
672 `(,',basic-eq item list))
673 ,(unless (eq name 'adjoin) ;; applies KEY to ITEM.
674 `(deftransform ,basic-key ((item list key) (eq-comparable-type t t) * :important nil)
675 `(,',basic-key-eq item list key)))
676 (deftransform ,test ((item list test) (t t t) * :node node)
677 (let ((test (lvar-fun-is test '(eq eql equal equalp char-equal))))
678 (case (change-test-based-on-item test (lvar-type item))
680 `(,',basic-eq item list))
681 (eql
682 `(,',basic item list))
684 (give-up-ir1-transform)))))
685 (deftransform ,key-test ((item list key test) (t t t t) * :important nil)
686 (let ((test (lvar-fun-is test '(eq eql
687 ,@(unless (eq name 'adjoin)
688 '(equal equalp char-equal))))))
689 (case ,(if (eq name 'adjoin)
690 'test
691 '(change-test-based-on-item test (lvar-type item)))
693 `(,',basic-key-eq item list key))
694 (eql
695 `(,',basic-key item list key))
697 (give-up-ir1-transform)))))
698 ,@(when if/if-not
699 (let ((if-name (symbolicate name "-IF"))
700 (if-not-name (symbolicate name "-IF-NOT")))
701 `((deftransform ,if-name ((pred list &key key) * * :node node)
702 (transform-list-pred-seek ',if-name pred list key node))
703 (deftransform ,if-not-name ((pred list &key key) * * :node node)
704 (transform-list-pred-seek ',if-not-name pred list key node)))))))))
705 (def adjoin)
706 (def assoc t)
707 (def member t)
708 (def rassoc t))
710 ;;; A similar transform used to apply to MEMBER and ASSOC, but since
711 ;;; TRANSFORM-LIST-ITEM-SEEK now takes care of them those transform
712 ;;; would never fire, and (%MEMBER-TEST ITEM LIST #'EQ) should be
713 ;;; almost as fast as MEMQ.
714 (deftransform delete ((item list &key test) (t list &rest t) *)
715 "convert to EQ test"
716 (let ((type (lvar-type item)))
717 (unless (or (and test (lvar-fun-is test '(eq)))
718 (and (eq-comparable-type-p type)
719 (or (not test) (lvar-fun-is test '(eql)))))
720 (give-up-ir1-transform)))
721 `(delq item list))
723 (deftransform delete-if ((pred list) (t list))
724 "open code"
725 '(do ((x list (cdr x))
726 (splice '()))
727 ((endp x) list)
728 (cond ((funcall pred (car x))
729 (if (null splice)
730 (setq list (cdr x))
731 (rplacd splice (cdr x))))
732 (t (setq splice x)))))
734 (deftransform fill ((seq item &key (start 0) (end nil))
735 (list t &key (:start t) (:end t)))
736 '(list-fill* seq item start end))
738 (defun find-basher (saetp &optional item node)
739 (let* ((element-type (sb-vm:saetp-specifier saetp))
740 (element-ctype (sb-vm:saetp-ctype saetp))
741 (n-bits (sb-vm:saetp-n-bits saetp))
742 (kind (cond ((sb-vm:saetp-fixnum-p saetp) :tagged)
743 ((member element-type '(character base-char)) :char)
744 ((eq element-type 'single-float) :single-float)
745 #+64-bit
746 ((eq element-type 'double-float) :double-float)
747 #+64-bit
748 ((equal element-type '(complex single-float))
749 :complex-single-float)
751 (aver (integer-type-p element-ctype))
752 :bits))))
753 (if (and item (constant-lvar-p item))
754 (let* ((basher-name (format nil "UB~D-BASH-FILL" n-bits))
755 (basher (or (find-symbol basher-name #.(find-package "SB-KERNEL"))
756 (abort-ir1-transform
757 "Unknown fill basher, please report to sbcl-devel: ~A"
758 basher-name)))
759 (tmp (lvar-value item)))
760 (unless (ctypep tmp element-ctype)
761 (abort-ir1-transform "~S is not ~S" tmp element-type))
762 (values
763 basher
764 ;; Construct a word that we can repeatedly smash
765 ;; on the array: for less-than-word sized elements it
766 ;; contains multiple copies of the fill item.
767 (let* ((bits
768 (ldb (byte n-bits 0)
769 (ecase kind
770 (:tagged
771 (ash tmp sb-vm:n-fixnum-tag-bits))
772 (:char
773 (char-code tmp))
774 (:bits
775 tmp)
776 (:single-float
777 (single-float-bits tmp))
778 #+64-bit
779 (:double-float
780 (double-float-bits tmp))
781 #+64-bit
782 (:complex-single-float
783 #+big-endian
784 (logior (ash (single-float-bits (realpart tmp)) 32)
785 (ldb (byte 32 0)
786 (single-float-bits (imagpart tmp))))
787 #+little-endian
788 (logior (ash (single-float-bits (imagpart tmp)) 32)
789 (ldb (byte 32 0)
790 (single-float-bits (realpart tmp))))))))
791 (res bits))
792 (loop for i of-type sb-vm:word from n-bits by n-bits
793 until (= i sb-vm:n-word-bits)
794 do (setf res (ldb (byte sb-vm:n-word-bits 0)
795 (logior res (ash bits i)))))
796 res)))
797 (progn
798 (when node
799 (delay-ir1-transform node :constraint))
800 (let* ((with
801 (ecase kind
802 (:tagged
803 'fixnum)
804 (:char
805 (if (= n-bits sb-vm:n-word-bits)
806 'word
807 (format nil "UB~A" n-bits)))
808 (:bits
809 (cond ((not (csubtypep element-ctype (specifier-type 'unsigned-byte)))
810 (format nil "SB~A" n-bits))
811 ((= n-bits sb-vm:n-word-bits)
812 'word)
814 (format nil "UB~A" n-bits))))
815 (:single-float
816 'single-float)
817 #+64-bit
818 (:double-float
819 'double-float)
820 #+64-bit
821 (:complex-single-float
822 'complex-single-float)))
823 (basher-name (if (eq with 'word)
824 (format nil "UB~D-BASH-FILL" n-bits)
825 (format nil "UB~D-BASH-FILL-WITH-~A"
826 n-bits (string with)))))
827 (values
828 (or (find-symbol basher-name #.(find-package "SB-KERNEL"))
829 (abort-ir1-transform
830 "Unknown fill basher, please report to sbcl-devel: ~A"
831 basher-name))
832 (if (eq kind :char)
833 '(char-code item)
834 'item)))))))
836 (deftransform quickfill ((seq item) (vector t) * :node node)
837 ;; The QUICKFILL function has no START,END lexical vars, but if
838 ;; the transform hits the bashable non-simple or non-bashable case,
839 ;; it will invoke WITH-ARRAY-DATA using these variables.
840 `(let ((start 0) (end nil))
841 (declare (ignorable start end))
842 ,(fill-transform 'quickfill node seq item nil nil)))
843 (deftransform fill ((seq item &key (start 0) (end nil))
844 (vector t &key (:start t) (:end t))
846 :node node)
847 (fill-transform 'fill node seq item start end))
848 (defun fill-transform (fun-name node seq item start end)
849 (add-annotation seq
850 (make-lvar-sequence-bounds-annotation :deps (list start end)
851 :source-path (node-source-path node)))
852 (let* ((type (lvar-type seq))
853 (element-ctype (array-type-upgraded-element-type type))
854 (element-type (type-specifier element-ctype))
855 (saetp (unless (eq *wild-type* element-ctype)
856 (find-saetp-by-ctype element-ctype))))
857 (cond ((eq *wild-type* element-ctype)
858 (delay-ir1-transform node :constraint)
859 `(vector-fill* seq item start end))
860 ((and (csubtypep type (specifier-type 'simple-base-string))
861 (not start)
862 (not end)
863 (policy node (>= speed space)))
864 (let ((multiplier (logand #x0101010101010101 most-positive-word)))
865 `(let* ((value ,(if (and (constant-lvar-p item)
866 (typep (lvar-value item) 'base-char))
867 (* multiplier (char-code (lvar-value item)))
868 ;; Use multiplication if it's known to be cheap
869 #+(or x86 x86-64)
870 `(* ,multiplier (char-code (the base-char item)))
871 #-(or x86 x86-64)
872 '(let ((code (char-code (the base-char item))))
873 (setf code (dpb code (byte 8 8) code))
874 (setf code (dpb code (byte 16 16) code))
875 #+64-bit (dpb code (byte 32 32) code))))
876 (len (vector-length seq))
877 (words (truncate len sb-vm:n-word-bytes)))
878 (dotimes (index words)
879 (declare (optimize (speed 3) (safety 0))
880 (type index index))
881 (setf (%vector-raw-bits seq index) value))
882 ;; For 64-bit:
883 ;; if 1 more byte should be written, then shift-towards-start 56
884 ;; if 2 more bytes ... then shift-towards-start 48
885 ;; etc
886 ;; This correctly rewrites the trailing null in its proper place.
887 (let ((bits (ash (mod len sb-vm:n-word-bytes) 3)))
888 (when (plusp bits)
889 (setf (%vector-raw-bits seq words)
890 (shift-towards-start value (- bits)))))
891 seq)))
892 ((and (csubtypep type (specifier-type 'simple-bit-vector))
893 (not start)
894 (not end)
895 (policy node (>= speed space)))
896 `(let ((value (logand (- (the bit item)) most-positive-word)))
897 ;; Unlike for the SIMPLE-BASE-STRING case, we are allowed to touch
898 ;; bits beyond LENGTH with impunity.
899 (dotimes (index (ceiling (vector-length seq) sb-vm:n-word-bits))
900 (declare (optimize (speed 3) (safety 0))
901 (type index index))
902 (setf (%vector-raw-bits seq index) value))
903 seq))
904 ;; FIXME: this case takes over before we get a chance to select
905 ;; a variant of the SPLAT vop that can use XMM registers.
906 ;; Should this be #-x86-64 then?
907 ((and (array-type-p type)
908 (not (array-type-complexp type))
909 (or (not start)
910 (and (constant-lvar-p start)
911 (eql (lvar-value start) 0)))
912 (not end)
913 (typep (array-type-dimensions type) '(cons number null))
914 (<= (car (array-type-dimensions type))
915 (cond #+soft-card-marks
916 ((eq element-ctype *universal-type*)
917 ;; Each write will have a store barrier,
918 ;; marking it pretty large.
921 10))))
922 `(progn
923 ,@(loop for i below (car (array-type-dimensions type))
924 collect `(setf (aref seq ,i) item))
925 seq))
926 #+x86-64
927 ((and (type= element-ctype *universal-type*)
928 (csubtypep (lvar-type seq) (specifier-type '(simple-array * (*))))
929 ;; FIXME: why can't this work with arbitrary START and END?
930 ;; VECTOR-FILL/T certainly seems to take them.
931 (or (not start)
932 (and (constant-lvar-p start)
933 (eql (lvar-value start) 0)))
934 (or (not end)
935 ;; QUICKFILL always fills the whole vector, but I anticipate
936 ;; supplying END to avoid a call to VECTOR-LENGTH
937 (eq fun-name 'quickfill)))
938 ;; VECTOR-LENGTH entails one fewer transform than LENGTH
939 ;; and it too can derive a constant length if known.
940 '(vector-fill/t seq item 0 (vector-length seq)))
941 ((and saetp (sb-vm:valid-bit-bash-saetp-p saetp))
942 (multiple-value-bind (basher bash-value) (find-basher saetp item node)
943 (values
944 ;; KLUDGE: WITH-ARRAY data in its full glory is going to mess up
945 ;; dynamic-extent for MAKE-ARRAY :INITIAL-ELEMENT initialization.
946 (cond
947 ((eq fun-name 'quickfill)
948 ;; array is simple, and out-of-bounds can't happen
949 `(,basher ,bash-value seq 0 (vector-length seq)))
950 ;; FIXME: isn't this (NOT (CONSERVATIVE-ARRAY-TYPE-COMPLEXP (lvar-type seq))) ?
951 ((csubtypep (lvar-type seq) (specifier-type '(simple-array * (*))))
952 `(block nil
953 (tagbody
954 (let* ((len (vector-length seq))
955 (end (cond (end
956 (when (> end len)
957 (go bad-index))
958 end)
959 (len))))
960 (return (,basher ,bash-value seq
961 ,(if (or (not start)
962 (and (constant-lvar-p start)
963 (eql (lvar-value start) 0)))
965 `(if (> start end)
966 (go bad-index)
967 start))
968 (- end start))))
969 bad-index
970 (sequence-bounding-indices-bad-error seq start end))))
972 `(with-array-data ((data seq)
973 (start start)
974 (end end)
975 :check-fill-pointer t)
976 (declare (type (simple-array ,element-type 1) data))
977 (declare (type index start end))
978 (declare (optimize (safety 0) (speed 3)))
979 (,basher ,bash-value data start (- end start))
980 seq)))
981 `((declare (type ,element-type item))))))
982 ;; OK, it's not a "bashable" array type.
983 ((policy node (> speed space))
984 (values
985 `(with-array-data ((data seq)
986 (start start)
987 (end end)
988 :check-fill-pointer t)
989 (declare (type (simple-array ,element-type 1) data))
990 (declare (type index start end))
991 ;; WITH-ARRAY-DATA did our range checks once and for all, so
992 ;; it'd be wasteful to check again on every AREF...
993 ;; Force bounds-checks to 0 even if local policy had it >0.
994 (declare (optimize (safety 0) (speed 3)
995 (insert-array-bounds-checks 0)))
996 ,(cond #+x86-64
997 ((type= element-ctype *universal-type*)
998 '(vector-fill/t data item start end))
1000 `(do ((i start (1+ i)))
1001 ((= i end))
1002 (declare (type index i))
1003 (setf (aref data i) item))))
1004 seq)
1005 ;; ... though we still need to check that the new element can fit
1006 ;; into the vector in safe code. -- CSR, 2002-07-05
1007 `((declare (type ,element-type item)))))
1008 ((csubtypep type (specifier-type 'string))
1009 '(string-fill* seq item start end))
1011 '(vector-fill* seq item start end)))))
1013 (deftransform fill ((seq item &key (start 0) (end nil))
1014 ((and sequence (not vector) (not list)) t &key (:start t) (:end t)))
1015 `(sb-sequence:fill seq item
1016 :start start
1017 :end (%check-generic-sequence-bounds seq start end)))
1019 ;;;; hairy sequence transforms
1021 ;;; FIXME: no hairy sequence transforms in SBCL?
1023 ;;; There used to be a bunch of commented out code about here,
1024 ;;; containing the (apparent) beginning of hairy sequence transform
1025 ;;; infrastructure. People interested in implementing better sequence
1026 ;;; transforms might want to look at it for inspiration, even though
1027 ;;; the actual code is ancient CMUCL -- and hence bitrotted. The code
1028 ;;; was deleted in 1.0.7.23.
1030 ;;;; string operations
1032 ;;; We transform the case-sensitive string predicates into a non-keyword
1033 ;;; version. This is an IR1 transform so that we don't have to worry about
1034 ;;; changing the order of evaluation.
1035 (macrolet ((def (fun pred*)
1036 `(deftransform ,fun ((string1 string2 &key (start1 0) end1
1037 (start2 0) end2)
1038 * *)
1039 `(,',pred* string1 string2 start1 end1 start2 end2))))
1040 (def string< string<*)
1041 (def string> string>*)
1042 (def string<= string<=*)
1043 (def string>= string>=*)
1044 (def string= string=*)
1045 (def string/= string/=*))
1047 ;;; Return a form that tests the free variables STRING1 and STRING2
1048 ;;; for the ordering relationship specified by LESSP and EQUALP. The
1049 ;;; start and end are also gotten from the environment. Both strings
1050 ;;; must be simple.
1051 (macrolet ((def (name test index)
1052 `(deftransform ,name ((string1 string2 start1 end1 start2 end2)
1053 (simple-string simple-string t t t t) *)
1054 `(multiple-value-bind (index diff)
1055 (%sp-string-compare string1 string2 start1 end1 start2 end2)
1056 (if ,',test
1057 ,,(if index ''index 'nil)
1058 ,,(if index 'nil ''index))))))
1059 (def string<* (< diff 0) t)
1060 (def string<=* (> diff 0) nil)
1061 (def string>* (> diff 0) t)
1062 (def string>=* (< diff 0) nil))
1064 (deftransform string=* ((string1 string2 start1 end1 start2 end2)
1065 (string string
1066 (constant-arg (eql 0))
1067 (constant-arg null)
1068 (constant-arg (eql 0))
1069 (constant-arg null)))
1070 (cond ((and (constant-lvar-p string1)
1071 (equal (lvar-value string1) ""))
1072 `(zerop (length string2)))
1073 ((and (constant-lvar-p string2)
1074 (equal (lvar-value string2) ""))
1075 `(zerop (length string1)))
1077 (give-up-ir1-transform))))
1079 (deftransform string/=* ((string1 string2 start1 end1 start2 end2)
1080 (string string
1081 (constant-arg (eql 0))
1082 (constant-arg null)
1083 (constant-arg (eql 0))
1084 (constant-arg null)))
1085 (cond ((and (constant-lvar-p string1)
1086 (equal (lvar-value string1) ""))
1087 `(and (plusp (length string2))
1089 ((and (constant-lvar-p string2)
1090 (equal (lvar-value string2) ""))
1091 `(and (plusp (length string1))
1094 (give-up-ir1-transform))))
1096 (deftransform string=*
1097 ((string1 string2 start1 end1 start2 end2) (simple-base-string simple-base-string t t t t) *)
1098 `(simple-base-string= string1 string2 start1 end1 start2 end2))
1100 #+sb-unicode
1101 (deftransform string=*
1102 ((string1 string2 start1 end1 start2 end2) (simple-character-string simple-character-string t t t t) *)
1103 `(simple-character-string= string1 string2 start1 end1 start2 end2))
1105 (deftransform string/=*
1106 ((string1 string2 start1 end1 start2 end2) (simple-string simple-string t t t t) *)
1107 `(multiple-value-bind (index diff)
1108 (%sp-string-compare string1 string2 start1 end1 start2 end2)
1109 (declare (ignorable index))
1110 (if (,'/= diff 0)
1111 ,'index
1112 nil)))
1114 (defun string-compare-transform (string1 string2 start1 end1 start2 end2)
1115 (let* ((start1 (if start1
1116 (lvar-value start1)
1118 (start2 (if start2
1119 (lvar-value start2)
1121 (lengths1 (vector-type-lengths (lvar-type string1)))
1122 (lengths2 (vector-type-lengths (lvar-type string2)))
1123 (end1 (and end1 (lvar-value end1)))
1124 (end2 (and end2 (lvar-value end2))))
1125 (if (and lengths1
1126 lengths2
1127 (loop for length1 in lengths1
1128 never
1129 (loop for length2 in lengths2
1130 thereis
1131 (let ((end1 (or end1 length1))
1132 (end2 (or end2 length2)))
1133 (or (not (and (<= start1 end1 length1)
1134 (<= start2 end2 length2)))
1135 (= (- end1 start1)
1136 (- end2 start2)))))))
1138 (give-up-ir1-transform))))
1140 (deftransforms (string=* simple-base-string=
1141 simple-character-string=)
1142 ((string1 string2 start1 end1 start2 end2)
1143 (t t (constant-arg t) (constant-arg t) (constant-arg t) (constant-arg t)))
1144 (string-compare-transform string1 string2 start1 end1 start2 end2))
1146 (deftransform string-equal ((string1 string2 &key start1 end1 start2 end2)
1147 (t t &key (:start1 (constant-arg t))
1148 (:start2 (constant-arg t))
1149 (:end1 (constant-arg t))
1150 (:end2 (constant-arg t))))
1151 (string-compare-transform string1 string2 start1 end1 start2 end2))
1153 (deftransform string/=* ((str1 str2 start1 end1 start2 end2) * * :node node
1154 :important nil)
1155 ;; An IF node doesn't care about the mismatch index.
1156 ;; Transforming to (not (string= ..)) would lead to internal confusion
1157 ;; due to incorrect typing: STRING/= can't return T, so return 0 for true.
1158 (if (if-p (node-dest node))
1159 `(if (string=* str1 str2 start1 end1 start2 end2) nil 0)
1160 (give-up-ir1-transform)))
1162 (defun check-sequence-test (item sequence test key node)
1163 (let ((item (lvar-type item)))
1164 (when (or (not test)
1165 (lvar-fun-is test '(eq eql equal equalp two-arg-=)))
1166 (labels ((sequence-element-type (type)
1167 (cond ((array-type-p type)
1168 (let ((elt-type (array-type-element-type type)))
1169 (if (eq elt-type *wild-type*)
1170 *universal-type*
1171 elt-type)))
1172 ((csubtypep type (specifier-type 'string))
1173 (specifier-type 'character))
1175 *universal-type*))))
1176 (multiple-value-bind (key-type key) (and key
1177 (lvar-fun-type key))
1178 (let ((*compiler-error-context* node))
1179 (when (and (or (not key)
1180 (eq key 'identity))
1181 (not (types-equal-or-intersect item (sequence-element-type (lvar-type sequence)))))
1182 (compiler-style-warn "Item of type ~s can't be found in a sequence of type ~s."
1183 (type-specifier item)
1184 (type-specifier (lvar-type sequence))))
1185 (when (fun-type-p key-type)
1186 (let ((returns (single-value-type (fun-type-returns key-type))))
1187 (unless (types-equal-or-intersect item returns)
1188 (compiler-style-warn "Item of type ~s can't be found using :key ~s which returns ~s."
1189 (type-specifier item)
1191 (type-specifier returns)))))))))))
1193 (defun check-sequence-ranges (string start end node &optional (suffix "") sequence-name)
1194 (let* ((type (lvar-type string))
1195 (lengths (vector-type-lengths type))
1196 (annotation (find-if #'lvar-sequence-bounds-annotation-p (lvar-annotations string))))
1197 (when annotation
1198 (when (shiftf (lvar-annotation-fired annotation) t)
1199 (return-from check-sequence-ranges)))
1200 (flet ((arg-type (x)
1201 (typecase x
1202 (constant (ctype-of (constant-value x)))
1203 (lvar (lvar-type x))
1204 (t (leaf-type x)))))
1205 (flet ((check (index name length-type)
1206 (when index
1207 (let ((index-type (arg-type index)))
1208 (unless (types-equal-or-intersect index-type
1209 (specifier-type length-type))
1210 (let ((*compiler-error-context* node))
1211 (compiler-warn "Bad :~a~a ~a for~a ~a"
1212 name suffix
1213 (type-specifier index-type)
1214 (if sequence-name
1215 (format nil " for ~a of type" sequence-name)
1216 suffix)
1217 (type-specifier type))
1218 t))))))
1219 (loop for length in lengths
1220 thereis
1221 (check start "start" `(integer 0 ,length)))
1222 (loop for length in lengths
1223 thereis
1224 (check end "end" `(or null (integer 0 ,length)))))
1225 (when (and start end)
1226 (let* ((start-type (arg-type start))
1227 (start-interval (type-approximate-interval start-type))
1228 (end-type (arg-type end))
1229 (end-interval (type-approximate-interval end-type)))
1230 (when (and (interval-p start-interval)
1231 (interval-p end-interval)
1232 (interval-< end-interval start-interval))
1233 (let ((*compiler-error-context* node))
1234 (compiler-warn ":start~a ~a is greater than :end~a ~a"
1235 suffix
1236 (type-specifier start-type)
1237 suffix
1238 (type-specifier end-type)))))))))
1239 (defoptimizers ir2-hook
1240 (string=* string<* string>* string<=* string>=*
1241 %sp-string-compare simple-base-string=
1242 #+sb-unicode simple-character-string=)
1243 ((string1 string2 start1 end1 start2 end2) node)
1244 (check-sequence-ranges string1 start1 end1 node 1 'string1)
1245 (check-sequence-ranges string2 start2 end2 node 2 'string2))
1247 (defoptimizers ir2-hook
1248 (string-equal string-not-equal string-greaterp string-lessp)
1249 ((string1 string2 &key start1 end1 start2 end2) node)
1250 (check-sequence-ranges string1 start1 end1 node 1 'string1)
1251 (check-sequence-ranges string2 start2 end2 node 2 'string2))
1253 (defoptimizers ir2-hook
1254 (string-downcase string-upcase
1255 nstring-downcase nstring-upcase
1256 string-capitalize nstring-capitalize)
1257 ((string &key start end) node)
1258 (check-sequence-ranges string start end node))
1260 (defoptimizers ir2-hook
1261 (find-if find-if-not position-if position-if-not
1262 remove-if remove-if-not delete-if delete-if-not
1263 count-if count-if-not
1264 reduce remove-duplicates delete-duplicates)
1265 ((x sequence &key start end &allow-other-keys) node)
1266 (check-sequence-ranges sequence start end node))
1268 (defoptimizers ir2-hook
1269 (find position
1270 remove delete
1271 count)
1272 ((item sequence &key key test start end &allow-other-keys) node)
1273 (check-sequence-ranges sequence start end node)
1274 (check-sequence-test item sequence test key node))
1276 (defoptimizers ir2-hook
1277 (remove-duplicates delete-duplicates)
1278 ((sequence &key start end &allow-other-keys) node)
1279 (check-sequence-ranges sequence start end node))
1281 (defoptimizer (%find-position ir2-hook) ((item sequence from-end start end key test) node)
1282 (check-sequence-ranges sequence start end node)
1283 (check-sequence-test item sequence test key node))
1285 (defoptimizers ir2-hook
1286 (%find-position-if %find-position-if-not)
1287 ((predicate sequence from-end start end key) node)
1288 (check-sequence-ranges sequence start end node))
1290 (defoptimizer (fill ir2-hook) ((sequence item &key start end) node)
1291 (check-sequence-ranges sequence start end node))
1293 (defoptimizer (search ir2-hook) ((sub-sequence1 main-sequence2 &key start1 end1 start2 end2 &allow-other-keys) node)
1294 (check-sequence-ranges sub-sequence1 start1 end1 node 1 'sub-sequence1)
1295 (check-sequence-ranges main-sequence2 start2 end2 node 2 'main-sequence2))
1297 (defoptimizer (mismatch ir2-hook) ((sequence1 sequence2 &key start1 end1 start2 end2 &allow-other-keys) node)
1298 (check-sequence-ranges sequence1 start1 end1 node 1 'sequence1)
1299 (check-sequence-ranges sequence2 start2 end2 node 2 'sequence2))
1301 (defoptimizer (vector-subseq* ir2-hook) ((vector start end) node)
1302 (check-sequence-ranges vector start end node))
1304 (defun string-cmp-deriver (string1 string2 start1 end1 start2 end2 &optional equality)
1305 (flet ((dims (string start end)
1306 (let* ((type (lvar-type string))
1307 (length (vector-type-length type))
1308 (start (cond ((not start)
1310 ((constant-lvar-p start)
1311 (lvar-value start))))
1312 (end (cond ((not end)
1313 length)
1314 ((constant-lvar-p end)
1315 (or (lvar-value end)
1316 length)))))
1317 (values
1318 start
1320 (and start end
1321 (- end start))))))
1322 (multiple-value-bind (start1 end1 length1)
1323 (dims string1 start1 end1)
1324 (let (low
1325 high
1326 (length2 (nth-value 2 (dims string2 start2 end2))))
1327 (when start1
1328 (setf low start1))
1329 (when end1
1330 (setf high end1))
1331 (when (and length2 start1)
1332 (let ((high2 (+ start1 length2)))
1333 (when (or (not high)
1334 (> high high2))
1335 (setf high high2))))
1336 (when (or low high)
1337 (let ((type (make-numeric-type :class 'integer :high high :low low)))
1338 (if (and equality length1 length2
1339 (/= length1 length2))
1340 (if (eq equality '%sp-string-compare)
1341 (make-values-type (list type
1342 (specifier-type '(and integer (not (eql 0))))))
1343 type)
1344 (type-union type
1345 (specifier-type 'null)))))))))
1347 (macrolet ((def (name &optional equality)
1348 `(defoptimizer (,name derive-type) ((string1 string2 start1 end1 start2 end2))
1349 (string-cmp-deriver string1 string2 start1 end1 start2 end2 ,equality))))
1350 (def string<*)
1351 (def string>*)
1352 (def string<=*)
1353 (def string>=*)
1354 (def string/=* t)
1355 (def %sp-string-compare '%sp-string-compare))
1357 (macrolet ((def (name &optional equality)
1358 `(defoptimizer (,name derive-type) ((string1 string2 &key start1 end1 start2 end2))
1359 (string-cmp-deriver string1 string2 start1 end1 start2 end2 ,equality))))
1360 (def string-greaterp)
1361 (def string-lessp)
1362 (def string-not-equal t))
1364 (deftransform string ((x) (symbol)) '(symbol-name x))
1365 (deftransform string ((x) (string)) '(progn x))
1367 ;;;; transforms for sequence functions
1369 ;;; FIXME: In the copy loops below, we code the loops in a strange
1370 ;;; fashion:
1372 ;;; (do ((i (+ src-offset length) (1- i)))
1373 ;;; ((<= i 0) ...)
1374 ;;; (... (aref foo (1- i)) ...))
1376 ;;; rather than the more natural (and seemingly more efficient):
1378 ;;; (do ((i (1- (+ src-offset length)) (1- i)))
1379 ;;; ((< i 0) ...)
1380 ;;; (... (aref foo i) ...))
1382 ;;; (more efficient because we don't have to do the index adjusting on
1383 ;;; every iteration of the loop)
1385 ;;; We do this to avoid a suboptimality in SBCL's backend. In the
1386 ;;; latter case, the backend thinks I is a FIXNUM (which it is), but
1387 ;;; when used as an array index, the backend thinks I is a
1388 ;;; POSITIVE-FIXNUM (which it is). However, since the backend thinks of
1389 ;;; these as distinct storage classes, it cannot coerce a move from a
1390 ;;; FIXNUM TN to a POSITIVE-FIXNUM TN. The practical effect of this
1391 ;;; deficiency is that we have two extra moves and increased register
1392 ;;; pressure, which can lead to some spectacularly bad register
1393 ;;; allocation. (sub-FIXME: the register allocation even with the
1394 ;;; strangely written loops is not always excellent, either...). Doing
1395 ;;; it the first way, above, means that I is always thought of as a
1396 ;;; POSITIVE-FIXNUM and there are no issues.
1398 ;;; Besides, the *-WITH-OFFSET machinery will fold those index
1399 ;;; adjustments in the first version into the array addressing at no
1400 ;;; performance penalty!
1402 ;;; This transform is critical to the performance of string streams. If
1403 ;;; you tweak it, make sure that you compare the disassembly, if not the
1404 ;;; performance of, the functions implementing string streams
1405 ;;; (e.g. SB-IMPL::BASE-STRING-SOUT).
1406 (defun transform-replace-bashable (bash-function node)
1407 ;; This is a little circuitous - we transform REPLACE into BASH-COPY
1408 ;; and then possibly transform BASH-COPY into an unrolled loop.
1409 ;; There ought to be a way to see if the BASH-COPY transform applies.
1410 `(let* ((len1 (length seq1))
1411 (len2 (length seq2))
1412 (end1 (or end1 len1))
1413 (end2 (or end2 len2))
1414 (replace-len (min (- end1 start1) (- end2 start2))))
1415 ,@(when (policy node (/= insert-array-bounds-checks 0))
1416 '((unless (<= 0 start1 end1 len1)
1417 (sequence-bounding-indices-bad-error seq1 start1 end1))
1418 (unless (<= 0 start2 end2 len2)
1419 (sequence-bounding-indices-bad-error seq2 start2 end2))))
1420 (,bash-function seq2 start2 seq1 start1 replace-len)
1421 seq1))
1422 (defun transform-replace (same-types-p node)
1423 `(let* ((len1 (length seq1))
1424 (len2 (length seq2))
1425 (end1 (or end1 len1))
1426 (end2 (or end2 len2))
1427 (replace-len (min (- end1 start1) (- end2 start2))))
1428 ,@(when (policy node (/= insert-array-bounds-checks 0))
1429 '((unless (<= 0 start1 end1 len1)
1430 (sequence-bounding-indices-bad-error seq1 start1 end1))
1431 (unless (<= 0 start2 end2 len2)
1432 (sequence-bounding-indices-bad-error seq2 start2 end2))))
1433 ,(flet ((down ()
1434 '(do ((i (truly-the (or (eql -1) index) (+ start1 replace-len -1)) (1- i))
1435 (j (truly-the (or (eql -1) index) (+ start2 replace-len -1)) (1- j)))
1436 ((< j start2))
1437 (declare (optimize (insert-array-bounds-checks 0)))
1438 (setf (aref seq1 i) (data-vector-ref seq2 j))))
1439 (up ()
1440 '(do ((i start1 (1+ i))
1441 (j start2 (1+ j))
1442 (end (+ start1 replace-len)))
1443 ((>= i end))
1444 (declare (optimize (insert-array-bounds-checks 0)))
1445 (setf (aref seq1 i) (data-vector-ref seq2 j)))))
1446 ;; "If sequence-1 and sequence-2 are the same object and the region being modified
1447 ;; overlaps the region being copied from, then it is as if the entire source region
1448 ;; were copied to another place and only then copied back into the target region.
1449 ;; However, if sequence-1 and sequence-2 are not the same, but the region being modified
1450 ;; overlaps the region being copied from (perhaps because of shared list structure or
1451 ;; displaced arrays), then after the replace operation the subsequence of sequence-1
1452 ;; being modified will have unpredictable contents."
1453 (if same-types-p ; source and destination sequences could be EQ
1454 `(if (and (eq seq1 seq2) (> start1 start2)) ,(down) ,(up))
1455 (up)))
1456 seq1))
1458 (deftransform replace ((seq1 seq2 &key (start1 0) (start2 0) end1 end2)
1459 ((simple-array * (*)) (simple-array * (*)) &rest t) (simple-array * (*))
1460 :node node)
1461 (let ((et1 (ctype-array-specialized-element-types (lvar-type seq1)))
1462 (et2 (ctype-array-specialized-element-types (lvar-type seq2))))
1463 (if (and (typep et1 '(cons * null))
1464 (typep et2 '(cons * null))
1465 (eq (car et1) (car et2)))
1466 (let ((saetp (find-saetp-by-ctype (car et1))))
1467 (if (sb-vm:valid-bit-bash-saetp-p saetp)
1468 (transform-replace-bashable
1469 (intern (format nil "UB~D-BASH-COPY" (sb-vm:saetp-n-bits saetp))
1470 #.(find-package "SB-KERNEL"))
1471 node)
1472 (transform-replace t node)))
1473 (give-up-ir1-transform))))
1474 #+sb-unicode
1475 (progn
1476 (deftransform replace ((seq1 seq2 &key (start1 0) (start2 0) end1 end2)
1477 (simple-base-string simple-character-string &rest t) simple-base-string
1478 :node node)
1479 (transform-replace nil node))
1480 (deftransform replace ((seq1 seq2 &key (start1 0) (start2 0) end1 end2)
1481 (simple-character-string simple-base-string &rest t) simple-character-string
1482 :node node)
1483 (transform-replace nil node)))
1485 (defoptimizer (replace ir2-hook) ((seq1 seq2 &key start1 end1 start2 end2) node)
1486 (flet ((element-type (lvar)
1487 (type-array-element-type (lvar-type lvar))))
1488 (let ((type1 (element-type seq1))
1489 (type2 (element-type seq2)))
1490 (check-sequence-ranges seq1 start1 end1 node 1 'target-sequence1)
1491 (check-sequence-ranges seq2 start2 end2 node 2 'source-sequence2)
1492 (cond ((eq type1 *wild-type*))
1493 ((eq type2 *wild-type*)
1494 (when (constant-lvar-p seq2)
1495 (map nil (lambda (x)
1496 (unless (ctypep x type1)
1497 (let ((*compiler-error-context* node))
1498 (compiler-warn "The source sequence has an element ~s incompatible with the target array element type ~a."
1500 (type-specifier type1)))
1501 (return-from replace-ir2-hook-optimizer))
1503 (lvar-value seq2))))
1504 ((not (types-equal-or-intersect type1 type2))
1505 (let ((*compiler-error-context* node))
1506 (compiler-warn "Incompatible array element types: ~a and ~a"
1507 (type-specifier type1)
1508 (type-specifier type2))))))))
1510 (defoptimizer (%make-array ir2-hook) ((dimensions widetag n-bits &key initial-contents &allow-other-keys) node)
1511 (when (and (constant-lvar-p widetag)
1512 initial-contents)
1513 (let* ((saetp (find (lvar-value widetag) sb-vm:*specialized-array-element-type-properties*
1514 :key #'sb-vm:saetp-typecode))
1515 (element-type (sb-vm:saetp-ctype saetp))
1516 (initial-contents-type (lvar-type initial-contents))
1517 (initial-contents-element-type (type-array-element-type initial-contents-type)))
1518 (cond ((not (or (eq initial-contents-element-type *wild-type*)
1519 (types-equal-or-intersect element-type initial-contents-element-type)))
1520 (let ((*compiler-error-context* node))
1521 (compiler-warn "Incompatible :initial-contents ~s for :element-type ~a."
1522 (type-specifier initial-contents-type)
1523 (sb-vm:saetp-specifier saetp))))
1524 ((constant-lvar-p initial-contents)
1525 (let ((initial-contents (lvar-value initial-contents)))
1526 (when (sequencep initial-contents)
1527 (map nil (lambda (x)
1528 (unless (ctypep x element-type)
1529 (let ((*compiler-error-context* node))
1530 (compiler-warn ":initial-contents has an element ~s incompatible with :element-type ~a."
1532 (type-specifier element-type)))
1533 (return-from %make-array-ir2-hook-optimizer))
1535 initial-contents))))))))
1537 (defun check-sequence-item (item seq node format-string)
1538 (let ((seq-type (lvar-type seq))
1539 (item-type (lvar-type item)))
1540 (when (neq item-type *wild-type*)
1541 (let ((element-type (type-array-element-type seq-type)))
1542 (unless (or (eq element-type *wild-type*)
1543 (types-equal-or-intersect item-type element-type))
1544 (let ((*compiler-error-context* node))
1545 (compiler-warn format-string
1546 (type-specifier item-type)
1547 (type-specifier seq-type))))))))
1549 (defoptimizers ir2-hook
1550 (substitute substitute-if substitute-if-not
1551 nsubstitute nsubstitute-if nsubstitute-if-not)
1552 ((new x seq &key start end &allow-other-keys) node)
1553 (check-sequence-ranges seq start end node)
1554 (check-sequence-item new seq node "Can't substitute ~a into ~a"))
1556 (defoptimizer (vector-fill* ir2-hook) ((seq item start end) node)
1557 (check-sequence-ranges seq start end node)
1558 (check-sequence-item item seq node "Can't fill ~a into ~a"))
1560 (defoptimizer (vector-push ir2-hook) ((item vector) node)
1561 (check-sequence-item item vector node "Can't push ~a into ~a"))
1563 (defoptimizer (vector-push-extend ir2-hook) ((item vector &optional min-extension) node)
1564 (check-sequence-item item vector node "Can't push ~a into ~a"))
1566 (defun check-concatenate (type sequences node &optional (description "concatenate"))
1567 (let ((result-element-type (if (ctype-p type)
1568 type
1569 (type-array-element-type (or (careful-specifier-type type)
1570 (return-from check-concatenate))))))
1571 (unless (or (eq result-element-type *wild-type*)
1572 (eq result-element-type *universal-type*))
1573 (loop for i from 0
1574 for sequence in sequences
1575 for sequence-type = (lvar-type sequence)
1576 for element-type = (type-array-element-type sequence-type)
1577 do (unless (or (eq element-type *wild-type*)
1578 (types-equal-or-intersect element-type result-element-type))
1579 (let ((*compiler-error-context* node))
1580 (compiler-warn "Can't ~a ~s into ~s"
1581 description
1582 (type-specifier sequence-type)
1583 (if (ctype-p type)
1584 (type-specifier (make-array-type '(*)
1585 :specialized-element-type type
1586 :element-type type))
1587 type))))))))
1589 (defoptimizer (%concatenate-to-string ir2-hook) ((&rest args) node)
1590 (check-concatenate 'string args node))
1592 (defoptimizer (%concatenate-to-base-string ir2-hook) ((&rest args) node)
1593 (check-concatenate 'base-string args node))
1595 (defoptimizer (%concatenate-to-vector ir2-hook) ((widetag &rest args) node)
1596 (when (constant-lvar-p widetag)
1597 (check-concatenate (sb-vm:saetp-ctype
1598 (find (lvar-value widetag)
1599 sb-vm:*specialized-array-element-type-properties*
1600 :key #'sb-vm:saetp-typecode))
1601 args node)))
1603 (defoptimizer (merge ir2-hook) ((type sequence1 sequence2 predicate &key &allow-other-keys) node)
1604 (when (constant-lvar-p type)
1605 (check-concatenate (lvar-value type) (list sequence1 sequence2) node "merge")))
1607 ;;; Expand simple cases of UB<SIZE>-BASH-COPY inline. "simple" is
1608 ;;; defined as those cases where we are doing word-aligned copies from
1609 ;;; both the source and the destination and we are copying from the same
1610 ;;; offset from both the source and the destination. (The last
1611 ;;; condition is there so we can determine the direction to copy at
1612 ;;; compile time rather than runtime. Remember that UB<SIZE>-BASH-COPY
1613 ;;; acts like memmove, not memcpy.) These conditions may seem rather
1614 ;;; restrictive, but they do catch common cases, like allocating a (* 2
1615 ;;; N)-size buffer and blitting in the old N-size buffer in.
1617 (defun make-bash-copy-transform (n-bits-per-elem)
1618 (deftransform transform-bash-copy ((src src-offset dst dst-offset length)
1620 :defun-only lambda)
1621 (declare (ignore src dst length))
1622 (binding* ((n-elems-per-word (truncate sb-vm:n-word-bits n-bits-per-elem))
1623 ((src-word src-elt) (truncate (lvar-value src-offset) n-elems-per-word))
1624 ((dst-word dst-elt) (truncate (lvar-value dst-offset) n-elems-per-word)))
1625 ;; Avoid non-word aligned copies.
1626 (unless (and (zerop src-elt) (zerop dst-elt))
1627 (give-up-ir1-transform))
1628 ;; Avoid copies where we would have to insert code for
1629 ;; determining the direction of copying.
1630 (unless (= src-word dst-word)
1631 (give-up-ir1-transform))
1632 `(let ((end (+ ,src-word (truncate (the index length) ,n-elems-per-word)))
1633 (extra (mod length ,n-elems-per-word)))
1634 (declare (type index end))
1635 ;; Handle any bits at the end.
1636 (unless (zerop extra)
1637 ;; MASK selects just the bits that we want from the ending word of
1638 ;; the source array. The number of bits to shift out is
1639 ;; (- n-word-bits (* extra n-bits-per-elem))
1640 ;; which is equal mod n-word-bits to the expression below.
1641 (let ((mask (shift-towards-start
1642 most-positive-word (* extra ,(- n-bits-per-elem)))))
1643 (%set-vector-raw-bits
1644 dst end (logior (logand (%vector-raw-bits src end) mask)
1645 (logandc2 (%vector-raw-bits dst end) mask)))))
1646 ;; Copy from the end to save a register.
1647 (do ((i (1- end) (1- i)))
1648 ((< i ,src-word))
1649 (%set-vector-raw-bits dst i (%vector-raw-bits src i)))
1650 (values)))))
1652 ;;; Detect misuse with sb-devel. "Misuse" means mismatched array element types
1653 #-sb-devel
1654 (loop for i = 1 then (* i 2)
1655 do (%deftransform (package-symbolicate "SB-KERNEL" "UB" i "-BASH-COPY")
1657 '(function ((simple-unboxed-array (*)) (constant-arg index)
1658 (simple-unboxed-array (*)) (constant-arg index)
1659 index) *)
1660 (make-bash-copy-transform i))
1661 until (= i sb-vm:n-word-bits))
1663 ;;; We expand copy loops inline in SUBSEQ and COPY-SEQ if we're copying
1664 ;;; arrays with elements of size >= the word size. We do this because
1665 ;;; we know the arrays cannot alias (one was just consed), therefore we
1666 ;;; can determine at compile time the direction to copy, and for
1667 ;;; word-sized elements, UB<WORD-SIZE>-BASH-COPY will do a bit of
1668 ;;; needless checking to figure out what's going on. The same
1669 ;;; considerations apply if we are copying elements larger than the word
1670 ;;; size, with the additional twist that doing it inline is likely to
1671 ;;; cons far less than calling REPLACE and letting generic code do the
1672 ;;; work.
1674 ;;; However, we do not do this for elements whose size is < than the
1675 ;;; word size because we don't want to deal with any alignment issues
1676 ;;; inline. The UB*-BASH-COPY transforms might fix things up later
1677 ;;; anyway.
1679 (defun inlineable-copy-vector-p (type)
1680 (and (array-type-p type)
1681 ;; The two transforms that use this test already specify that their
1682 ;; sequence argument is a VECTOR,
1683 ;; so this seems like it would be more efficient as
1684 ;; and (not (array-type-complexp type))
1685 ;; (not (eq (array-type-element-type type) *wild-type*))
1686 ;; Anyway it no longer works to write this as a single specifier
1687 ;; '(or (simple-unboxed-array (*)) simple-vector) because that
1688 ;; type is just (simple-array * (*)) which isn't amenable to
1689 ;; inline copying since we don't know what it holds.
1690 (or (csubtypep type (specifier-type '(simple-unboxed-array (*))))
1691 (csubtypep type (specifier-type 'simple-vector)))))
1693 (defun maybe-expand-copy-loop-inline (src src-offset dst dst-offset length
1694 element-type)
1695 (let ((saetp (find-saetp element-type)))
1696 (aver saetp)
1697 (if (>= (sb-vm:saetp-n-bits saetp) sb-vm:n-word-bits)
1698 (expand-aref-copy-loop src src-offset dst dst-offset length)
1699 `(locally (declare (optimize (safety 0)))
1700 (replace ,dst ,src :start1 ,dst-offset :start2 ,src-offset :end1 ,length)))))
1702 (defun expand-aref-copy-loop (src src-offset dst dst-offset length)
1703 (if (eql src-offset dst-offset)
1704 `(do ((i (+ ,src-offset ,length) (1- i)))
1705 ((<= i ,src-offset))
1706 (declare (optimize (insert-array-bounds-checks 0)))
1707 (setf (aref ,dst (1- i)) (aref ,src (1- i))))
1708 ;; KLUDGE: The compiler is not able to derive that (+ offset
1709 ;; length) must be a fixnum, but arrives at (unsigned-byte 29).
1710 ;; We, however, know it must be so, as by this point the bounds
1711 ;; have already been checked.
1712 `(do ((i (truly-the fixnum (+ ,src-offset ,length)) (1- i))
1713 (j (+ ,dst-offset ,length) (1- j)))
1714 ((<= i ,src-offset))
1715 (declare (optimize (insert-array-bounds-checks 0))
1716 (type (integer 0 #.array-dimension-limit) j i))
1717 (setf (aref ,dst (1- j)) (aref ,src (1- i))))))
1719 ;;; MAKE-SEQUENCE, SUBSEQ, COPY-SEQ
1721 (deftransform make-sequence ((result-type size &key initial-element) * *)
1722 (multiple-value-bind (spec type)
1723 (and (constant-lvar-p result-type)
1724 (let ((spec (lvar-value result-type)))
1725 (values spec (ir1-transform-specifier-type spec))))
1726 (unless type
1727 (give-up-ir1-transform))
1728 (if (type= type (specifier-type 'list))
1729 `(%make-list size initial-element)
1730 (multiple-value-bind (elt-type dim complexp)
1731 (cond ((and (union-type-p type)
1732 (csubtypep type (specifier-type 'string)))
1733 (let* ((types (union-type-types type))
1734 (first (first types)))
1735 (when (array-type-p first)
1736 (let ((dim (first (array-type-dimensions first)))
1737 (complexp (array-type-complexp first)))
1738 ;; Require sameness of dim and complexp. Give up on
1739 ;; (OR (VECTOR CHARACTER) (VECTOR BASE-CHAR 2))
1740 ;; which eventually fails in the call to the function.
1741 (when (every (lambda (x)
1742 (and (array-type-p x)
1743 (eql (first (array-type-dimensions x))
1744 dim)
1745 (eq (array-type-complexp x) complexp)))
1746 (rest types))
1747 (values
1748 `(or ,@(mapcar
1749 (lambda (x)
1750 (type-specifier (array-type-element-type x)))
1751 types))
1752 dim complexp))))))
1753 ((and (array-type-p type)
1754 (csubtypep type (specifier-type 'vector)))
1755 (when (contains-unknown-type-p (array-type-element-type type))
1756 (give-up-ir1-transform "~S is an unknown vector type" spec))
1757 (values (let ((et (array-type-element-type type)))
1758 ;; VECTOR means (VECTOR T)
1759 (if (type= et *wild-type*)
1761 (type-specifier et)))
1762 (first (array-type-dimensions type))
1763 (array-type-complexp type))))
1764 ;; Don't transform if size is present in the specifier
1765 ;; and the SIZE argument is not known to be equal.
1766 (cond ((and (or (eq '* dim)
1767 (and dim (constant-lvar-p size) (eql (lvar-value size) dim)))
1768 ;; not sure what it would mean to make it non-simple
1769 (neq complexp t))
1770 `(make-array size :element-type ',elt-type
1771 ,@(when initial-element
1772 `(:initial-element initial-element))))
1773 ;; no transform, but we can detect some style issues
1775 (when dim ; was a recognizable vector subtype
1776 (let* ((elt-ctype (specifier-type elt-type))
1777 (saetp (find-saetp-by-ctype elt-ctype)))
1778 (cond ((not initial-element)
1779 (let ((default-initial-element
1780 (sb-vm:saetp-initial-element-default saetp)))
1781 (unless (ctypep default-initial-element elt-ctype)
1782 ;; As with MAKE-ARRAY, this is merely undefined
1783 ;; behavior, not an error.
1784 (compiler-style-warn
1785 'initial-element-mismatch-style-warning
1786 :format-control "The default initial element ~S is not a ~S."
1787 :format-arguments (list default-initial-element elt-type)))))
1788 ;; In would be possible in some cases,
1789 ;; like :INITIAL-ELEMENT (IF X #\x #\y) in a call
1790 ;; to MAKE-SEQUENCE '(VECTOR (MEMBER #\A #\B))
1791 ;; to detect erroneous non-constants initializers,
1792 ;; but it is not important enough to bother with.
1793 ((and (constant-lvar-p initial-element)
1794 (not (ctypep (lvar-value initial-element)
1795 elt-ctype)))
1796 ;; MAKE-ARRAY considers this a warning, not an error.
1797 (compiler-warn 'array-initial-element-mismatch
1798 :format-control "~S ~S is not a ~S"
1799 :format-arguments
1800 (list :initial-element (lvar-value initial-element) elt-type))))))
1801 (give-up-ir1-transform)))))))
1803 (deftransform subseq ((seq start &optional end)
1804 (vector t &optional t)
1806 :node node)
1807 (let ((type (lvar-type seq)))
1808 (cond
1809 ((and (inlineable-copy-vector-p type)
1810 (policy node (> speed space)))
1811 (let ((element-type (type-specifier (array-type-specialized-element-type type))))
1812 `(let* ((length (length seq))
1813 (end (or end length)))
1814 ,@(when (policy node (/= insert-array-bounds-checks 0))
1815 '((unless (<= 0 start end length)
1816 (sequence-bounding-indices-bad-error seq start end))))
1817 (let* ((size (- end start))
1818 (result (make-array size :element-type ',element-type)))
1819 ,(maybe-expand-copy-loop-inline 'seq (if (constant-lvar-p start)
1820 (lvar-value start)
1821 'start)
1822 'result 0 'size element-type)
1823 result))))
1825 '(vector-subseq* seq start end)))))
1827 (deftransform subseq ((seq start &optional end)
1828 (list t &optional t))
1829 `(list-subseq* seq start end))
1831 (deftransform subseq ((seq start &optional end)
1832 ((and sequence (not vector) (not list)) t &optional t))
1833 '(sb-sequence:subseq seq start end))
1835 (deftransform copy-seq ((seq) (vector))
1836 (let ((type (lvar-type seq)))
1837 (cond ((inlineable-copy-vector-p type)
1838 (let ((element-type (type-specifier (array-type-specialized-element-type type))))
1839 `(let* ((length (length seq))
1840 (result (make-array length :element-type ',element-type)))
1841 ,(maybe-expand-copy-loop-inline 'seq 0 'result 0 'length element-type)
1842 result)))
1844 '(vector-subseq* seq 0 nil)))))
1846 (deftransform copy-seq ((seq) (list))
1847 '(list-copy-seq* seq))
1849 (deftransform copy-seq ((seq) ((and sequence (not vector) (not list))))
1850 '(sb-sequence:copy-seq seq))
1852 (deftransform search ((pattern text &key start1 start2 end1 end2 test test-not
1853 key from-end)
1854 ((constant-arg sequence) t &rest t))
1855 (if key
1856 (give-up-ir1-transform)
1857 (let* ((pattern (lvar-value pattern))
1858 (pattern-start (cond ((not (proper-sequence-p pattern))
1859 (give-up-ir1-transform))
1860 ((not start1)
1862 ((constant-lvar-p start1)
1863 (lvar-value start1))
1865 (give-up-ir1-transform))))
1866 (pattern-end (cond ((not end1)
1867 (length pattern))
1868 ((constant-lvar-p end1)
1869 (or (lvar-value end1)
1870 (length pattern)))
1872 (give-up-ir1-transform))))
1873 (pattern (if (and (= (- pattern-end pattern-start) 1)
1874 (sequence-of-length-at-least-p pattern
1875 (1+ pattern-start)))
1876 (elt pattern pattern-start)
1877 (give-up-ir1-transform))))
1878 (macrolet ((maybe-arg (arg &optional (key (keywordicate arg)))
1879 `(and ,arg `(,,key ,',arg))))
1880 `(position ',pattern text
1881 ,@(maybe-arg start2 :start)
1882 ,@(maybe-arg end2 :end)
1883 ,@(maybe-arg test)
1884 ,@(maybe-arg test-not)
1885 ,@(maybe-arg from-end))))))
1887 ;;; FIXME: it really should be possible to take advantage of the
1888 ;;; macros used in code/seq.lisp here to avoid duplication of code,
1889 ;;; and enable even funkier transformations.
1890 (deftransform search ((pattern text &key (start1 0) (start2 0) end1 end2
1891 (test #'eql)
1892 (key #'identity)
1893 from-end)
1894 (vector vector &rest t)
1896 :node node
1897 :policy (> speed (max space safety)))
1898 "open code"
1899 (flet ((maybe (x)
1900 (when (lvar-p x)
1901 (if (constant-lvar-p x)
1902 (when (lvar-value x)
1903 :yes)
1904 :maybe))))
1905 (let ((from-end (when (lvar-p from-end)
1906 (unless (constant-lvar-p from-end)
1907 (give-up-ir1-transform ":FROM-END is not constant."))
1908 (lvar-value from-end)))
1909 (key? (maybe key))
1910 (test? (maybe test))
1911 (check-bounds-p (policy node (plusp insert-array-bounds-checks))))
1912 `(block search
1913 (flet ((oops (vector start end)
1914 (sequence-bounding-indices-bad-error vector start end)))
1915 (declare (ignorable #'oops))
1916 (let* ((len1 (length pattern))
1917 (len2 (length text))
1918 (end1 (or end1 len1))
1919 (end2 (or end2 len2))
1920 ,@(case key?
1921 (:yes `((key (%coerce-callable-to-fun key))))
1922 (:maybe `((key (when key
1923 (%coerce-callable-to-fun key))))))
1924 ,@(when test?
1925 `((test (%coerce-callable-to-fun test)))))
1926 (declare (type index start1 start2 end1 end2))
1927 ,@(when check-bounds-p
1928 `((unless (<= start1 end1 len1)
1929 (oops pattern start1 end1))
1930 (unless (<= start2 end2 len2)
1931 (oops pattern start2 end2))))
1932 (when (= end1 start1)
1933 (return-from search (if from-end
1934 end2
1935 start2)))
1936 (do (,(if from-end
1937 '(index2 (- end2 (- end1 start1)) (1- index2))
1938 '(index2 start2 (1+ index2))))
1939 (,(if from-end
1940 '(< index2 start2)
1941 '(>= index2 end2))
1942 nil)
1943 ;; INDEX2 is FIXNUM, not an INDEX, as right before the loop
1944 ;; terminates is hits -1 when :FROM-END is true and :START2
1945 ;; is 0.
1946 (declare (type fixnum index2))
1947 (when (do ((index1 start1 (1+ index1))
1948 (index2 index2 (1+ index2)))
1949 ((>= index1 end1) t)
1950 (declare (type index index1 index2)
1951 (optimize (insert-array-bounds-checks 0)))
1952 ,@(unless from-end
1953 '((when (= index2 end2)
1954 (return-from search nil))))
1955 (unless (,@(if test?
1956 `(funcall test)
1957 `(eql))
1958 ,(case key?
1959 (:yes `(funcall key (aref pattern index1)))
1960 (:maybe `(let ((elt (aref pattern index1)))
1961 (if key
1962 (funcall key elt)
1963 elt)))
1964 (otherwise `(aref pattern index1)))
1965 ,(case key?
1966 (:yes `(funcall key (aref text index2)))
1967 (:maybe `(let ((elt (aref text index2)))
1968 (if key
1969 (funcall key elt)
1970 elt)))
1971 (otherwise `(aref text index2))))
1972 (return nil)))
1973 (return index2)))))))))
1975 (defoptimizer (search derive-type) ((sequence1 sequence2
1976 &key start1 end1 start2 end2
1977 from-end
1978 &allow-other-keys))
1979 (let* ((constant-start1 (and start1
1980 (constant-lvar-p start1)
1981 (lvar-value start1)))
1982 (constant-end1 (and end1
1983 (constant-lvar-p end1)
1984 (lvar-value end1)))
1985 (constant-start2 (and start2
1986 (constant-lvar-p start2)
1987 (lvar-value start2)))
1988 (constant-end2 (and end2
1989 (constant-lvar-p end2)
1990 (lvar-value end2)))
1991 (not-from-end (unsupplied-or-nil from-end))
1992 (min-result (or constant-start2 0))
1993 (max-result (or constant-end2 (1- array-dimension-limit)))
1994 (max2 (sequence-lvar-dimensions sequence2))
1995 (max-result (if (integerp max2)
1996 (min max-result max2)
1997 max-result))
1998 (min1 (nth-value 1 (sequence-lvar-dimensions sequence1)))
1999 (min-sequence1-length (cond ((and constant-start1 constant-end1)
2000 (- constant-end1 constant-start1))
2001 ((and constant-end1 (not start1))
2002 constant-end1)
2003 ((and constant-start1
2004 (not end1)
2005 (integerp min1))
2006 (- min1 constant-start1))
2007 ((or start1 end1 (not (integerp min1)))
2008 ;; The result can be equal to MAX-RESULT only when
2009 ;; searching for "" and :start2 being equal to :end2
2010 ;; or :from-end t
2011 (if (or (not not-from-end)
2012 (and start2
2013 (not constant-start2))
2014 (= max-result min-result))
2018 min1))))
2019 (specifier-type `(or (integer ,min-result
2020 ,(- max-result min-sequence1-length))
2021 null))))
2023 (defun index-into-sequence-derive-type (sequence start end &key (inclusive t))
2024 (let* ((constant-start (and start
2025 (constant-lvar-p start)
2026 (lvar-value start)))
2027 (constant-end (and end
2028 (constant-lvar-p end)
2029 (lvar-value end)))
2030 (min-result (or constant-start 0))
2031 (max-result (or constant-end (1- array-dimension-limit)))
2032 (max (sequence-lvar-dimensions sequence))
2033 (max-result (if (integerp max)
2034 (min max-result max)
2035 max-result)))
2036 (values min-result (if inclusive
2037 max-result
2038 (1- max-result)))))
2040 (defoptimizer (mismatch derive-type) ((sequence1 sequence2
2041 &key start1 end1
2042 &allow-other-keys))
2043 (declare (ignorable sequence2))
2044 ;; Could be as smart as the SEARCH one above but I ran out of steam.
2045 (multiple-value-bind (min max) (index-into-sequence-derive-type sequence1 start1 end1)
2046 (specifier-type `(or (integer ,min ,max) null))))
2048 (defun position-derive-type (item sequence start end key test test-not)
2049 (multiple-value-bind (min max)
2050 (index-into-sequence-derive-type sequence start end :inclusive nil)
2051 (when (>= max min)
2052 (let ((integer-range `(integer ,min ,max))
2053 (definitely-foundp nil))
2054 ;; Figure out whether this call will not return NIL.
2055 ;; This could be smarter about the keywords args, but the primary intent
2056 ;; is to avoid a style-warning about arithmetic in such forms such as
2057 ;; (1+ (position (the (member :x :y) item) #(:foo :bar :x :y))).
2058 ;; In that example, a more exact bound could be determined too.
2059 (cond ((or (not (constant-lvar-p sequence))
2060 start end key test test-not
2061 (not item)))
2063 (let ((const-seq (lvar-value sequence))
2064 (item-type (lvar-type item)))
2065 (when (and (or (vectorp const-seq) (proper-list-p const-seq))
2066 (member-type-p item-type))
2067 (setq definitely-foundp t) ; assume best case
2068 (block nil
2069 (mapc-member-type-members
2070 (lambda (possibility)
2071 (unless (find possibility const-seq)
2072 (setq definitely-foundp nil)
2073 (return)))
2074 item-type))))))
2075 (specifier-type (if definitely-foundp
2076 integer-range
2077 `(or ,integer-range null)))))))
2079 (defun find-derive-type (item sequence key test start end from-end)
2080 (declare (ignore start end from-end))
2081 (let ((type *universal-type*)
2082 (key-identity-p (or (not key)
2083 (lvar-value-is key nil)
2084 (lvar-fun-is key '(identity)))))
2085 (flet ((fun-accepts-type (fun-lvar argument)
2086 (when fun-lvar
2087 (let ((fun-type (lvar-fun-type fun-lvar t t)))
2088 (when (fun-type-p fun-type)
2089 (let ((arg (nth argument (fun-type-n-arg-types (1+ argument) fun-type))))
2090 (when arg
2091 (setf type
2092 (type-intersection type arg)))))))))
2093 (when (and item
2094 key-identity-p
2095 (or (not test)
2096 (lvar-fun-is test '(eq eql char= char-equal))
2097 (lvar-value-is test nil)))
2098 ;; Maybe FIND returns ITEM itself (or an EQL number).
2099 (setf type (lvar-type item)))
2100 ;; Should return something the functions can accept
2101 (if key-identity-p
2102 (fun-accepts-type test (if item 1 0)) ;; the -if variants.
2103 (fun-accepts-type key 0)))
2104 (let ((upgraded-type (type-array-element-type (lvar-type sequence))))
2105 (unless (eq upgraded-type *wild-type*)
2106 (setf type
2107 (type-intersection type upgraded-type))))
2108 (unless (eq type *empty-type*)
2109 (type-union type
2110 (specifier-type 'null)))))
2112 (defoptimizer (find derive-type) ((item sequence &key key test
2113 start end from-end))
2114 (find-derive-type item sequence key test start end from-end))
2116 (defoptimizer (find-if derive-type) ((predicate sequence &key key start end from-end))
2117 (find-derive-type nil sequence key predicate start end from-end))
2119 (defoptimizer (find-if-not derive-type) ((predicate sequence &key key start end from-end))
2120 (find-derive-type nil sequence key predicate start end from-end))
2122 (defoptimizer (position derive-type) ((item sequence
2123 &key start end
2124 key test test-not
2125 &allow-other-keys))
2126 (position-derive-type item sequence start end key test test-not))
2128 (defoptimizer (position-if derive-type) ((function sequence
2129 &key start end
2130 &allow-other-keys))
2131 (declare (ignore function))
2132 (multiple-value-bind (min max)
2133 (index-into-sequence-derive-type sequence start end :inclusive nil)
2134 (specifier-type `(or (integer ,min ,max) null))))
2136 (defoptimizer (position-if-not derive-type) ((function sequence
2137 &key start end
2138 &allow-other-keys))
2139 (declare (ignore function))
2140 (multiple-value-bind (min max)
2141 (index-into-sequence-derive-type sequence start end :inclusive nil)
2142 (specifier-type `(or (integer ,min ,max) null))))
2144 (defoptimizer (%find-position derive-type) ((item sequence from-end start end key test))
2145 (let ((find (find-derive-type item sequence key test start end from-end))
2146 (position (position-derive-type item sequence start end key test nil)))
2147 (when (or find position)
2148 (make-values-type (list (or find *universal-type*)
2149 (or position *universal-type*))))))
2151 (defoptimizer (%find-position-if derive-type) ((predicate sequence from-end start end key))
2152 (let ((find (find-derive-type nil sequence key predicate start end from-end))
2153 (position (position-derive-type nil sequence start end key predicate nil)))
2154 (when (or find position)
2155 (make-values-type (list (or find *universal-type*)
2156 (or position *universal-type*))))))
2158 (defoptimizer (%find-position-if-not derive-type) ((predicate sequence from-end start end key))
2159 (let ((find (find-derive-type nil sequence key predicate start end from-end))
2160 (position (position-derive-type nil sequence start end key predicate nil)))
2161 (when (or find position)
2162 (make-values-type (list (or find *universal-type*)
2163 (or position *universal-type*))))))
2165 (defoptimizer (count derive-type) ((item sequence
2166 &key start end
2167 &allow-other-keys))
2168 (declare (ignore item))
2169 (multiple-value-bind (min max)
2170 (index-into-sequence-derive-type sequence start end)
2171 (specifier-type `(integer 0 ,(- max min)))))
2173 (defoptimizer (count-if derive-type) ((function sequence
2174 &key start end
2175 &allow-other-keys))
2176 (declare (ignore function))
2177 (multiple-value-bind (min max)
2178 (index-into-sequence-derive-type sequence start end)
2179 (specifier-type `(integer 0 ,(- max min)))))
2181 (defoptimizer (count-if-not derive-type) ((function sequence
2182 &key start end
2183 &allow-other-keys))
2184 (declare (ignore function))
2185 (multiple-value-bind (min max)
2186 (index-into-sequence-derive-type sequence start end)
2187 (specifier-type `(integer 0 ,(- max min)))))
2189 (defoptimizer (subseq derive-type) ((sequence start &optional end) node)
2190 (let* ((sequence-type (lvar-type sequence))
2191 (constant-start (and (constant-lvar-p start)
2192 (lvar-value start)))
2193 (constant-end (and end
2194 (constant-lvar-p end)
2195 (lvar-value end)))
2196 (index-length (and constant-start constant-end
2197 (- constant-end constant-start)))
2198 (list-type (specifier-type 'list)))
2199 (flet ((bad ()
2200 (let ((*compiler-error-context* node))
2201 (compiler-warn "Bad bounding indices ~s, ~s for ~
2202 ~/sb-impl:print-type/"
2203 constant-start constant-end sequence-type))))
2204 (cond ((and index-length
2205 (minusp index-length))
2206 ;; Would be a good idea to transform to something like
2207 ;; %compile-time-type-error
2208 (bad))
2209 ((csubtypep sequence-type list-type)
2210 (let ((null-type (specifier-type 'null)))
2211 (cond ((csubtypep sequence-type null-type)
2212 (cond ((or (and constant-start
2213 (plusp constant-start))
2214 (and index-length
2215 (plusp index-length)))
2216 (bad))
2217 ((eql constant-start 0)
2218 null-type)
2220 list-type)))
2221 ((not index-length)
2222 list-type)
2223 ((zerop index-length)
2224 null-type)
2226 (specifier-type 'cons)))))
2227 ((csubtypep sequence-type (specifier-type 'vector))
2228 (let* ((dimensions
2229 ;; Can't trust lengths from non-simple vectors due to
2230 ;; fill-pointer and adjust-array
2231 (and (csubtypep sequence-type (specifier-type 'simple-array))
2232 (ctype-array-dimensions sequence-type)))
2233 (dimensions-length
2234 (and (singleton-p dimensions)
2235 (integerp (car dimensions))
2236 (car dimensions)))
2237 (length (cond (index-length)
2238 ((and dimensions-length
2239 (not end)
2240 constant-start)
2241 (- dimensions-length constant-start))))
2242 (simplified (simplify-vector-type sequence-type)))
2243 (cond ((and dimensions-length
2245 (and constant-start
2246 (> constant-start dimensions-length))
2247 (and constant-end
2248 (> constant-end dimensions-length))))
2249 (bad))
2250 (length
2251 (type-intersection simplified
2252 (specifier-type `(simple-array * (,length)))))
2254 simplified))))
2255 ((not index-length)
2256 nil)
2257 ((zerop index-length)
2258 (specifier-type '(not cons)))
2260 (specifier-type '(not null)))))))
2262 ;;; Open-code CONCATENATE for strings. It would be possible to extend
2263 ;;; this transform to non-strings, but I chose to just do the case that
2264 ;;; should cover 95% of CONCATENATE performance complaints for now.
2265 ;;; -- JES, 2007-11-17
2267 ;;; Only handle the simple result type cases. If somebody does (CONCATENATE
2268 ;;; '(STRING 6) ...) their code won't be optimized, but nobody does that in
2269 ;;; practice.
2271 ;;; Limit full open coding based on length of constant sequences. Default
2272 ;;; value is chosen so that other parts of the compiler (constraint propagation
2273 ;;; mainly) won't go nonlinear too badly. It's not an exact number -- but
2274 ;;; in the right ballpark.
2275 (defvar *concatenate-open-code-limit* 129)
2277 (defun string-concatenate-transform (node type lvars)
2278 (let ((vars (make-gensym-list (length lvars))))
2279 (if (policy node (<= speed space))
2280 ;; Out-of-line
2281 (let ((constants-to-string
2282 ;; Strings are handled more efficiently by
2283 ;; %concatenate-to-* functions
2284 (loop for var in vars
2285 for lvar in lvars
2286 collect (if (and (constant-lvar-p lvar)
2287 (proper-sequence-p (lvar-value lvar))
2288 (every #'characterp (lvar-value lvar)))
2289 (coerce (lvar-value lvar) 'string)
2290 var))))
2291 `(lambda (.dummy. ,@vars)
2292 (declare (ignore .dummy.)
2293 (ignorable ,@vars))
2294 ,(ecase type
2295 ((string simple-string)
2296 `(%concatenate-to-string ,@constants-to-string))
2297 ((base-string simple-base-string)
2298 `(%concatenate-to-base-string ,@constants-to-string)))))
2299 ;; Inline
2300 (let* ((element-type (ecase type
2301 ((string simple-string) 'character)
2302 ((base-string simple-base-string) 'base-char)))
2303 (lvar-values (loop for lvar in lvars
2304 collect (when (constant-lvar-p lvar)
2305 (lvar-value lvar))))
2306 (lengths
2307 (loop for value in lvar-values
2308 for var in vars
2309 collect (if value
2310 (length value)
2311 `(sb-impl::string-dispatch ((simple-array * (*))
2312 sequence)
2313 ,var
2314 #-sb-xc-host
2315 (declare (muffle-conditions compiler-note))
2316 (length ,var)))))
2317 (non-constant-start
2318 (loop for value in lvar-values
2319 while (and (stringp value)
2320 (< (length value) *concatenate-open-code-limit*))
2321 sum (length value))))
2322 `(lambda (.dummy. ,@vars)
2323 (declare (ignore .dummy.)
2324 (ignorable ,@vars))
2325 (declare (optimize (insert-array-bounds-checks 0)))
2326 (let* ((.length. (+ ,@lengths))
2327 (.pos. ,non-constant-start)
2328 (.string. (make-string .length. :element-type ',element-type)))
2329 (declare (type index .length. .pos.)
2330 #-sb-xc-host (muffle-conditions compiler-note)
2331 (ignorable .pos.))
2332 ,@(loop with constants = -1
2333 for value in lvar-values
2334 for var in vars
2335 collect
2336 (cond ((and (stringp value)
2337 (< (length value) *concatenate-open-code-limit*))
2338 ;; Fold the array reads for constant arguments
2339 `(progn
2340 ,@(loop for c across value
2341 for i from 0
2342 collect
2343 ;; Without truly-the we get massive numbers
2344 ;; of pointless error traps.
2345 `(setf (aref .string.
2346 (truly-the index ,(if constants
2347 (incf constants)
2348 `(+ .pos. ,i))))
2349 ,c))
2350 ,(unless constants
2351 `(incf (truly-the index .pos.) ,(length value)))))
2353 (prog1
2354 `(sb-impl::string-dispatch
2355 (#+sb-unicode
2356 (simple-array character (*))
2357 (simple-array base-char (*))
2359 ,var
2360 (replace .string. ,var
2361 ,@(cond ((not constants)
2362 '(:start1 .pos.))
2363 ((plusp non-constant-start)
2364 `(:start1 ,non-constant-start))))
2365 (incf (truly-the index .pos.) (length ,var)))
2366 (setf constants nil)))))
2367 .string.))))))
2369 (defun vector-specifier-widetag (type)
2370 ;; FIXME: This only accepts vectors without dimensions even though
2371 ;; it's not that hard to support them for the concatenate transform,
2372 ;; but it's probably not used often enough to bother.
2373 (cond ((and (array-type-p type)
2374 (equal (array-type-dimensions type) '(*)))
2375 (let* ((el-ctype (array-type-element-type type))
2376 (el-ctype (if (eq el-ctype *wild-type*)
2377 *universal-type*
2378 el-ctype))
2379 (saetp (find-saetp-by-ctype el-ctype)))
2380 (when saetp
2381 (sb-vm:saetp-typecode saetp))))
2382 ((and (union-type-p type)
2383 (csubtypep type (specifier-type 'string))
2384 (loop for type in (union-type-types type)
2385 always (and (array-type-p type)
2386 (equal (array-type-dimensions type) '(*)))))
2387 #+sb-unicode
2388 sb-vm:simple-character-string-widetag
2389 #-sb-unicode
2390 sb-vm:simple-base-string-widetag)))
2392 (deftransform concatenate ((result-type &rest lvars)
2393 ((constant-arg t)
2394 &rest sequence)
2395 * :node node)
2396 (let* ((type (ir1-transform-specifier-type (lvar-value result-type)))
2397 (vector-widetag (vector-specifier-widetag type)))
2398 (flet ((coerce-constants (vars type)
2399 ;; Lists are faster to iterate over than vectors of
2400 ;; unknown type.
2401 (loop for var in vars
2402 for lvar in lvars
2403 collect (if (and (constant-lvar-p lvar)
2404 (proper-sequence-p (lvar-value lvar))
2405 (not (typep (lvar-value lvar) type)))
2406 `',(coerce (lvar-value lvar) type)
2407 var))))
2409 (cond ((type= type (specifier-type 'list))
2410 (let ((vars (make-gensym-list (length lvars))))
2411 `(lambda (type ,@vars)
2412 (declare (ignore type)
2413 (ignorable ,@vars))
2414 (%concatenate-to-list ,@(coerce-constants vars 'list)))))
2415 ((not vector-widetag)
2416 (give-up-ir1-transform))
2417 ((= vector-widetag sb-vm:simple-base-string-widetag)
2418 (string-concatenate-transform node 'simple-base-string lvars))
2419 #+sb-unicode
2420 ((= vector-widetag sb-vm:simple-character-string-widetag)
2421 (string-concatenate-transform node 'string lvars))
2422 ;; FIXME: other vectors may use inlined expansion from
2423 ;; STRING-CONCATENATE-TRANSFORM as well.
2425 (let ((vars (make-gensym-list (length lvars))))
2426 `(lambda (type ,@vars)
2427 (declare (ignore type)
2428 (ignorable ,@vars))
2429 ,(if (= vector-widetag sb-vm:simple-vector-widetag)
2430 `(%concatenate-to-simple-vector
2431 ,@(coerce-constants vars 'vector))
2432 `(%concatenate-to-vector
2433 ,vector-widetag ,@(coerce-constants vars 'list))))))))))
2435 ;;;; CONS accessor DERIVE-TYPE optimizers
2437 (defoptimizer (car derive-type) ((cons))
2438 ;; This and CDR needs to use LVAR-CONSERVATIVE-TYPE because type inference
2439 ;; gets confused by things like (SETF CAR).
2440 (let ((type (lvar-conservative-type cons))
2441 (null-type (specifier-type 'null)))
2442 (cond ((eq type null-type)
2443 null-type)
2444 ((cons-type-p type)
2445 (cons-type-car-type type)))))
2447 (defoptimizer (cdr derive-type) ((cons))
2448 (let ((type (lvar-conservative-type cons))
2449 (null-type (specifier-type 'null)))
2450 (cond ((eq type null-type)
2451 null-type)
2452 ((cons-type-p type)
2453 (cons-type-cdr-type type)))))
2455 ;;;; FIND, POSITION, and their -IF and -IF-NOT variants
2457 ;;; We want to make sure that %FIND-POSITION is inline-expanded into
2458 ;;; %FIND-POSITION-IF only when %FIND-POSITION-IF has an inline
2459 ;;; expansion, so we factor out the condition into this function.
2460 (defun check-inlineability-of-find-position-if (sequence from-end)
2461 (let ((ctype (lvar-type sequence)))
2462 (cond ((csubtypep ctype (specifier-type 'vector))
2463 ;; It's not worth trying to inline vector code unless we
2464 ;; know a fair amount about it at compile time.
2465 (upgraded-element-type-specifier-or-give-up sequence)
2466 (unless (constant-lvar-p from-end)
2467 (give-up-ir1-transform
2468 "FROM-END argument value not known at compile time")))
2469 ((csubtypep ctype (specifier-type 'list))
2470 ;; Inlining on lists is generally worthwhile.
2473 (give-up-ir1-transform
2474 "sequence type not known at compile time")))))
2476 ;;; %FIND-POSITION-IF and %FIND-POSITION-IF-NOT for LIST data
2477 (defun %find/position-if-list-expansion (sense from-end start end node)
2478 (declare (ignore from-end))
2479 ;; Circularity detection slows things down. It is permissible not to.
2480 ;; In fact, FIND is given as an archetypal example of a function that
2481 ;; "should be prepared to signal an error" but might not [CLHS 1.4.2].
2482 ;; We relax the definition of "safe" from safety=3 to >=2.
2483 (let ((safe (policy node (>= safety 2)))
2484 ;; The secondary value is inconsequential when flowing into a non-MV
2485 ;; combination, so we avoid counting loop iterations if possible.
2486 ;; This is limited in power, but good enough, for want of a proper
2487 ;; dead-code-elimination phase of the compiler.
2488 (indexed
2489 (not (and (lvar-single-value-p (node-lvar node))
2490 (constant-lvar-p start)
2491 (eql (lvar-value start) 0)
2492 (lvar-value-is end nil)))))
2493 `(let ((find nil)
2494 (position nil))
2495 (flet ((bounds-error ()
2496 (sequence-bounding-indices-bad-error sequence start end)))
2497 (if (and end (> start end))
2498 (bounds-error)
2499 (do ((slow sequence (cdr slow))
2500 ,@(when safe '((fast (cdr sequence) (cddr fast))))
2501 ,@(when indexed '((index 0 (+ index 1)))))
2502 ((cond ((null slow)
2503 (,@(if indexed
2504 '(if (and end (> end index)) (bounds-error))
2505 '(progn))
2506 (return (values find position))))
2507 ,@(when indexed
2508 '(((and end (>= index end))
2509 (return (values find position)))))
2510 ,@(when safe
2511 '(((eq slow fast)
2512 (circular-list-error sequence)))))
2513 (sb-impl::unreachable))
2514 (declare (list slow ,@(and safe '(fast)))
2515 ;; If you have as many as INDEX conses on a 32-bit build,
2516 ;; then you've either used up 4GB of memory (impossible)
2517 ;; or you're stuck in a circular list in unsafe code.
2518 ;; Correspondingly larger limit for 64-bit.
2519 ,@(and indexed '((index index))))
2520 (,@(if indexed '(when (>= index start)) '(progn))
2521 (let ((element (car slow)))
2522 ;; This hack of dealing with non-NIL FROM-END for list data
2523 ;; by iterating forward through the list and keeping track of
2524 ;; the last time we found a match might be more screwy than
2525 ;; what the user expects, but it seems to be allowed by the
2526 ;; ANSI standard. (And if the user is screwy enough to ask
2527 ;; for FROM-END behavior on list data, turnabout is fair play.)
2529 ;; It's also not enormously efficient, calling PREDICATE
2530 ;; and KEY more often than necessary; but all the alternatives
2531 ;; seem to have their own efficiency problems.
2532 (,sense (funcall predicate (funcall key element))
2533 (if from-end
2534 (setf find element position ,(and indexed 'index))
2535 (return (values element ,(and indexed 'index)))))))))))))
2537 (macrolet ((def (name condition)
2538 `(deftransform ,name ((predicate sequence from-end start end key)
2539 (function list t t t function)
2541 :node node
2542 :policy (> speed space))
2543 "expand inline"
2544 (%find/position-if-list-expansion ',condition
2545 from-end start end node))))
2546 (def %find-position-if when)
2547 (def %find-position-if-not unless))
2549 (defun sequence-element-type (sequence key)
2550 (let ((key-return-type *universal-type*))
2551 (when key
2552 (multiple-value-bind (type name) (lvar-fun-type key)
2553 (cond ((eq name 'identity)
2554 (setf key nil))
2556 (setf key-return-type (if (fun-type-p type)
2557 (single-value-type (fun-type-returns type))
2558 *universal-type*))
2559 (if (constant-fold-arg-p name)
2560 (setf key name)
2561 (return-from sequence-element-type key-return-type))))))
2562 (let ((type (sequence-elements-type sequence key)))
2563 (if (or (eq type *universal-type*)
2564 (eq type *wild-type*))
2565 key-return-type
2566 type))))
2568 (deftransform %find-position ((item sequence from-end start end key test))
2569 (let* ((test (lvar-fun-is test '(eql equal equalp char-equal)))
2570 (test-origin test))
2571 (when test
2572 (setf test (change-test-based-on-item test (lvar-type item)))
2573 (unless (eq test 'eq)
2574 (let ((elt (sequence-element-type sequence key)))
2575 (setf test (change-test-based-on-item test elt))
2576 (when (and (eq test 'equalp)
2577 (csubtypep (lvar-type item) (specifier-type 'integer))
2578 (csubtypep elt (specifier-type 'integer)))
2579 (setf test (if (or (csubtypep (lvar-type item) (specifier-type 'fixnum))
2580 (csubtypep elt (specifier-type 'fixnum)))
2582 'eql))))))
2583 (if (eq test test-origin)
2584 (give-up-ir1-transform)
2585 `(%find-position item sequence from-end start end key #',test))))
2587 ;;; %FIND-POSITION for LIST data can be expanded into %FIND-POSITION-IF
2588 ;;; without loss of efficiency. (I.e., the optimizer should be able
2589 ;;; to straighten everything out.)
2590 (deftransform %find-position ((item sequence from-end start end key test)
2591 (t list t t t t t)
2593 :policy (> speed space))
2594 "expand inline"
2595 '(%find-position-if (let ((test-fun (%coerce-callable-to-fun test)))
2596 ;; The order of arguments for asymmetric tests
2597 ;; (e.g. #'<, as opposed to order-independent
2598 ;; tests like #'=) is specified in the spec
2599 ;; section 17.2.1 -- the O/Zi stuff there.
2600 (lambda (i)
2601 (funcall test-fun item i)))
2602 sequence
2603 from-end
2604 start
2606 (%coerce-callable-to-fun key)))
2608 ;;; The inline expansions for the VECTOR case are saved as macros so
2609 ;;; that we can share them between the DEFTRANSFORMs and the default
2610 ;;; cases in the DEFUNs. (This isn't needed for the LIST case, because
2611 ;;; the DEFTRANSFORMs for LIST are less choosy about when to expand.)
2612 (defun %find-position-or-find-position-if-vector-expansion (sequence-arg
2613 from-end
2614 start
2615 end-arg
2616 element
2617 done-p-expr)
2618 (with-unique-names (offset block index n-sequence sequence end)
2619 (let ((maybe-return
2620 ;; WITH-ARRAY-DATA has already performed bounds
2621 ;; checking, so we can safely elide the checks
2622 ;; in the inner loop.
2623 `(let ((,element (locally (declare (optimize (insert-array-bounds-checks 0)))
2624 (aref ,sequence ,index))))
2625 (when ,done-p-expr
2626 (return-from ,block
2627 (values ,element
2628 (- ,index ,offset)))))))
2629 `(let* ((,n-sequence ,sequence-arg))
2630 (with-array-data ((,sequence ,n-sequence :offset-var ,offset)
2631 (,start ,start)
2632 (,end ,end-arg)
2633 :check-fill-pointer t)
2634 (block ,block
2635 (if ,from-end
2636 (loop for ,index
2637 ;; (If we aren't fastidious about declaring that
2638 ;; INDEX might be -1, then (FIND 1 #() :FROM-END T)
2639 ;; can send us off into never-never land, since
2640 ;; INDEX is initialized to -1.)
2641 of-type index-or-minus-1
2642 from (1- ,end) downto ,start
2644 ,maybe-return)
2645 (loop for ,index of-type index from ,start below ,end
2647 ,maybe-return))
2648 (values nil nil)))))))
2650 (sb-xc:defmacro %find-position-vector-macro (item sequence
2651 from-end start end key test)
2652 (with-unique-names (element)
2653 (%find-position-or-find-position-if-vector-expansion
2654 sequence
2655 from-end
2656 start
2658 element
2659 ;; (See the LIST transform for a discussion of the correct
2660 ;; argument order, i.e. whether the searched-for ,ITEM goes before
2661 ;; or after the checked sequence element.)
2662 `(funcall ,test ,item (funcall ,key ,element)))))
2664 (sb-xc:defmacro %find-position-if-vector-macro (predicate sequence
2665 from-end start end key)
2666 (with-unique-names (element)
2667 (%find-position-or-find-position-if-vector-expansion
2668 sequence
2669 from-end
2670 start
2672 element
2673 `(funcall ,predicate (funcall ,key ,element)))))
2675 (sb-xc:defmacro %find-position-if-not-vector-macro (predicate sequence
2676 from-end start end key)
2677 (with-unique-names (element)
2678 (%find-position-or-find-position-if-vector-expansion
2679 sequence
2680 from-end
2681 start
2683 element
2684 `(not (funcall ,predicate (funcall ,key ,element))))))
2686 ;;; %FIND-POSITION, %FIND-POSITION-IF and %FIND-POSITION-IF-NOT for
2687 ;;; VECTOR data
2688 (deftransform %find-position-if ((predicate sequence from-end start end key)
2689 (function vector t t t function)
2691 :policy (> speed space))
2692 "expand inline"
2693 (check-inlineability-of-find-position-if sequence from-end)
2694 '(%find-position-if-vector-macro predicate sequence
2695 from-end start end key))
2697 (deftransform %find-position-if-not ((predicate sequence from-end start end key)
2698 (function vector t t t function)
2700 :policy (> speed space))
2701 "expand inline"
2702 (check-inlineability-of-find-position-if sequence from-end)
2703 '(%find-position-if-not-vector-macro predicate sequence
2704 from-end start end key))
2706 (deftransform %find-position ((item sequence from-end start end key test)
2707 (t vector t t t function function)
2709 :node node)
2710 "expand inline"
2711 (check-inlineability-of-find-position-if sequence from-end)
2712 (unless
2713 (or (policy node (> speed space))
2714 ;; These have compact inline expansion
2715 (and (or (not key)
2716 (lvar-fun-is key '(identity)))
2717 (and (constant-lvar-p start)
2718 (eql (lvar-value start) 0))
2719 (and (constant-lvar-p end)
2720 (null (lvar-value end)))
2721 (csubtypep (lvar-type sequence) (specifier-type 'simple-array))
2722 (let ((element-type (array-type-upgraded-element-type (lvar-type sequence)))
2723 (test (lvar-fun-name* test))
2724 (item (lvar-type item)))
2725 (when (neq element-type *wild-type*)
2726 (case (type-specifier element-type)
2727 ((double-float single-float)
2728 (and (csubtypep item element-type)
2729 (memq test '(= eql equal equalp))))
2730 ((t)
2731 (eq test 'eq))
2732 (character
2733 (or (memq test '(eq eql equal char=))
2734 (and (eq test 'char-equal)
2735 (or (csubtypep item (specifier-type 'base-char))
2736 (and (constant-lvar-p sequence)
2737 (every (lambda (x) (typep x 'base-char))
2738 (lvar-value sequence)))))))
2739 (base-char
2740 (memq test '(eq eql equal char= char-equal)))
2742 (and (csubtypep element-type (specifier-type 'integer))
2743 (csubtypep item element-type)
2744 (memq test '(eq eql equal equalp =)))))))))
2745 (give-up-ir1-transform))
2746 ;; Delay to prefer the string and bit-vector transforms
2747 (delay-ir1-transform node :constraint)
2748 '(%find-position-vector-macro item sequence
2749 from-end start end key test))
2751 (deftransform %find-position ((item sequence from-end start end key test)
2752 (t bit-vector t t t t t)
2753 * :node node)
2754 (when (and test (lvar-fun-is test '(eq eql equal)))
2755 (setf test nil))
2756 (when (and key (lvar-fun-is key '(identity)))
2757 (setf key nil))
2758 (when (or test key)
2759 (give-up-ir1-transform "non-trivial :KEY or :TEST"))
2760 (block not-a-bit
2761 `(with-array-data ((bits sequence :offset-var offset)
2762 (start start)
2763 (end end)
2764 :check-fill-pointer t)
2765 (let ((p ,(let* ((dir (cond ((not (constant-lvar-p from-end)) 0) ; unknown
2766 ((lvar-value from-end) 2) ; reverse
2767 (t 1))) ; forward
2768 (from-end-arg (if (eql dir 0) '(from-end) '())))
2769 (if (constant-lvar-p item)
2770 (case (lvar-value item)
2771 (0 `(,(elt #(%bit-position/0 %bit-pos-fwd/0 %bit-pos-rev/0) dir)
2772 bits ,@from-end-arg start end))
2773 (1 `(,(elt #(%bit-position/1 %bit-pos-fwd/1 %bit-pos-rev/1) dir)
2774 bits ,@from-end-arg start end))
2775 (otherwise (return-from not-a-bit `(values nil nil))))
2776 `(,(elt #(%bit-position %bit-pos-fwd %bit-pos-rev) dir)
2777 item bits ,@from-end-arg start end)))))
2778 (if p
2779 (values item (the index (- (truly-the index p) offset)))
2780 (values nil nil))))))
2782 (deftransform %find-position ((item sequence from-end start end key test)
2783 (character string t t t function function)
2785 :policy (> speed space))
2786 (if (eq '* (upgraded-element-type-specifier sequence))
2787 (let ((form
2788 `(sb-impl::string-dispatch ((simple-array character (*))
2789 (simple-array base-char (*)))
2790 sequence
2791 (%find-position item sequence from-end start end key test))))
2792 (if (csubtypep (lvar-type sequence) (specifier-type 'simple-string))
2793 form
2794 ;; Otherwise we'd get three instances of WITH-ARRAY-DATA from
2795 ;; %FIND-POSITION.
2796 `(with-array-data ((sequence sequence :offset-var offset)
2797 (start start)
2798 (end end)
2799 :check-fill-pointer t)
2800 (multiple-value-bind (elt index) ,form
2801 (values elt (when (fixnump index) (- index offset)))))))
2802 ;; The type is known exactly, other transforms will take care of it.
2803 (give-up-ir1-transform)))
2805 ;;; logic to unravel :TEST, :TEST-NOT, and :KEY options in FIND,
2806 ;;; POSITION-IF, etc.
2807 (define-source-transform effective-find-position-test (test test-not)
2808 (once-only ((test test)
2809 (test-not test-not))
2810 `(cond
2811 ((and ,test ,test-not)
2812 (error "can't specify both :TEST and :TEST-NOT"))
2813 (,test (%coerce-callable-to-fun ,test))
2814 (,test-not
2815 ;; (Without DYNAMIC-EXTENT, this is potentially horribly
2816 ;; inefficient, but since the TEST-NOT option is deprecated
2817 ;; anyway, we don't care.)
2818 (complement (%coerce-callable-to-fun ,test-not)))
2819 ;; :TEST of NIL (whether implicit or explicit) means #'EQL.
2820 ;; This behavior is not specified by CLHS, but is fairly conventional.
2821 ;; (KEY is expressly specified as allowing NIL, but TEST is not)
2822 ;; In our implementation, it has to be this way because we don't track
2823 ;; whether the :TEST and :TEST-NOT args were actually present.
2824 (t #'eql))))
2825 (define-source-transform effective-find-position-key (key)
2826 (once-only ((key key))
2827 `(if ,key
2828 (%coerce-callable-to-fun ,key)
2829 #'identity)))
2831 (defun note-perfect-hash-used (description expr)
2832 (declare (ignorable description))
2833 #+nil
2834 (let ((*print-pretty* t) (*print-right-margin* 200)
2835 (*print-lines* nil) (*print-level* nil) (*print-length* nil))
2836 (format t "~&;; NOTE: ~A~%-> ~A~%" description expr))
2837 expr)
2839 ;;; Construct a form which computes a 32-bit hash given an object in ITEM (which
2840 ;;; customarily is named literally 'ITEM) whose values should be - but might not be -
2841 ;;; one of the objects in KEYS. If it is not, the expression's result should be
2842 ;;; irrelevant. (Calling code has to do some kind of "hit" test)
2843 ;;; The 32-bit hash is then fed into a perfect hash expression.
2844 ;;; TODO:
2845 ;;; 1. There is potential for more optimization.
2846 ;;; For example, let's say the key set includes only symbols and characters.
2847 ;;; Clearly we have to call SYMBOLP or some variant thereof prior to dereferencing
2848 ;;; the HASH slot of a symbol. For non-symbols, it doesn't really matter if the
2849 ;;; item is a character, so we could use (ASH (GET-LISP-OBJ-ADDRESS OBJ) -32)
2850 ;;; instead of doing CHARACTERP and CHAR-CODE. They come out the same, and for
2851 ;;; non-characters it doesn't matter what the result is.
2852 ;;; 2. this should probably take a ":MISS" argument which is a block name to return
2853 ;;; from if the key type doesn't match any of the accepted types
2854 ;;; rather than returning 0.
2855 (defun prehash-for-perfect-hash (item keys)
2856 (let (symbolp fixnump characterp)
2857 (dolist (key keys)
2858 (cond ((symbolp key) (setq symbolp t))
2859 ((fixnump key) (setq fixnump t))
2860 ((characterp key) (setq characterp t))))
2861 (collect ((calc))
2862 (when symbolp
2863 (if (vop-existsp :translate hash-as-if-symbol-name)
2864 (calc '((pointerp item)
2865 (hash-as-if-symbol-name item)))
2866 ;; NON-NULL-SYMBOL-P is the less expensive test as it omits the OR
2867 ;; which accepts NIL along with OTHER-POINTER objects.
2868 (calc `((,(if (member nil keys) 'symbolp 'non-null-symbol-p) item)
2869 (symbol-name-hash (truly-the symbol item))))))
2870 (when fixnump
2871 (calc '((fixnump item) (ldb (byte 32 0) (truly-the fixnum item)))))
2872 (when characterp
2873 (calc '((characterp item) (char-code (truly-the character item)))))
2874 (let ((calc `(cond ,@(calc) (t 0))))
2875 (if (eq item 'item) calc (subst item 'item calc))))))
2877 ;;; This tries to optimize for MEMBER directed to an IF node by not using a value vector.
2878 ;;; FIND directed to an IF is a little funny because if you find a NIL then it has to
2879 ;;; return NIL; but FIND does not use a value vector anyway, so there is nothing gained
2880 ;;; by avoiding a value vector.
2881 ;;; This can optimize out one CAR or CDR operation in CDR of ASSOC or CAR of ASSOC,
2882 ;;; but (TODO) it can't completely optimize out CADR in (CADR (ASSOC x '((:s1 val1) ...)))
2883 ;;; enough though it should be equivalent to (CAR (ASSOC x '((:s1 . val1) ...))).
2884 (defun try-perfect-find/position-map (fun-name conditional lvar-type items from-end node)
2885 (declare (type (member find position member assoc rassoc) fun-name))
2886 ;; It's certainly not worth doing a hash calculation for 2 keys.
2887 ;; And it's usually not worth it for 3 keys. At least for the MEMBER operation, the code size
2888 ;; is not smaller using a hash, and there are still 3 conditional jumps: one to test whether
2889 ;; the arg is POINTERP, one to see if the perfect hash is 0..2, and one to see if there was a
2890 ;; hit in the key vector. Straightforwardly testing takes 3 jumps, so just do that.
2891 (when (< (length items) (if (eq fun-name 'member) 4 3))
2892 (return-from try-perfect-find/position-map))
2893 (let ((hashable
2894 ;; TODO: allow (OR CHARACTER FIXNUM) also
2895 (every (lambda (item)
2896 (case fun-name
2897 (assoc (and (listp item)
2898 (symbolp (car item))))
2899 (rassoc (and (listp item)
2900 (symbolp (cdr item))))
2901 (t (symbolp item))))
2902 items)))
2903 (unless hashable
2904 (return-from try-perfect-find/position-map)))
2905 ;; alists can contain NIL which does not represent a pair at all.
2906 ;; (Why is such a seemingly random stipulation even part of the language?)
2907 (when (member fun-name '(assoc rassoc))
2908 (setf items (remove-if #'null items)))
2909 (let ((alistp) ; T if an alist, :SYNTHETIC if we avoid using conses in the mapping
2910 (map (make-hash-table)))
2911 ;; Optimize out the CDR operation in (CDR (ASSOC ...)) respectively
2912 ;; the CAR in (CAR (RASSOC ...)).
2913 ;; CADR and SECOND would have been converted as (CAR (CDR ...)
2914 ;; so it works for those also.
2915 (when (member fun-name '(assoc rassoc))
2916 (setq alistp t)
2917 (let ((expect (if (eq fun-name 'assoc) '(cdr) '(car)))
2918 (dest (node-dest node)))
2919 (when (and (combination-p dest)
2920 (lvar-fun-is (combination-fun dest) expect)
2921 (let* ((args (combination-args dest)) (arg (first args)))
2922 (and (singleton-p args)
2923 (lvar-has-single-use-p arg)
2924 (eq (lvar-use arg) node))))
2925 (setq alistp :synthetic))))
2926 (cond ((vectorp items)
2927 (dotimes (position (length items))
2928 (let ((elt (svref items position)))
2929 ;; FROM-END will replace an entry already in MAP, as doing so exhibits
2930 ;; the desired behavior of using the rightmost match.
2931 ;; Otherwise, when *not* FROM-END, take only the leftmost occurrence.
2932 (when (or from-end (not (gethash elt map)))
2933 (setf (gethash elt map) position)))))
2935 (aver (not from-end))
2936 (do ((list items (cdr list)))
2937 ((endp list))
2938 (ecase fun-name
2939 (member
2940 (let ((elt (car list)))
2941 (unless (gethash elt map) (setf (gethash elt map) list))))
2942 (assoc
2943 (let* ((pair (car list)) (key (car pair)))
2944 (unless (gethash key map)
2945 (setf (gethash key map) (if (eq alistp t) pair (cdr pair))))))
2946 (rassoc
2947 (let* ((pair (car list)) (key (cdr pair)))
2948 (unless (gethash key map)
2949 (setf (gethash key map) (if (eq alistp t) pair (car pair))))))))))
2950 (flet () ; XXX: reindent from here down
2951 ;; Sort to avoid sensitivity to the hash-table iteration order when cross-compiling.
2952 ;; Not necessary for the target but not worth a #+/- either.
2953 ;; TODO: rather than sorting, compute KEYS from the originally-specified ITEMS after
2954 ;; removing duplicates. If we permit keys to be (OR CHARACTER SYMBOL FIXNUM)
2955 ;; there is not really a good sort order on a mixture of those, though I suppose
2956 ;; we could sort by the hash, since that has to be unique or the transform fails.
2957 (binding* ((keys (sort (loop for k being each hash-key of map collect k) #'string<))
2958 (hashes (map '(simple-array (unsigned-byte 32) (*)) #'symbol-name-hash keys))
2959 (n (length hashes))
2960 (certainp (csubtypep lvar-type (specifier-type `(member ,@keys))))
2961 (pow2size (power-of-two-ceiling n))
2962 ;; FIXME: I messed up the minimal/non-minimal thing that was
2963 ;; trying to simplify the calculation at the expense of a few extra cells.
2964 ;; Minimal will always be right.
2965 (minimal t)
2966 (lambda (make-perfect-hash-lambda hashes items minimal) :exit-if-null)
2967 (keyspace-size (if minimal n pow2size))
2968 (domain (sb-xc:make-array keyspace-size :initial-element 0))
2969 (range
2970 (cond ((eq fun-name 'position)
2971 (sb-xc:make-array keyspace-size
2972 :element-type
2973 (cond ((<= n #x100) '(unsigned-byte 8))
2974 ((<= n #x10000) '(unsigned-byte 16))
2975 (t '(unsigned-byte 32)))
2976 :initial-element 0))
2977 ((or conditional (eq fun-name 'find)) nil)
2978 ;; if ALISTP=T then use a single array of cons cells,
2979 ;; which the user wants (or seems to)
2980 ((eq alistp t) domain)
2981 (t (sb-xc:make-array keyspace-size))))
2982 (phashfun (sb-c::compile-perfect-hash lambda hashes)))
2983 (when certainp
2984 (when conditional
2985 (aver (eq fun-name 'member)) ; return whatever expression CONDITIONAL is
2986 (return-from try-perfect-find/position-map conditional))
2987 (when (eq fun-name 'find) ; nothing to do. Wasted some time, no big deal
2988 (return-from try-perfect-find/position-map 'item))) ; transform arg is always named ITEM
2989 (maphash (lambda (key val &aux (phash (funcall phashfun (symbol-name-hash key))))
2990 (cond ((eq alistp t)
2991 (setf (aref domain phash) val)) ; VAL is the (key . val) pair
2993 (setf (svref domain phash) key)
2994 (when range (setf (aref range phash) val)))))
2995 map)
2996 (when (eq alistp :synthetic)
2997 (let* ((car/cdr (node-dest node))
2998 (fun (lvar-use (combination-fun car/cdr))))
2999 (aver (ref-p fun))
3000 (when (every #'fixnump range)
3001 (setq range (coerce-to-smallest-eltype range)))
3002 (change-ref-leaf fun (find-free-fun 'values "?") :recklessly t)
3003 (setf (combination-fun-info car/cdr) (info :function :info 'values))
3004 ;; This is cargo-culted from a related transform on MEMBER where we cause it to
3005 ;; return a value that is not based on the input list directly.
3006 (derive-node-type node (specifier-type 't) :from-scratch t)
3007 (reoptimize-node car/cdr)))
3008 ;; TRULY-THE around PHASH is warranted when CERTAINP because while the compiler can
3009 ;; derive the type of the final LOGAND, it's a complete mystery to it that the range
3010 ;; of the perfect hash is smaller than 2^N.
3011 (note-perfect-hash-used
3012 `(,fun-name ,conditional ,items)
3013 `(let* ((hash ,(prehash-for-perfect-hash 'item keys))
3014 (phash (,lambda hash)))
3015 ,(if certainp
3016 `(aref ,range (truly-the (mod ,n) phash))
3017 (let* ((key-expr (if (eq alistp t)
3018 `(,(if (eq fun-name 'assoc) 'car 'cdr) key)
3019 'key))
3020 (expr `(let ((key (svref ,domain phash)))
3021 (if (eq ,key-expr item)
3022 ,(cond (conditional) ; return whatever this expression is
3023 ((eq fun-name 'find) 'item)
3024 ((eq range domain)
3025 'key)
3027 `(aref ,range phash)))))))
3028 ;; An unexpected symbol-hash fed into a minimal perfect hash function
3029 ;; can produce garbage out, so we have to bounds-check it.
3030 ;; Otherwise, with a non-minimal hash function, the table size is
3031 ;; exactly right for the number of bits of output of the function
3032 (if minimal
3033 `(if (< phash ,n)
3034 ,expr)
3035 expr)))))))))
3037 (macrolet ((define-find-position (fun-name values-index)
3038 `(deftransform ,fun-name ((item sequence &key
3039 from-end (start 0) end
3040 key test test-not)
3041 (t (or list vector) &rest t))
3042 (when (and (constant-lvar-p sequence)
3043 (or (proper-sequence-p (lvar-value sequence))
3044 (give-up-ir1-transform))
3045 (zerop (length (lvar-value sequence))))
3046 (if (and test test-not)
3047 ;; even though one kwd arg could legit be NIL, it's not interesting.
3048 (give-up-ir1-transform)
3049 (return-from ,fun-name
3050 '(lambda (&rest args) (declare (ignore args)) nil))))
3051 (let ((effective-test
3052 (unless test-not
3053 (if test (lvar-fun-name* test) 'eql)))
3054 (test-form '(effective-find-position-test test test-not))
3055 (const-seq (when (constant-lvar-p sequence)
3056 (lvar-value sequence))))
3057 ;; Destructive modification of constants is illegal.
3058 ;; Therefore if this sequence would have been output as a code header
3059 ;; constant, its contents can't change. We don't need to reference
3060 ;; the sequence itself to compare elements.
3061 ;; There are two transforms to try in this situation:
3062 ;; 1) If we can make a perfect map of N symbols, then do that. No upper bound
3063 ;; on N. This could be enhanced to take fixnums and characters- any objects for
3064 ;; which the hash values are computable at compile-time.
3065 ;; 2) Otherwise, use COND, not to exceed some length limit.
3066 (when (and const-seq
3067 (member effective-test '(eql eq char= char-equal))
3068 (not start) (not end) (not key)
3069 (or (not from-end) (constant-lvar-p from-end)))
3070 (let* ((items (coerce const-seq 'simple-vector))
3071 ;; It seems silly to use :from-end and a constant list
3072 ;; in a way where it actually matters (with repeated elements),
3073 ;; but we either have to do it right or not do it.
3074 (reversedp (and from-end (lvar-value from-end)))
3075 (or-eq-transform-p (and (memq effective-test '(eql eq char=))
3076 (or-eq-transform-p items))))
3077 (awhen (and (memq effective-test '(eql eq))
3078 (not or-eq-transform-p)
3079 (try-perfect-find/position-map
3080 ',fun-name nil (lvar-type item) items reversedp nil))
3081 (return-from ,fun-name
3082 `(lambda (item sequence &rest rest)
3083 (declare (ignore sequence rest))
3084 ,it)))
3085 (when (or or-eq-transform-p
3086 (<= (length items) 10))
3087 (let ((clauses (loop for x across items for i from 0
3088 ;; Later transforms will change EQL to EQ if appropriate.
3089 collect `((,effective-test item ',x)
3090 ,(ecase ',fun-name
3091 (position i)
3092 (find
3093 (cond
3094 ((memq effective-test '(eq char=))
3095 'item)
3096 ((and (eq effective-test 'eql)
3097 (sb-xc:typep x 'eq-comparable-type))
3098 'item)
3099 ((and (eq effective-test 'char-equal)
3100 (if (characterp x)
3101 (not (both-case-p x))
3102 (give-up-ir1-transform)))
3103 'item)
3105 `',x))))))))
3106 (return-from ,fun-name
3107 `(lambda (item sequence &rest rest)
3108 (declare (ignore sequence rest))
3109 (cond ,@(if reversedp (nreverse clauses) clauses))))))))
3110 `(nth-value ,',values-index
3111 (%find-position item sequence
3112 from-end start
3114 (effective-find-position-key key)
3115 ,test-form))))))
3116 (define-find-position find 0)
3117 (define-find-position position 1))
3119 ;;; Lower :test
3120 (macrolet ((def (fun-name)
3121 `(deftransform ,fun-name ((item sequence &key
3122 from-end start end
3123 key test test-not)
3124 (t &rest t))
3125 (macrolet ((maybe-arg (arg &optional (key (keywordicate arg)))
3126 `(and ,arg `(,,key ,',arg))))
3127 (let ((test (and (not test-not)
3128 (change-test-lvar-based-on-item test item))))
3129 (if test
3130 `(,',fun-name item sequence :test ',test
3131 ,@(maybe-arg from-end)
3132 ,@(maybe-arg start)
3133 ,@(maybe-arg end)
3134 ,@(maybe-arg key)
3135 ,@(maybe-arg test-not))
3136 (give-up-ir1-transform)))))))
3137 (def find)
3138 (def position))
3140 (macrolet ((define-find-position-if (fun-name values-index)
3141 `(deftransform ,fun-name ((predicate sequence &key
3142 from-end (start 0)
3143 end key)
3144 (t (or list vector) &rest t))
3145 '(nth-value
3146 ,values-index
3147 (%find-position-if (%coerce-callable-to-fun predicate)
3148 sequence from-end
3149 start end
3150 (effective-find-position-key key))))))
3151 (define-find-position-if find-if 0)
3152 (define-find-position-if position-if 1))
3154 ;;; the deprecated functions FIND-IF-NOT and POSITION-IF-NOT. We
3155 ;;; didn't bother to worry about optimizing them, except note that on
3156 ;;; Sat, Oct 06, 2001 at 04:22:38PM +0100, Christophe Rhodes wrote on
3157 ;;; sbcl-devel
3159 ;;; My understanding is that while the :test-not argument is
3160 ;;; deprecated in favour of :test (complement #'foo) because of
3161 ;;; semantic difficulties (what happens if both :test and :test-not
3162 ;;; are supplied, etc) the -if-not variants, while officially
3163 ;;; deprecated, would be undeprecated were X3J13 actually to produce
3164 ;;; a revised standard, as there are perfectly legitimate idiomatic
3165 ;;; reasons for allowing the -if-not versions equal status,
3166 ;;; particularly remove-if-not (== filter).
3168 ;;; This is only an informal understanding, I grant you, but
3169 ;;; perhaps it's worth optimizing the -if-not versions in the same
3170 ;;; way as the others?
3172 ;;; FIXME: Maybe remove uses of these deprecated functions within the
3173 ;;; implementation of SBCL.
3174 (macrolet ((define-find-position-if-not (fun-name values-index)
3175 `(deftransform ,fun-name ((predicate sequence &key
3176 from-end (start 0)
3177 end key)
3178 (t (or list vector) &rest t))
3179 '(nth-value
3180 ,values-index
3181 (%find-position-if-not (%coerce-callable-to-fun predicate)
3182 sequence from-end
3183 start end
3184 (effective-find-position-key key))))))
3185 (define-find-position-if-not find-if-not 0)
3186 (define-find-position-if-not position-if-not 1))
3188 (macrolet ((define-trimmer-transform (fun-name leftp rightp)
3189 `(deftransform ,fun-name ((char-bag string)
3190 (t simple-string))
3191 (let ((find-expr
3192 (if (constant-lvar-p char-bag)
3193 ;; If the bag is constant, use MEMBER
3194 ;; instead of FIND, since we have a
3195 ;; deftransform for MEMBER that can
3196 ;; open-code all of the comparisons when
3197 ;; the list is constant. -- JES, 2007-12-10
3198 `(not (member (schar string index)
3199 ',(coerce (lvar-value char-bag) 'list)
3200 :test #'char=))
3201 '(not (find (schar string index) char-bag :test #'char=)))))
3202 `(flet ((char-not-in-bag (index)
3203 ,find-expr))
3204 (let* ((end (length string))
3205 (left-end (if ,',leftp
3206 (do ((index 0 (1+ index)))
3207 ((or (= index (the fixnum end))
3208 (char-not-in-bag index))
3209 index)
3210 (declare (fixnum index)))
3212 (right-end (if ,',rightp
3213 (do ((index (1- end) (1- index)))
3214 ((or (< index left-end)
3215 (char-not-in-bag index))
3216 (1+ index))
3217 (declare (fixnum index)))
3218 end)))
3219 (if (and (eql left-end 0)
3220 (eql right-end (length string)))
3221 string
3222 (subseq string left-end right-end))))))))
3223 (define-trimmer-transform string-left-trim t nil)
3224 (define-trimmer-transform string-right-trim nil t)
3225 (define-trimmer-transform string-trim t t))
3229 ;;; Pop anonymous constant values from the end, list/list* them if
3230 ;;; any, and link the remainder with list* at runtime. We don't try to
3231 ;;; fold named constant references, because while theoretically
3232 ;;; possible, in addition to needing to make a load form for a
3233 ;;; structure recording the constant name which wraps the constant
3234 ;;; value, the dumper would have to learn how to patch constant values
3235 ;;; into list structure, to deal with the load form potentially being
3236 ;;; evaluated for value earlier than the constant definition is
3237 ;;; loaded.
3238 (defun transform-backq-list-or-list* (function values)
3239 (let ((gensyms (make-gensym-list (length values)))
3240 (reverse (reverse values))
3241 (constants '()))
3242 (loop while (and reverse
3243 (constant-lvar-p (car reverse))
3244 (legal-immediate-constant-p
3245 (nth-value 1 (lvar-value (car reverse)))))
3246 do (push (lvar-value (pop reverse)) constants))
3247 (if (null constants)
3248 `(lambda ,gensyms
3249 (,function ,@gensyms))
3250 (let ((tail (apply function constants)))
3251 (if (null reverse)
3252 `',tail
3253 (let* ((nvariants (length reverse))
3254 (variants (subseq gensyms 0 nvariants)))
3255 `(lambda ,gensyms
3256 (declare (ignore ,@(subseq gensyms nvariants)))
3257 ,(if tail
3258 `(list* ,@variants ',tail)
3259 `(list ,@variants)))))))))
3261 (deftransform sb-impl::|List| ((&rest elts))
3262 (transform-backq-list-or-list* 'list elts))
3264 (deftransform sb-impl::|List*| ((&rest elts))
3265 (transform-backq-list-or-list* 'list* elts))
3267 (deftransform sb-impl::|Vector| ((&rest elts))
3268 (let ((gensyms (make-gensym-list (length elts)))
3269 constants)
3270 ;; There's not much that can be done with semi-constant vectors-
3271 ;; either we're going to call VECTOR at compile-time or runtime.
3272 ;; There's little point to building up intermediate lists in the partially
3273 ;; constant case. There are ways to expand using MULTIPLE-VALUE-CALL that
3274 ;; might avoid consing intermediate lists if ,@ is involved
3275 ;; though I doubt it would provide benefit to many real-world scenarios.
3276 (dolist (elt elts)
3277 (cond ((and (constant-lvar-p elt)
3278 (legal-immediate-constant-p (nth-value 1 (lvar-value elt))))
3279 (push (lvar-value elt) constants))
3281 (setq constants :fail)
3282 (return))))
3283 `(lambda ,gensyms
3284 ,@(cond ((listp constants)
3285 `((declare (ignore ,@gensyms))
3286 ,(apply 'vector (nreverse constants))))
3288 `((vector ,@gensyms)))))))
3290 ;; Merge adjacent constant values
3291 (deftransform sb-impl::|Append| ((&rest elts))
3292 (let ((gensyms (make-gensym-list (length elts)))
3293 (acc nil)
3294 (ignored '())
3295 (arguments '()))
3296 (flet ((convert-accumulator ()
3297 (let ((constant (apply 'append (nreverse (shiftf acc nil)))))
3298 (when constant
3299 (push `',constant arguments)))))
3300 (loop for gensym in gensyms
3301 for (elt . next) on elts by #'cdr
3302 do (cond ((constant-lvar-p elt)
3303 (let ((elt (lvar-value elt)))
3304 (when (and next (not (proper-list-p elt)))
3305 (abort-ir1-transform
3306 "Non-list or improper list spliced in ~
3307 the middle of a backquoted list."))
3308 (push gensym ignored)
3309 (push elt acc)))
3311 (convert-accumulator)
3312 (push gensym arguments)))
3313 finally (convert-accumulator)))
3314 (let ((arguments (nreverse arguments)))
3315 `(lambda ,gensyms
3316 (declare (ignore ,@ignored))
3317 (append ,@arguments)))))
3319 (deftransform reverse ((sequence) (vector) * :important nil)
3320 `(sb-impl::vector-reverse sequence))
3322 (deftransform reverse ((sequence) (list) * :important nil)
3323 `(sb-impl::list-reverse sequence))
3325 (deftransform nreverse ((sequence) (vector) * :important nil)
3326 `(sb-impl::vector-nreverse sequence))
3328 (deftransform nreverse ((sequence) (list) * :important nil)
3329 `(sb-impl::list-nreverse sequence))
3331 (deftransforms (intersection nintersection)
3332 ((list1 list2 &key key test test-not))
3333 (let ((null-type (specifier-type 'null)))
3334 (cond ((or (csubtypep (lvar-type list1) null-type)
3335 (csubtypep (lvar-type list2) null-type))
3336 nil)
3337 ((and (same-leaf-ref-p list1 list2)
3338 (not test-not)
3339 (not key)
3340 (or (not test)
3341 (lvar-fun-is test '(eq eql equal equalp))))
3342 'list1)
3344 (give-up-ir1-transform)))))
3346 (deftransform nunion ((list1 list2 &key key test test-not))
3347 (let ((null-type (specifier-type 'null)))
3348 (cond ((csubtypep (lvar-type list1) null-type)
3349 'list2)
3350 ((csubtypep (lvar-type list2) null-type)
3351 'list1)
3352 ((and (same-leaf-ref-p list1 list2)
3353 (not test-not)
3354 (not key)
3355 (or (not test)
3356 (lvar-fun-is test '(eq eql equal equalp))))
3357 'list1)
3359 (give-up-ir1-transform)))))
3361 (deftransform union ((list1 list2 &key key test test-not))
3362 (let ((null-type (specifier-type 'null)))
3363 (flet ((to-adjoin (a b)
3364 (when (constant-lvar-p a)
3365 (let ((value (lvar-value a)))
3366 (when (typep value '(cons * null))
3367 `(adjoin ',(car value) ,b
3368 ,@(and test '(:test test))
3369 ,@(and test-not '(:test-not test-not))))))))
3370 (cond ((csubtypep (lvar-type list1) null-type)
3371 'list2)
3372 ((csubtypep (lvar-type list2) null-type)
3373 'list1)
3374 ((and (same-leaf-ref-p list1 list2)
3375 (not test-not)
3376 (not key)
3377 (or (not test)
3378 (lvar-fun-is test '(eq eql equal equalp))))
3379 'list1)
3380 ((and (not key)
3381 (or (to-adjoin list1 'list2)
3382 (to-adjoin list2 'list1))))
3384 (give-up-ir1-transform))))))
3386 (defoptimizer (union derive-type) ((list1 list2 &rest args))
3387 (let ((cons-type (specifier-type 'cons)))
3388 (if (or (csubtypep (lvar-type list1) cons-type)
3389 (csubtypep (lvar-type list2) cons-type))
3390 cons-type
3391 (specifier-type 'list))))
3393 (defoptimizer (nunion derive-type) ((list1 list2 &rest args))
3394 (let ((cons-type (specifier-type 'cons)))
3395 (if (or (csubtypep (lvar-type list1) cons-type)
3396 (csubtypep (lvar-type list2) cons-type))
3397 cons-type
3398 (specifier-type 'list))))
3400 (deftransforms (set-difference nset-difference)
3401 ((list1 list2 &key key test test-not))
3402 (let ((null-type (specifier-type 'null)))
3403 (cond ((csubtypep (lvar-type list1) null-type)
3404 nil)
3405 ((csubtypep (lvar-type list2) null-type)
3406 'list1)
3407 ((and (same-leaf-ref-p list1 list2)
3408 (not test-not)
3409 (not key)
3410 (or (not test)
3411 (lvar-fun-is test '(eq eql equal equalp))))
3412 nil)
3414 (give-up-ir1-transform)))))
3416 (deftransform subsetp ((list1 list2 &key key test test-not))
3417 (cond ((csubtypep (lvar-type list1) (specifier-type 'null))
3419 ((and (same-leaf-ref-p list1 list2)
3420 (not test-not)
3421 (not key)
3422 (or (not test)
3423 (lvar-fun-is test '(eq eql equal equalp))))
3426 (give-up-ir1-transform))))
3428 (deftransforms (set-exclusive-or nset-exclusive-or)
3429 ((list1 list2 &key key test test-not))
3430 (let ((null-type (specifier-type 'null)))
3431 (cond ((csubtypep (lvar-type list1) null-type)
3432 'list2)
3433 ((csubtypep (lvar-type list2) null-type)
3434 'list1)
3435 ((and (same-leaf-ref-p list1 list2)
3436 (not test-not)
3437 (not key)
3438 (or (not test)
3439 (lvar-fun-is test '(eq eql equal equalp))))
3440 'list1)
3442 (give-up-ir1-transform)))))
3444 (deftransform tree-equal ((list1 list2 &key test test-not))
3445 (cond ((and (same-leaf-ref-p list1 list2)
3446 (not test-not)
3447 (or (not test)
3448 (lvar-fun-is test '(eq eql equal equalp))))
3450 ((and (not test-not)
3451 (or (not test)
3452 (lvar-fun-is test '(eql))))
3453 `(sb-impl::tree-equal-eql list1 list2))
3455 (give-up-ir1-transform))))
3457 (defun vector-type-length (type)
3458 (catch 'give-up-ir1-transform
3459 (return-from
3460 vector-type-length
3461 (let* ((dim (array-type-dimensions-or-give-up type)))
3462 (when (and (typep dim '(cons integer null))
3463 (not (conservative-array-type-complexp type)))
3464 (first dim)))))
3465 nil)
3467 (defun vector-type-lengths (type)
3468 (if (union-type-p type)
3469 (loop with lengths
3470 for type in (union-type-types type)
3471 do (pushnew (or (vector-type-length type)
3472 (return))
3473 lengths)
3474 finally (return lengths))
3475 (let ((length (vector-type-length type)))
3476 (when length
3477 (list length)))))
3479 (defoptimizer (reduce derive-type) ((fun sequence
3480 &key
3481 initial-value
3483 start
3485 &allow-other-keys))
3486 (multiple-value-bind (fun-type name) (lvar-fun-type fun t t)
3487 (when (fun-type-p fun-type)
3488 (let* ((initial-value-type (and initial-value
3489 (lvar-type initial-value)))
3490 (sequence-type (lvar-type sequence))
3491 (element-type
3492 (cond ((and key
3493 (multiple-value-bind (key-type name) (lvar-fun-type key t t)
3494 (cond ((eq name 'identity)
3495 nil)
3496 ((fun-type-p key-type)
3497 (single-value-type (fun-type-returns key-type)))
3499 *universal-type*)))))
3500 ((csubtypep sequence-type (specifier-type 'array))
3501 (let ((upgraded-type
3502 (array-type-upgraded-element-type sequence-type)))
3503 (if (eq upgraded-type *wild-type*)
3504 *universal-type*
3505 upgraded-type)))))
3506 (end (if end
3507 (and (constant-lvar-p end)
3508 (or (lvar-value end)
3509 (vector-type-length sequence-type)))
3510 (vector-type-length sequence-type)))
3511 (start (if start
3512 (and (constant-lvar-p start)
3513 (lvar-value start))
3515 (length (and start end
3516 (- end start))))
3517 ;; Calling the type deriver would be more universal, but
3518 ;; type derivers expect a combination, but even then there's
3519 ;; not a lot of standard functions which are usually used
3520 ;; with REDUCE and which benefit from improved type
3521 ;; derivation.
3523 (when (and (eq name '+)
3524 element-type
3525 (neq element-type *wild-type*)
3526 (neq element-type *universal-type*))
3527 (let* ((non-empty (typep length '(integer 1)))
3528 (identity-p (and (not initial-value)
3529 (not non-empty))))
3530 (labels ((try (type)
3531 (let ((type (specifier-type type)))
3532 (when (csubtypep element-type type)
3533 (cond (identity-p
3534 (type-union type
3535 (specifier-type '(eql 0))))
3536 (initial-value
3537 (let ((contagion (numeric-contagion type initial-value-type
3538 :rational nil
3539 :unsigned t)))
3540 (if non-empty
3541 contagion
3542 (type-union contagion initial-value-type))))
3544 type))))))
3545 (some #'try '(double-float single-float float unsigned-byte integer rational real)))))
3546 (let ((fun-result (single-value-type (fun-type-returns fun-type))))
3547 (cond (initial-value-type
3548 (type-union initial-value-type fun-result))
3549 ((typep length '(integer 2))
3550 fun-result)
3551 (element-type
3552 (type-union fun-result element-type)))))))))
3554 (defoptimizer (nth derive-type) ((n list))
3555 (when (constant-lvar-p list)
3556 (let* ((list (lvar-value list))
3557 (rest list)
3558 type
3559 (seen (list list)))
3560 (loop for element = (pop rest)
3561 do (setf type
3562 (if type
3563 (type-union (ctype-of element) type)
3564 (ctype-of element)))
3565 until (or (memq rest seen)
3566 (atom rest))
3567 do (push rest seen)
3568 finally (unless (or rest
3569 (let ((n-int (type-approximate-interval (lvar-type n))))
3570 (and n-int
3571 (interval<n n-int (length list)))))
3572 (setf type (type-union (specifier-type 'null) type))))
3573 type)))
3575 (defoptimizer (car constraint-propagate-if) ((list))
3576 (values list (specifier-type 'cons) nil nil t))
3578 (setf (fun-info-constraint-propagate-if (fun-info-or-lose 'cdr))
3579 #'car-constraint-propagate-if-optimizer)