Signal floating-point-overflow from bignum-to-float.
[sbcl.git] / tests / compiler.pure.lisp
blobf02b84fa5c0b919232711e5d0f680e17b9727b83
1 ;;;; various compiler tests without side effects
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; While most of SBCL is derived from the CMU CL system, the test
7 ;;;; files (like this one) were written from scratch after the fork
8 ;;;; from CMU CL.
9 ;;;;
10 ;;;; This software is in the public domain and is provided with
11 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
14 (cl:in-package :cl-user)
16 (load "compiler-test-util.lisp")
18 ;; The tests in this file do not work under the legacy interpreter.
19 (when (and (eq sb-ext:*evaluator-mode* :interpret)
20 (not (member :sb-fasteval *features*)))
21 (invoke-restart 'run-tests::skip-file))
23 ;;; Exercise a compiler bug (by crashing the compiler).
24 ;;;
25 ;;; This test code is from Douglas Crosher's simplified TICKLE-BUG
26 ;;; (2000-09-06 on cmucl-imp).
27 ;;;
28 ;;; The bug was fixed by Douglas Crosher's patch, massaged for SBCL by
29 ;;; Martin Atzmueller (2000-09-13 on sbcl-devel).
30 (with-test (:name (:compiler-bug labels tagbody))
31 (checked-compile-and-assert ()
32 `(lambda ()
33 (labels ((fun1 ()
34 (fun2))
35 (fun2 ()
36 (when nil
37 (tagbody
38 tag
39 (fun2)
40 (go tag)))
41 (when nil
42 (tagbody
43 tag
44 (fun1)
45 (go tag)))))
46 (fun1)
47 nil))
48 (() nil)))
50 ;;; Exercise a compiler bug (by crashing the compiler).
51 ;;;
52 ;;; Tim Moore gave a patch for this bug in CMU CL 2000-05-24 on
53 ;;; cmucl-imp, and Martin Atzmueller applied it to SBCL.
54 (with-test (:name (:compiler-bug flet inline :undefined-function))
55 (multiple-value-bind (fun failure-p warnings style-warnings)
56 (checked-compile
57 `(lambda (x)
58 (or (integerp x)
59 (block used-by-some-y?
60 (flet ((frob (stk)
61 (dolist (y stk)
62 (unless (rejected? y)
63 (return-from used-by-some-y? t)))))
64 (declare (inline frob))
65 (frob (rstk x))
66 (frob (mrstk x)))
67 nil)))
68 :allow-style-warnings t)
69 (declare (ignore failure-p warnings))
70 (assert (= 3 (length style-warnings)))
71 (funcall fun 13)))
73 ;;; bug 112, reported by Martin Atzmueller 2001-06-25 (originally
74 ;;; from Bruno Haible in CMU CL bugs collection), fixed by
75 ;;; Alexey Dejneka 2002-01-27
76 (assert (= 1 ; (used to give 0 under bug 112)
77 (let ((x 0))
78 (declare (special x))
79 (let ((x 1))
80 (let ((y x))
81 (declare (special x)) y)))))
82 (assert (= 1 ; (used to give 1 even under bug 112, still works after fix)
83 (let ((x 0))
84 (declare (special x))
85 (let ((x 1))
86 (let ((y x) (x 5))
87 (declare (special x)) y)))))
89 ;;; another LET-related bug fixed by Alexey Dejneka at the same
90 ;;; time as bug 112
91 (with-test (:name (let :repeated-name :bug-112))
92 ;; Should complain about duplicate variable names in LET binding
93 (multiple-value-bind (fun failure-p)
94 (checked-compile `(lambda ()
95 (let (x
96 (x 1))
97 (list x)))
98 :allow-failure t)
99 (assert (functionp fun))
100 (assert failure-p)))
102 ;;; bug 169 (reported by Alexey Dejneka 2002-05-12, fixed by David
103 ;;; Lichteblau 2002-05-21)
104 (with-test (:name (let :earmuffs))
105 ;; Compiling this code should cause a STYLE-WARNING about *X*
106 ;; looking like a special variable but not being one.
107 (multiple-value-bind (fun failure-p warnings style-warnings)
108 (checked-compile
109 `(lambda (n)
110 (let ((*x* n))
111 (funcall (symbol-function 'x-getter))
112 (print *x*)))
113 :allow-style-warnings 'sb-kernel:asterisks-around-lexical-variable-name)
114 (declare (ignore failure-p warnings))
115 (assert (functionp fun))
116 (assert (= 1 (length style-warnings))))
117 ;; Compiling this code should not cause a warning (because the
118 ;; DECLARE turns *X* into a special variable as its name suggests it
119 ;; should be).
120 (checked-compile `(lambda (n)
121 (let ((*x* n))
122 (declare (special *x*))
123 (funcall (symbol-function 'x-getter))
124 (print *x*)))))
126 ;;; a bug in 0.7.4.11
127 (with-test (:name (compile typep satisfies))
128 (let ((*standard-output* (make-broadcast-stream)))
129 (funcall (checked-compile
130 '(lambda ()
131 (dolist (i '(a b 1 2 "x" "y"))
132 ;; In sbcl-0.7.4.11, the compiler tried to source-transform the
133 ;; TYPEP here but got confused and died, doing
134 ;; (ASSOC '(AND INTEGERP (SATISFIES PLUSP)))
135 ;; *BACKEND-TYPE-PREDICATES*
136 ;; :TEST #'TYPE=)
137 ;; and blowing up because TYPE= tried to call PLUSP on the
138 ;; characters of the MEMBER-TYPE representing STANDARD-CHAR.
139 (when (typep i '(and integer (satisfies oddp)))
140 (print i))))))
141 (funcall (checked-compile
142 '(lambda ()
143 (dotimes (i 14)
144 (when (typep i '(and integer (satisfies oddp)))
145 (print i))))))))
147 ;;; bug 156 (reported by APD sbcl-devel 2002-04-12, fixed by CSR patch
148 ;;; sbcl-devel 2002-07-02): FUNCTION-LAMBDA-EXPRESSION of
149 ;;; interactively-compiled functions was broken by sleaziness and
150 ;;; confusion in the assault on 0.7.0, so this expression used to
151 ;;; signal TYPE-ERROR when it found NIL instead of a DEBUG-SOURCE.
152 (eval '(function-lambda-expression #'(lambda (x) x)))
154 ;;; bug caught and fixed by Raymond Toy cmucl-imp 2002-07-10: &REST
155 ;;; variable is not optional.
156 (with-test (:name (:lambda-list &rest :missing-name))
157 (multiple-value-bind (fun failure-p)
158 (checked-compile `(lambda (&rest) 12) :allow-failure t)
159 (assert failure-p)
160 (assert-error (funcall fun))))
162 ;;; on the PPC, we got the magic numbers in undefined_tramp wrong for
163 ;;; a while; fixed by CSR 2002-07-18
164 (with-test (:name :undefined-function-error)
165 (multiple-value-bind (value error)
166 (ignore-errors (funcall (checked-compile
167 `(lambda () (some-undefined-function))
168 :allow-style-warnings t)))
169 (assert (null value))
170 (assert (eq (cell-error-name error) 'some-undefined-function))))
172 (with-test (:name :unbound-variable-error)
173 (let ((foo (gensym)))
174 (assert (eq (handler-case (symbol-value foo)
175 (unbound-variable (c) (cell-error-name c)))
176 foo))
177 ;; on x86-64 the code for a literal symbol uses a slightly different path,
178 ;; so test that too
179 (assert (eq (handler-case xyzzy*%state
180 (unbound-variable (c) (cell-error-name c)))
181 'xyzzy*%state))
182 ;; And finally, also on x86-64, there was massive confusion about
183 ;; variable names that looked like names of thread slots.
184 (assert (eq (handler-case *state*
185 (unbound-variable (c) (cell-error-name c)))
186 '*state*))))
188 ;;; Non-symbols shouldn't be allowed as VARs in lambda lists. (Where VAR
189 ;;; is a variable name, as in section 3.4.1 of the ANSI spec.)
190 (with-test (:name (:lambda-list :non-symbols))
191 (mapc (lambda (case)
192 (destructuring-bind (form wrongp) case
193 (multiple-value-bind (fun failure-p)
194 (checked-compile form :allow-failure wrongp)
195 (assert (functionp fun))
196 (when wrongp
197 (assert failure-p)
198 (assert-error (funcall fun))))))
199 '(((lambda ("foo") 12) t)
200 ((lambda (foo) foo) nil)
202 ((lambda (&optional 12) "foo") t)
203 ((lambda (&optional twelve) twelve) nil)
205 ((lambda (&optional (12 12)) "foo") t)
206 ((lambda (&optional (twelve 12)) twelve) nil)
208 ((lambda (&key #\c) "foo") t)
209 ((lambda (&key c) c) nil)
211 ((lambda (&key (#\c #\c)) "foo") t)
212 ((lambda (&key (c #\c)) c) nil)
214 ((lambda (&key ((#\c #\c) #\c)) "foo") t)
215 ((lambda (&key ((:c c-var) #\c)) c-var) nil))))
217 ;;; As reported and fixed by Antonio Martinez-Shotton sbcl-devel
218 ;;; 2002-09-12, this failed in sbcl-0.7.7.23. (with failed AVER
219 ;;; "(LEAF-HAS-SOURCE-NAME-P LEAF)")
220 (assert (= (funcall (eval `(lambda (x) (funcall ,(lambda (y) (+ y 3)) x))) 14)
221 17))
223 ;;; bug 181: bad type specifier dropped compiler into debugger
224 (with-test (:name (compile declare :bad-type-specifier :bug-181))
225 (multiple-value-bind (fun failure-p)
226 (checked-compile `(lambda (x)
227 (declare (type (0) x))
229 :allow-warnings t)
230 (assert failure-p)))
232 (with-test (:name (compile make-array :bad-type-specifier :bug-181))
233 (multiple-value-bind (fun failure-p warnings)
234 (checked-compile `(lambda (x)
235 (declare (ignore x))
236 (make-array 1 :element-type '(0)))
237 :allow-warnings t)
238 (declare (ignore failure-p warnings))
239 ;; FIXME (assert (= 1 (length warnings)))
240 (assert-error (funcall fun 1))))
242 ;;; the following functions must not be flushable
243 (dolist (form '((make-sequence 'fixnum 10)
244 (concatenate 'fixnum nil)
245 (map 'fixnum #'identity nil)
246 (merge 'fixnum nil nil #'<)))
247 (assert (not (eval `(locally (declare (optimize (safety 0)))
248 (ignore-errors (progn ,form t)))))))
250 (dolist (form '((values-list (car (list '(1 . 2))))
251 (fboundp '(set bet))
252 (atan #c(1 1) (car (list #c(2 2))))
253 (nthcdr (car (list (floor (cos 3)))) '(1 2 3 4 5))
254 (nthcdr (car (list 5)) '(1 2 . 3))))
255 (assert (not (eval `(locally (declare (optimize (safety 3)))
256 (ignore-errors (progn ,form t)))))))
258 ;;; feature: we shall complain if functions which are only useful for
259 ;;; their result are called and their result ignored.
260 (with-test (:name :discarded-result)
261 (loop for (form expected-des) in
262 '(((progn (nreverse (list 1 2)) t)
263 "The return value of NREVERSE should not be discarded.")
264 ((progn (nreconc (list 1 2) (list 3 4)) t)
265 "The return value of NRECONC should not be discarded.")
266 ((locally
267 (declare (inline sort))
268 (sort (list 1 2) #'<) t)
269 ;; FIXME: it would be nice if this warned on non-inlined sort
270 ;; but the current simple boolean function attribute
271 ;; can't express the condition that would be required.
272 "The return value of STABLE-SORT-LIST should not be discarded.")
273 ((progn (sort (vector 1 2) #'<) t)
274 ;; Apparently, SBCL (but not CL) guarantees in-place vector
275 ;; sort, so no warning.
276 nil)
277 ((progn (delete 2 (list 1 2)) t)
278 "The return value of DELETE should not be discarded.")
279 ((progn (delete-if #'evenp (list 1 2)) t)
280 ("The return value of DELETE-IF should not be discarded."))
281 ((progn (delete-if #'evenp (vector 1 2)) t)
282 ("The return value of DELETE-IF should not be discarded."))
283 ((progn (delete-if-not #'evenp (list 1 2)) t)
284 "The return value of DELETE-IF-NOT should not be discarded.")
285 ((progn (delete-duplicates (list 1 2)) t)
286 "The return value of DELETE-DUPLICATES should not be discarded.")
287 ((progn (merge 'list (list 1 3) (list 2 4) #'<) t)
288 "The return value of MERGE should not be discarded.")
289 ((progn (nreconc (list 1 3) (list 2 4)) t)
290 "The return value of NRECONC should not be discarded.")
291 ((progn (nunion (list 1 3) (list 2 4)) t)
292 "The return value of NUNION should not be discarded.")
293 ((progn (nintersection (list 1 3) (list 2 4)) t)
294 "The return value of NINTERSECTION should not be discarded.")
295 ((progn (nset-difference (list 1 3) (list 2 4)) t)
296 "The return value of NSET-DIFFERENCE should not be discarded.")
297 ((progn (nset-exclusive-or (list 1 3) (list 2 4)) t)
298 "The return value of NSET-EXCLUSIVE-OR should not be discarded."))
299 for expected = (sb-int:ensure-list expected-des)
301 (multiple-value-bind (fun failure-p warnings style-warnings)
302 (checked-compile `(lambda () ,form) :allow-style-warnings (when expected t))
303 (declare (ignore failure-p warnings))
304 (when expected
305 (assert (= (length expected) (length style-warnings)))
306 (dolist (warning style-warnings)
307 (let ((expect-one (pop expected)))
308 (assert (search expect-one
309 (with-standard-io-syntax
310 (let ((*print-right-margin* nil))
311 (princ-to-string warning))))
313 "~S should have warned ~S, but instead warned: ~A"
314 form expect-one warning))))
315 (assert (functionp fun)))))
317 ;;; a bug in the MAP deftransform caused non-VECTOR array specifiers
318 ;;; to cause errors in the compiler. Fixed by CSR in 0.7.8.10
319 (with-test (:name (map :non-vector))
320 (checked-compile `(lambda (x) (map 'simple-array 'identity x))))
322 ;;; bug 129: insufficient syntax checking in MACROLET
323 (with-test (:name (compile macrolet :syntax :bug-129))
324 (multiple-value-bind (fun failure-p)
325 (checked-compile '(lambda () (macrolet ((foo x `',x)) (foo 1 2 3)))
326 :allow-failure t)
327 (assert failure-p)
328 (assert-error (funcall fun) program-error)))
330 ;;; bug 124: environment of MACROLET-introduced macro expanders
331 (with-test (:name (macrolet :bug-124))
332 (assert (equal
333 (macrolet ((mext (x) `(cons :mext ,x)))
334 (macrolet ((mint (y) `'(:mint ,(mext y))))
335 (list (mext '(1 2))
336 (mint (1 2)))))
337 '((:MEXT 1 2) (:MINT (:MEXT 1 2))))))
339 ;;; bug 48c: SYMBOL-MACROLET should signal PROGRAM-ERROR if introduced
340 ;;; symbol is declared to be SPECIAL
341 (with-test (:name (compile symbol-macrolet special program-error :bug-48c))
342 (multiple-value-bind (fun failure-p)
343 (checked-compile '(lambda ()
344 (symbol-macrolet ((s '(1 2)))
345 (declare (special s))
347 :allow-failure t)
348 (assert failure-p)
349 (assert-error (funcall fun) program-error)))
351 ;;; ECASE should treat a bare T as a literal key
352 (with-test (:name (ecase t 1))
353 (assert-error (ecase 1 (t 0)) sb-kernel:case-failure))
355 (with-test (:name (ecase t 2))
356 (assert (eql (ecase 1 (t 0) (1 2)) 2)))
358 ;;; FTYPE should accept any functional type specifier
359 (with-test (:name (compile ftype function))
360 (checked-compile '(lambda (x) (declare (ftype function f)) (f x))
361 :allow-style-warnings t))
363 ;;; FUNCALL of special operators and macros should signal an
364 ;;; UNDEFINED-FUNCTION error
365 ;;; But note the subtle distinction between writing (FUNCALL 'QUOTE 1)
366 ;;; and (FUNCALL #'QUOTE 1). In the latter, the error must be signaled
367 ;;; by the FUNCTION special operator, but the error class is unspecified.
368 (with-test (:name (funcall undefined-function cell-error-name quote))
369 (multiple-value-bind (result error)
370 (ignore-errors (funcall 'quote 1))
371 (assert (null result))
372 (assert (typep error 'undefined-function))
373 (assert (eq (cell-error-name error) 'quote))))
375 (with-test (:name (funcall undefined-function cell-error-name and))
376 (multiple-value-bind (result error)
377 (ignore-errors (funcall 'and 1))
378 (assert (null result))
379 (assert (typep error 'undefined-function))
380 (assert (eq (cell-error-name error) 'and))))
382 ;;; PSETQ should behave when given complex symbol-macro arguments
383 (with-test (:name (psetq symbol-macrolet))
384 (multiple-value-bind (sequence index)
385 (symbol-macrolet ((x (aref a (incf i)))
386 (y (aref a (incf i))))
387 (let ((a (copy-seq #(0 1 2 3 4 5 6 7 8 9)))
388 (i 0))
389 (psetq x (aref a (incf i))
390 y (aref a (incf i)))
391 (values a i)))
392 (assert (equalp sequence #(0 2 2 4 4 5 6 7 8 9)))
393 (assert (= index 4))))
395 (with-test (:name (psetq :ill-formed-variable))
396 (multiple-value-bind (fun failure-p)
397 (checked-compile `(lambda ()
398 (let ((x (list 1 2)))
399 (psetq (car x) 3)
401 :allow-failure t)
402 (assert failure-p)
403 (assert-error (funcall fun) program-error)))
405 ;;; COPY-SEQ should work on known-complex vectors:
406 (assert (equalp #(1)
407 (let ((v (make-array 0 :fill-pointer 0)))
408 (vector-push-extend 1 v)
409 (copy-seq v))))
411 ;;; to support INLINE functions inside MACROLET, it is necessary for
412 ;;; FUNCTION-LAMBDA-EXPRESSION to return a proper lambda expression in
413 ;;; certain circumstances, one of which is when compile is called from
414 ;;; top-level.
415 (with-test (:name (compile function-lambda-expression
416 :toplevel :must-return-lambda-expression))
417 (let ((form '(lambda (x) (block nil (print x)))))
418 (assert (equal form (function-lambda-expression
419 (checked-compile form))))))
421 ;;; bug 62: too cautious type inference in a loop
422 (with-test (:name (compile loop :type-inference))
423 (multiple-value-bind (fun failure-p warnings)
424 (checked-compile `(lambda (a)
425 (declare (optimize speed (safety 0)))
426 (typecase a
427 (array (loop (print (car a))))))
428 :allow-failure t
429 :allow-warnings t)
430 (declare (ignore fun))
431 (assert failure-p)
432 (assert (= 1 (length warnings)))))
434 ;;; Bug reported by Robert E. Brown sbcl-devel 2003-02-02: compiler
435 ;;; failure
436 (with-test (:name (:compiler-bug declare type loop))
437 (checked-compile
438 `(lambda (key tree collect-path-p)
439 (let ((lessp (key-lessp tree))
440 (equalp (key-equalp tree)))
441 (declare (type (function (t t) boolean) lessp equalp))
442 (let ((path '(nil)))
443 (loop for node = (root-node tree)
444 then (if (funcall lessp key (node-key node))
445 (left-child node)
446 (right-child node))
447 when (null node)
448 do (return (values nil nil nil))
449 do (when collect-path-p
450 (push node path))
451 (when (funcall equalp key (node-key node))
452 (return (values node path t)))))))
453 :allow-style-warnings t))
455 ;;; CONSTANTLY should return a side-effect-free function (bug caught
456 ;;; by Paul Dietz' test suite)
457 (let ((i 0))
458 (let ((fn (constantly (progn (incf i) 1))))
459 (assert (= i 1))
460 (assert (= (funcall fn) 1))
461 (assert (= i 1))
462 (assert (= (funcall fn) 1))
463 (assert (= i 1))))
465 ;;; Bug 240 reported by tonyms on #lisp IRC 2003-02-25 (modified version)
466 (with-test (:name (:lambda-list &optional :earmuffs))
467 (loop for (form warns-p) in
468 '(((lambda (&optional *x*) *x*) t)
469 ((lambda (&optional *x* &rest y) (values *x* y)) t)
470 ((lambda (&optional *print-length*) (values *print-length*)) nil)
471 ((lambda (&optional *print-length* &rest y) (values *print-length* y)) nil)
472 ((lambda (&optional *x*) (declare (special *x*)) (values *x*)) nil)
473 ((lambda (&optional *x* &rest y) (declare (special *x*)) (values *x* y)) nil))
474 do (let ((style-warnings (nth-value
475 3 (checked-compile
476 form :allow-style-warnings warns-p))))
477 (assert (= (if warns-p 1 0) (length style-warnings))))))
479 ;;; Bug reported by Gilbert Baumann on #lisp IRC 2003-03-26
480 (assert (equal (funcall (eval '(lambda (x &optional (y (pop x))) (list x y)))
481 '(1 2))
482 '((2) 1)))
484 ;;; Bug reported by Paul Dietz on cmucl-imp and fixed by Gerd
485 ;;; Moellmann: CONVERT-MORE-CALL failed on the following call
486 (assert (eq (eval '((lambda (&key) 'u) :allow-other-keys nil)) 'u))
488 (assert-error (multiple-value-bind (a b c)
489 (eval '(truncate 3 4))
490 (declare (integer c))
491 (list a b c))
492 type-error)
494 (assert (equal (multiple-value-list (the (values &rest integer)
495 (eval '(values 3))))
496 '(3)))
498 ;;; Bug relating to confused representation for the wild function
499 ;;; type:
500 (assert (null (funcall (eval '(lambda () (multiple-value-list (values)))))))
502 ;;; &ENVIRONMENT parameter should be bound first (from Paul Dietz'
503 ;;; test suite)
504 (assert (eql (macrolet ((foo () 1))
505 (macrolet ((%f (&optional (x (macroexpand '(foo) env)) &environment env)
507 (%f)))
510 ;;; MACROLET should check for duplicated names
511 (with-test (:name (macrolet :lambda-list :repeated-names))
512 (dolist (ll '((x (z x))
513 (x y &optional z x w)
514 (x y &optional z z)
515 (x &rest x)
516 (x &rest (y x))
517 (x &optional (y nil x))
518 (x &optional (y nil y))
519 (x &key x)
520 (x &key (y nil x))
521 (&key (y nil z) (z nil w))
522 (&whole x &optional x)))
523 (let ((style-warnings (nth-value
524 3 (checked-compile
525 `(lambda ()
526 (macrolet ((foo ,ll nil)
527 (bar (&environment env)
528 `',(macro-function 'foo env)))
529 (bar)))
530 :allow-style-warnings t))))
531 (assert style-warnings))))
533 ;; Uh, this test is semi-bogus - it's trying to test that you can't
534 ;; repeat, but it's now actually testing that &WHOLE has to appear
535 ;; first, per the formal spec.
536 (with-test (:name (macrolet :lambda-list &whole :must-be-first))
537 (assert-error (checked-compile
538 `(lambda ()
539 (macrolet ((foo (&environment x &whole x) nil)
540 (bar (&environment env)
541 `',(macro-function 'foo env)))
542 (bar))))))
544 (assert (typep (eval `(the arithmetic-error
545 ',(make-condition 'arithmetic-error)))
546 'arithmetic-error))
548 (with-test (:name (compile make-array :dimensions nil))
549 (checked-compile `(lambda ()
550 (make-array nil :initial-element 11))))
552 (assert-error (funcall (eval #'open) "compiler.pure.lisp"
553 :external-format '#:nonsense))
554 (assert-error (funcall (eval #'load) "compiler.pure.lisp"
555 :external-format '#:nonsense))
557 (assert (= (the (values integer symbol) (values 1 'foo 13)) 1))
559 (with-test (:name (compile eval the type-error))
560 (checked-compile-and-assert (:optimize :safe)
561 '(lambda (v)
562 (list (the fixnum (the (real 0) (eval v)))))
563 ((0.1) (condition 'type-error))
564 ((-1) (condition 'type-error))))
566 ;;; the implicit block does not enclose lambda list
567 (with-test (:name (compile :implicit block :does-not-enclose :lambda-list))
568 (let ((forms '((defmacro #1=#:foo (&optional (x (return-from #1#)))
569 (declare (ignore x)))
570 #+nil(macrolet ((#2=#:foo (&optional (x (return-from #2#))))))
571 (define-compiler-macro #3=#:foo (&optional (x (return-from #3#)))
572 (declare (ignore x)))
573 (deftype #4=#:foo (&optional (x (return-from #4#)))
574 (declare (ignore x)))
575 (define-setf-expander #5=#:foo (&optional (x (return-from #5#)))
576 (declare (ignore x)))
577 (defsetf #6=#:foo (&optional (x (return-from #6#))) ()
578 (declare (ignore x))))))
579 (dolist (form forms)
580 (assert (nth-value
581 1 (checked-compile `(lambda () ,form) :allow-failure t))))))
583 (with-test (:name (compile make-array svref :derive-type))
584 (multiple-value-bind (fun failurep warnings)
585 (checked-compile `(lambda ()
586 (svref (make-array '(8 9) :adjustable t) 1))
587 :allow-warnings t)
588 (declare (ignore fun))
589 (assert failurep)
590 (assert (= 1 (length warnings)))))
592 ;;; CHAR= did not check types of its arguments (reported by Adam Warner)
593 (macrolet ((define-char=-test (function form)
594 `(with-test (:name (compile ,function :argument-type-check))
595 (checked-compile-and-assert (:optimize :safe)
596 ,form
597 ((#\a #\b nil) (condition 'type-error))))))
598 (define-char=-test char= `(lambda (x y z) (char= x y z)))
599 (define-char=-test char/= `(lambda (x y z)
600 (char/= x y z))))
602 ;;; Compiler lost return type of MAPCAR and friends
603 (with-test (:name (compile mapcar mapc maplist mapl
604 :return-type :type-derivation))
605 (dolist (fun '(mapcar mapc maplist mapl))
606 (assert (= 1 (length (nth-value
607 2 (checked-compile
608 `(lambda (x)
609 (1+ (,fun #'print x)))
610 :allow-warnings t))))))
612 (assert (= 1 (length (nth-value
613 2 (checked-compile
614 `(lambda ()
615 (declare (notinline mapcar))
616 (1+ (mapcar #'print '(1 2 3))))
617 :allow-warnings t))))))
619 ;;; bug found by Paul Dietz: (SETF AREF) for bit vectors with constant
620 ;;; index was effectless
621 (with-test (:name (compile setf aref bit-vector))
622 (let ((f (checked-compile `(lambda (a v)
623 (declare (type simple-bit-vector a) (type bit v))
624 (declare (optimize (speed 3) (safety 0)))
625 (setf (aref a 0) v)
626 a))))
627 (let ((y (make-array 2 :element-type 'bit :initial-element 0)))
628 (assert (equal y #*00))
629 (funcall f y 1)
630 (assert (equal y #*10)))))
632 ;;; use of declared array types
633 (with-test (:name (compile declare array type :no sb-ext:compiler-note))
634 (dolist (form `((lambda (x)
635 (declare (type (simple-array (simple-string 3) (5)) x)
636 (optimize speed))
637 (aref (aref x 0) 0))
638 (lambda (x)
639 (declare (type (simple-array (simple-array bit (10)) (10)) x)
640 (optimize speed))
641 (1+ (aref (aref x 0) 0)))))
642 (checked-compile form :allow-notes nil)))
644 ;;; compiler failure
645 (with-test (:name (compile typep not member))
646 (checked-compile-and-assert () `(lambda (x) (typep x '(not (member 0d0))))
647 ((1d0) 't)))
649 (with-test (:name (compile double-float atan))
650 (checked-compile `(lambda (x)
651 (declare (double-float x))
652 (let ((y (* x pi)))
653 (atan y y)))))
655 ;;; bogus optimization of BIT-NOT
656 (multiple-value-bind (result x)
657 (eval '(let ((x (eval #*1001)))
658 (declare (optimize (speed 2) (space 3))
659 (type (bit-vector) x))
660 (values (bit-not x nil) x)))
661 (assert (equal x #*1001))
662 (assert (equal result #*0110)))
664 ;;; the VECTOR type in CONCATENATE/MERGE/MAKE-SEQUENCE means (VECTOR T).
665 (with-test (:name (compile vector make-sequence sb-ext:compiler-note))
666 (checked-compile-and-assert (:allow-notes nil)
667 `(lambda ()
668 (let ((x (make-sequence 'vector 10 :initial-element 'a)))
669 (setf (aref x 4) 'b)
671 (() #(a a a a b a a a a a) :test #'equalp)))
673 ;;; this is not a check for a bug, but rather a test of compiler
674 ;;; quality
675 (with-test (:name (compile integer :type-derivation))
676 (dolist (type '((integer 0 *) ; upper bound
677 (real (-1) *)
678 float ; class
679 (real * (-10)) ; lower bound
681 (assert (= 1 (length (nth-value
682 2 (checked-compile
683 `(lambda (n)
684 (declare (optimize (speed 3) (compilation-speed 0)))
685 (loop for i from 1 to (the (integer -17 10) n) by 2
686 collect (when (> (random 10) 5)
687 (the ,type (- i 11)))))
688 :allow-warnings t)))))))
690 ;;; bug 278b
692 ;;; We suppose that INTEGER arithmetic cannot be efficient, and the
693 ;;; compiler has an optimized VOP for +; so this code should cause an
694 ;;; efficiency note.
695 (with-test (:name (compile integer + sb-ext:compiler-note :bug-278b))
696 (assert (= 1 (length (nth-value
697 4 (checked-compile
698 `(lambda (i)
699 (declare (optimize speed))
700 (declare (type integer i))
701 (+ i 2))))))))
703 ;;; bug 277: IGNORE/IGNORABLE declarations should be acceptable for
704 ;;; symbol macros
705 (with-test (:name (compile symbol-macrolet ignore ignorable :bug-277))
706 (checked-compile `(lambda (u v)
707 (symbol-macrolet ((x u)
708 (y v))
709 (declare (ignore x)
710 (ignorable y))
711 (list u v)))))
713 ;;; bug reported by Paul Dietz: wrong optimizer for (EXPT ... 0)
714 (with-test (:name (compile expt :optimizer))
715 (loop for (x type) in
716 '((14 integer)
717 (14 rational)
718 (-14/3 (rational -8 11))
719 (3s0 short-float)
720 (4f0 single-float)
721 (5d0 double-float)
722 (6l0 long-float)
723 (14 real)
724 (13/2 real)
725 (2s0 real)
726 (2d0 real)
727 (#c(-3 4) (complex fixnum))
728 (#c(-3 4) (complex rational))
729 (#c(-3/7 4) (complex rational))
730 (#c(2s0 3s0) (complex short-float))
731 (#c(2f0 3f0) (complex single-float))
732 (#c(2d0 3d0) (complex double-float))
733 (#c(2l0 3l0) (complex long-float))
734 (#c(2d0 3s0) (complex float))
735 (#c(2 3f0) (complex real))
736 (#c(2 3d0) (complex real))
737 (#c(-3/7 4) (complex real))
738 (#c(-3/7 4) complex)
739 (#c(2 3l0) complex))
740 do (dolist (zero '(0 0s0 0f0 0d0 0l0))
741 (dolist (real-zero (list zero (- zero)))
742 (let* ((src `(lambda (x) (expt (the ,type x) ,real-zero)))
743 (fun (checked-compile src))
744 (result (1+ (funcall (eval #'*) x real-zero))))
745 (assert (eql result (funcall fun x))))))))
747 ;;; (SIGNED-BYTE 1) [ returned from the logxor derive-type optimizer ]
748 ;;; wasn't recognized as a good type specifier.
749 (let ((fun (lambda (x y)
750 (declare (type (integer -1 0) x y) (optimize speed))
751 (logxor x y))))
752 (assert (= (funcall fun 0 0) 0))
753 (assert (= (funcall fun 0 -1) -1))
754 (assert (= (funcall fun -1 -1) 0)))
756 ;;; from PFD's torture test, triggering a bug in our effective address
757 ;;; treatment.
758 (with-test (:name (compile declare type logandc1 logandc2))
759 (checked-compile `(lambda (a b)
760 (declare (type (integer 8 22337) b))
761 (logandc2
762 (logandc2
763 (* (logandc1 (max -29303 b) 4) b)
764 (abs (logorc1 (+ (logandc1 -11 b) 2607688420) -31153924)))
765 (logeqv (max a 0) b)))))
767 ;;; Alpha floating point modes weren't being reset after an exception,
768 ;;; leading to an exception on the second compile, below.
769 (with-test (:name (compile :floating-point-mode))
770 (let ((form `(lambda (x y) (declare (type (double-float 0.0d0) x y)) (/ x y))))
771 (checked-compile form)
772 (handler-case (/ 1.0 0.0)
773 ;; provoke an exception
774 (arithmetic-error ()))
775 (checked-compile form)))
777 ;;; bug reported by Paul Dietz: component last block does not have
778 ;;; start ctran
779 (with-test (:name (compile block return-from))
780 (checked-compile `(lambda ()
781 (declare (notinline + logand)
782 (optimize (speed 0)))
783 (logand
784 (block b5
785 (flet ((%f1 ()
786 (return-from b5 -220)))
787 (let ((v7 (%f1)))
788 (+ 359749 35728422))))
789 -24076))))
791 (with-test (:name :ansi-misc.293a)
792 (checked-compile-and-assert (:allow-style-warnings t
793 :optimize :quick/incomplete)
794 '(lambda (a b c)
795 (declare (optimize (space 3) (compilation-speed 2)))
796 (block b6
797 (multiple-value-prog1
798 0 b 0
799 (catch 'ct7
800 (return-from b6
801 (catch 'ct2
802 (complex (cl::handler-bind nil -254932942) 0)))))))
803 ((1 2 3) -254932942)))
805 (with-test (:name :ansi-misc.293d)
806 (checked-compile-and-assert (:optimize :quick/incomplete)
807 `(lambda ()
808 (declare (optimize (space 2) (compilation-speed 2)))
809 (block b4
810 (multiple-value-prog1
812 (catch 'ct8
813 (return-from b4 (catch 'ct2 (progn (tagbody) 0)))))))
814 (() 0)))
816 (with-test (:name :ansi-misc.618)
817 (checked-compile-and-assert (:optimize :quick/incomplete)
818 `(lambda (c)
819 (declare (optimize (space 0) (compilation-speed 2)))
820 (block b1
821 (ignore-errors
822 (multiple-value-prog1 0
823 (apply (constantly 0)
825 (catch 'ct2 (return-from b1 0))
826 nil)))))
827 ((-4951) 0)))
829 ;;; bug 294 reported by Paul Dietz: miscompilation of REM and MOD
830 (with-test (:name (compile rem :bug-294))
831 (checked-compile-and-assert ()
832 `(lambda (b)
833 (declare (type (integer 2 152044363) b))
834 (rem b (min -16 0)))
835 ((108251912) 8)))
837 (with-test (:name (compile mod :bug-294))
838 (checked-compile-and-assert ()
839 `(lambda (c)
840 (declare (type (integer 23062188 149459656) c))
841 (mod c (min -2 0)))
842 ((95019853) -1)))
844 ;;; bug reported by Paul Dietz: block splitting inside FLUSH-DEAD-CODE
845 (with-test (:name (compile logeqv rem :dead-code :block-splitting))
846 (checked-compile `(lambda (a b c)
847 (block b6
848 (logeqv (rem c -6758)
849 (rem b (max 44 (return-from b6 a))))))))
851 (with-test (:name (compile block flet :dead-code :block-splitting))
852 (checked-compile `(lambda ()
853 (block nil
854 (flet ((foo (x y) (if (> x y) (print x) (print y))))
855 (foo 1 2)
856 (bar)
857 (foo (return 14) 2))))
858 :allow-style-warnings t))
860 ;;; bug in Alpha backend: not enough sanity checking of arguments to
861 ;;; instructions
862 (with-test (:name (compile ash))
863 (checked-compile-and-assert ()
864 '(lambda (x)
865 (declare (fixnum x))
866 (ash x -257))
867 ((1024) 0)))
869 ;;; bug found by WHN and pfdietz: compiler failure while referencing
870 ;;; an entry point inside a deleted lambda
871 (with-test (:name (compile :reference-entry-point-in-deleted lambda))
872 (checked-compile
873 `(lambda ()
874 (let (r3533)
875 (flet ((bbfn ()
876 (setf r3533
877 (progn
878 (flet ((truly (fn bbd)
879 (let (r3534)
880 (let ((p3537 nil))
881 (unwind-protect
882 (multiple-value-prog1
883 (progn
884 (setf r3534
885 (progn
886 (bubf bbd t)
887 (flet ((c-3536 ()
888 (funcall fn)))
889 (cdec #'c-3536
890 (vector bbd))))))
891 (setf p3537 t))
892 (unless p3537
893 (error "j"))))
894 r3534))
895 (c (pd) (pdc pd)))
896 (let ((a (smock a))
897 (b (smock b))
898 (b (smock c)))))))))
899 (wum #'bbfn "hc3" (list)))
900 r3533))
901 :allow-failure t :allow-style-warnings t))
903 (with-test (:name (compile flet unwind-protect :dead-code))
904 (checked-compile `(lambda () (flet ((%f () (unwind-protect nil))) nil))))
906 ;;; the strength reduction of constant multiplication used (before
907 ;;; sbcl-0.8.4.x) to lie to the compiler. This meant that, under
908 ;;; certain circumstances, the compiler would derive that a perfectly
909 ;;; reasonable multiplication never returned, causing chaos. Fixed by
910 ;;; explicitly doing modular arithmetic, and relying on the backends
911 ;;; being smart.
912 (with-test (:name (compile * :constant))
913 (checked-compile-and-assert ()
914 '(lambda (x)
915 (declare (type (integer 178956970 178956970) x))
916 (* x 24))
917 ((178956970) 4294967280)))
919 ;;; bug in modular arithmetic and type specifiers
920 (with-test (:name (compile logand))
921 (checked-compile-and-assert ()
922 '(lambda (x) (logand x x 0))
923 ((-1) 0)))
925 ;;; MISC.99 from Paul Dietz' random tester: FAST-ASH-MOD32-C VOP
926 ;;; produced wrong result for shift >=32 on X86
927 (with-test (:name (compile mask-field :fast-ash-mod32-c-vop 18))
928 (checked-compile-and-assert ()
929 '(lambda (a)
930 (declare (type (integer 4303063 101130078) a))
931 (mask-field (byte 18 2) (ash a 77)))
932 ((57132532) 0)))
934 ;;; rewrite the test case to get the unsigned-byte 32/64
935 ;;; implementation even after implementing some modular arithmetic
936 ;;; with signed-byte 30:
937 (with-test (:name (compile mask-field :fast-ash-mod32-c-vop 30))
938 (checked-compile-and-assert ()
939 '(lambda (a)
940 (declare (type (integer 4303063 101130078) a))
941 (mask-field (byte 30 2) (ash a 77)))
942 ((57132532) 0)))
943 (with-test (:name (compile mask-field :fast-ash-mod32-c-vop 64))
944 (checked-compile-and-assert ()
945 '(lambda (a)
946 (declare (type (integer 4303063 101130078) a))
947 (mask-field (byte 64 2) (ash a 77)))
948 ((57132532) 0)))
949 ;;; and a similar test case for the signed masking extension (not the
950 ;;; final interface, so change the call when necessary):
951 (with-test (:name (compile sb-c::mask-signed-field :fast-ash-mod32-c-vop 30))
952 (checked-compile-and-assert ()
953 '(lambda (a)
954 (declare (type (integer 4303063 101130078) a))
955 (sb-c::mask-signed-field 30 (ash a 77)))
956 ((57132532) 0)))
957 (with-test (:name (compile sb-c::mask-signed-field :fast-ash-mod32-c-vop 61))
958 (checked-compile-and-assert ()
959 '(lambda (a)
960 (declare (type (integer 4303063 101130078) a))
961 (sb-c::mask-signed-field 61 (ash a 77)))
962 ((57132532) 0)))
964 ;;; MISC.101 and MISC.103: FLUSH-DEST did not mark the USE's block for
965 ;;; type check regeneration
966 (with-test (:name (compile :flush-dest :use :regenerate-type-check :misc.101))
967 (checked-compile-and-assert (:allow-warnings 'sb-int:type-warning)
968 '(lambda (a c)
969 (declare (type (integer 185501219873 303014665162) a))
970 (declare (type (integer -160758 255724) c))
971 (let ((v8
972 (- -554046873252388011622614991634432
973 (ignore-errors c)
974 (unwind-protect 2791485))))
975 (max (ignore-errors a)
976 (let ((v6 (- v8 (restart-case 980))))
977 (min v8 v6)))))
978 ((259448422916 173715) 259448422916)))
979 (with-test (:name (compile :flush-dest :use :regenerate-type-check :misc.103))
980 (checked-compile-and-assert (:allow-warnings 'sb-int:type-warning)
981 '(lambda (a b)
982 (min -80
983 (abs
984 (ignore-errors
986 (logeqv b
987 (block b6
988 (return-from b6
989 (load-time-value -6876935))))
990 (if (logbitp 1 a) b (setq a -1522022182249)))))))
991 ((-1802767029877 -12374959963) -80)))
993 ;;; various MISC.*, related to NODEs/LVARs with derived type NIL
994 (with-test (:name (compile :node/lvar :derive-type :misc.1))
995 (checked-compile-and-assert (:allow-warnings t)
996 '(lambda (c)
997 (declare (type (integer -3924 1001809828) c))
998 (min 47 (if (ldb-test (byte 2 14) c)
999 -570344431
1000 (ignore-errors -732893970))))
1001 ((705347625) -570344431)))
1002 (with-test (:name (compile :node/lvar :derive-type :misc.2))
1003 (checked-compile-and-assert (:allow-style-warnings t
1004 :allow-warnings t)
1005 '(lambda (b)
1006 (declare (type (integer -1598566306 2941) b))
1007 (max -148949 (ignore-errors b)))
1008 ((0) 0)))
1009 (with-test (:name (compile :node/lvar :derive-type :misc.3))
1010 (checked-compile-and-assert (:allow-style-warnings t)
1011 '(lambda (b c)
1012 (declare (type (integer -4 -3) c))
1013 (block b7
1014 (flet ((%f1 (f1-1 f1-2 f1-3)
1015 (if (logbitp 0 (return-from b7
1016 (- -815145138 f1-2)))
1017 (return-from b7 -2611670)
1018 99345)))
1019 (let ((v2 (%f1 -2464 (%f1 -1146 c c) -2)))
1020 b))))
1021 ((2950453607 -4) -815145134)))
1022 (with-test (:name (compile :node/lvar :derive-type :misc.4))
1023 (checked-compile-and-assert (:allow-warnings 'sb-int:type-warning)
1024 '(lambda (b c)
1025 (declare (type (integer -29742055786 23602182204) b))
1026 (declare (type (integer -7409 -2075) c))
1027 (floor
1028 (labels ((%f2 ()
1029 (block b6
1030 (ignore-errors (return-from b6
1031 (if (= c 8) b 82674))))))
1032 (%f2))))
1033 ((22992834060 -5833) (values 82674 0))))
1034 (with-test (:name (compile :node/lvar :derive-type :misc.5))
1035 (checked-compile-and-assert (:allow-warnings 'sb-int:type-warning)
1036 '(lambda (a)
1037 (declare (type (integer -944 -472) a))
1038 (round
1039 (block b3
1040 (return-from b3
1041 (if (= 55957 a) -117 (ignore-errors
1042 (return-from b3 a)))))))
1043 ((-589) (values -589 0))))
1045 ;;; MISC.158
1046 (with-test (:name (compile :misc.158))
1047 (checked-compile-and-assert ()
1048 '(lambda (a b c)
1049 (declare (type (integer 79828 2625480458) a))
1050 (declare (type (integer -4363283 8171697) b))
1051 (declare (type (integer -301 0) c))
1052 (if (equal 6392154 (logxor a b))
1053 1706
1054 (let ((v5 (abs c)))
1055 (logand v5
1056 (logior (logandc2 c v5)
1057 (common-lisp:handler-case
1058 (ash a (min 36 22477))))))))
1059 ((100000 0 0) 0)))
1061 ;;; MISC.152, 153: deleted code and iteration var type inference
1062 (with-test (:name (compile :deleted-code :iteration-variable :type-inference :misc.152))
1063 (checked-compile-and-assert (:allow-style-warnings t)
1064 '(lambda (a)
1065 (block b5
1066 (let ((v1 (let ((v8 (unwind-protect 9365)))
1067 8862008)))
1069 (return-from b5
1070 (labels ((%f11 (f11-1) f11-1))
1071 (%f11 87246015)))
1072 (return-from b5
1073 (setq v1
1074 (labels ((%f6 (f6-1 f6-2 f6-3) v1))
1075 (dpb (unwind-protect a)
1076 (byte 18 13)
1077 (labels ((%f4 () 27322826))
1078 (%f6 -2 -108626545 (%f4)))))))))))
1079 ((-6) 87246015)))
1081 (with-test (:name (compile :deleted-code :iteration-variable :type-inference :misc.153))
1082 (checked-compile-and-assert ()
1083 '(lambda (a)
1084 (if (logbitp 3
1085 (case -2
1086 ((-96879 -1035 -57680 -106404 -94516 -125088)
1087 (unwind-protect 90309179))
1088 ((-20811 -86901 -9368 -98520 -71594)
1089 (let ((v9 (unwind-protect 136707)))
1090 (block b3
1091 (setq v9
1092 (let ((v4 (return-from b3 v9)))
1093 (- (ignore-errors (return-from b3 v4))))))))
1094 (t -50)))
1095 -20343
1097 ((0) -20343)))
1099 ;;; MISC.165
1100 (with-test (:name (compile :misc.165))
1101 (checked-compile-and-assert (:allow-style-warnings t)
1102 '(lambda (a b c)
1103 (block b3
1104 (flet ((%f15
1105 (f15-1 f15-2 f15-3
1106 &optional
1107 (f15-4
1108 (flet ((%f17
1109 (f17-1 f17-2 f17-3
1110 &optional (f17-4 185155520) (f17-5 c)
1111 (f17-6 37))
1113 (%f17 -1046 a 1115306 (%f17 b -146330 422) -337817)))
1114 (f15-5 a) (f15-6 -40))
1115 (return-from b3 -16)))
1116 (multiple-value-call #'%f15 (values -519354 a 121 c -1905)))))
1117 ((0 0 -5) -16)))
1119 ;;; MISC.172
1120 (with-test (:name (compile :misc.172))
1121 (checked-compile-and-assert (:allow-style-warnings t)
1122 '(lambda (a b c)
1123 (declare (notinline list apply))
1124 (labels ((%f12 (f12-1 f12-2)
1125 (labels ((%f2 (f2-1 f2-2)
1126 (flet ((%f6 ()
1127 (flet ((%f18
1128 (f18-1
1129 &optional (f18-2 a)
1130 (f18-3 -207465075)
1131 (f18-4 a))
1132 (return-from %f12 b)))
1133 (%f18 -3489553
1135 (%f18 (%f18 150 -64 f12-1)
1136 (%f18 (%f18 -8531)
1137 11410)
1139 56362666))))
1140 (labels ((%f7
1141 (f7-1 f7-2
1142 &optional (f7-3 (%f6)))
1143 7767415))
1144 f12-1))))
1145 (%f2 b -36582571))))
1146 (apply #'%f12 (list 774 -4413))))
1147 ((0 1 2) 774)))
1149 ;;; MISC.173
1150 (with-test (:name (compile :misc.173))
1151 (checked-compile-and-assert (:allow-style-warnings t)
1152 '(lambda (a b c)
1153 (declare (notinline values))
1154 (flet ((%f11
1155 (f11-1 f11-2
1156 &optional (f11-3 c) (f11-4 7947114)
1157 (f11-5
1158 (flet ((%f3 (f3-1 &optional (f3-2 b) (f3-3 5529))
1159 8134))
1160 (multiple-value-call #'%f3
1161 (values (%f3 -30637724 b) c)))))
1162 (setq c 555910)))
1163 (if (and nil (%f11 a a))
1164 (if (%f11 a 421778 4030 1)
1165 (labels ((%f7
1166 (f7-1 f7-2
1167 &optional
1168 (f7-3
1169 (%f11 -79192293
1170 (%f11 c a c -4 214720)
1173 (%f11 b 985)))
1174 (f7-4 a))
1176 (%f11 c b -25644))
1178 -32326608)))
1179 ((1 2 3) -32326608)))
1181 ;;; MISC.177, 182: IR2 copy propagation missed a hidden write to a
1182 ;;; local lambda argument
1183 (with-test (:name (compile :ir2-copy-propagation :misc.177 :misc.182))
1184 (checked-compile-and-assert (:allow-style-warnings t)
1185 '(lambda (a b c)
1186 (declare (type (integer 804561 7640697) a))
1187 (declare (type (integer -1 10441401) b))
1188 (declare (type (integer -864634669 55189745) c))
1189 (declare (ignorable a b c))
1190 (flet ((%f11
1191 (f11-1 f11-2)
1192 (labels ((%f4 () (round 200048 (max 99 c))))
1193 (logand
1194 f11-1
1195 (labels ((%f3 (f3-1) -162967612))
1196 (%f3 (let* ((v8 (%f4)))
1197 (setq f11-1 (%f4)))))))))
1198 (%f11 -120429363 (%f11 62362 b))))
1199 ((6714367 9645616 -637681868) -264223548)))
1201 ;;; Bug reported by Paul F. Dietz caused by derive type loss in VALUE
1202 ;;; transform
1203 (with-test (:name (compile :value-transform :derive-type))
1204 (checked-compile-and-assert (:optimize :quick/incomplete)
1205 '(lambda ()
1206 (declare (optimize (space 0) (compilation-speed 1)))
1207 (ceiling (ceiling (flet ((%f16 () 0)) (%f16)))))
1208 (() (values 0 0))))
1210 ;;; MISC.184
1211 (with-test (:name (compile :misc.184))
1212 (checked-compile-and-assert (:allow-style-warnings t)
1213 '(lambda (a b c)
1214 (declare (type (integer 867934833 3293695878) a))
1215 (declare (type (integer -82111 1776797) b))
1216 (declare (type (integer -1432413516 54121964) c))
1217 (if nil
1218 (flet ((%f15 (f15-1 &optional (f15-2 c))
1219 (labels ((%f1 (f1-1 f1-2) 0))
1220 (%f1 a 0))))
1221 (flet ((%f4 ()
1222 (multiple-value-call #'%f15
1223 (values (%f15 c 0) (%f15 0)))))
1224 (if nil (%f4)
1225 (flet ((%f8 (f8-1 &optional (f8-2 (%f4)) (f8-3 0))
1226 f8-3))
1227 0))))
1229 ((3040851270 1664281 -1340106197) 0)))
1231 ;;; MISC.249
1232 (with-test (:name (compile :misc.249))
1233 (checked-compile-and-assert (:optimize :quick/incomplete)
1234 '(lambda (a b)
1235 (declare (notinline <=))
1236 (declare (optimize (space 3) (compilation-speed 3)))
1237 (if (if (<= 0) nil nil)
1238 (labels ((%f9 (f9-1 f9-2 f9-3)
1239 (ignore-errors 0)))
1240 (dotimes (iv4 5 a) (%f9 0 0 b)))
1242 ((1 2) 0)))
1244 ;;; MISC.259-264 (aka "CSR screwed up implementing *-MOD32")
1245 (with-test (:name (compile :mod32 :misc.259))
1246 (checked-compile-and-assert (:optimize :quick/incomplete)
1247 '(lambda (a)
1248 (declare (type (integer 177547470 226026978) a))
1249 (declare (optimize (space 0) (compilation-speed 1)))
1250 (logand a (* a 438810)))
1251 ((215067723) 13739018)))
1254 ;;;; Bugs in stack analysis
1255 ;;; bug 299 (reported by PFD)
1256 (with-test (:name (compile :stack-analysis :bug-299))
1257 (checked-compile-and-assert ()
1258 '(lambda ()
1259 (multiple-value-call #'list
1260 (if (eval t) (eval '(values :a :b :c)) nil)
1261 (catch 'foo (throw 'foo (values :x :y)))))
1262 (() '(:a :b :c :x :y))))
1263 ;;; bug 298 (= MISC.183)
1264 (with-test (:name (compile :bug-298 :misc.183))
1265 (checked-compile-and-assert (:allow-style-warnings t)
1266 '(lambda (a b c)
1267 (declare (type (integer -368154 377964) a))
1268 (declare (type (integer 5044 14959) b))
1269 (declare (type (integer -184859815 -8066427) c))
1270 (declare (ignorable a b c))
1271 (block b7
1272 (flet ((%f3 (f3-1 f3-2 f3-3) 0))
1273 (apply #'%f3 0 (catch 'foo (return-from b7 (%f3 0 b c))) c nil))))
1274 ((0 6000 -9000000) 0)))
1275 (assert (equal (eval '(let () (apply #'list 1 (list (catch 'a (throw 'a (block b 2)))))))
1276 '(1 2)))
1277 (with-test (:name (compile multiple-value-call block return-from))
1278 (checked-compile-and-assert ()
1279 '(lambda (x)
1280 (block foo
1281 (multiple-value-call #'list
1283 (block bar
1284 (return-from foo
1285 (multiple-value-call #'list
1287 (block quux
1288 (return-from bar
1289 (catch 'baz
1290 (if x
1291 (return-from quux 1)
1292 (throw 'baz 2)))))))))))
1293 ((t) '(:b 1))
1294 ((nil) '(:a 2))))
1296 ;;; MISC.185
1297 (with-test (:name (compile :misc.185))
1298 (checked-compile-and-assert (:allow-style-warnings t)
1299 '(lambda (a b c)
1300 (declare (type (integer 5 155656586618) a))
1301 (declare (type (integer -15492 196529) b))
1302 (declare (type (integer 7 10) c))
1303 (flet ((%f3
1304 (f3-1 f3-2 f3-3
1305 &optional (f3-4 a) (f3-5 0)
1306 (f3-6
1307 (labels ((%f10 (f10-1 f10-2 f10-3)
1309 (apply #'%f10
1312 (- (if (equal a b) b (%f10 c a 0))
1313 (catch 'ct2 (throw 'ct2 c)))
1314 nil))))
1316 (%f3 (%f3 (%f3 b 0 0 0) a 0) a b b b c)))
1317 ((5 0 7) 0)))
1318 ;;; MISC.186
1319 (with-test (:name (eval compile :misc.186))
1320 (assert (eq
1321 (eval
1322 '(let* ((form '(labels ((%f3 (f3-1 f3-2) f3-1))
1323 (apply #'%f3 b (catch 'ct8 (throw 'ct8 (logeqv (%f3 c 0)))) nil)))
1324 (vars '(b c))
1325 (fn1 `(lambda ,vars
1326 (declare (type (integer -2 19) b)
1327 (type (integer -1520 218978) c)
1328 (optimize (speed 3) (safety 1) (debug 1)))
1329 ,form))
1330 (fn2 `(lambda ,vars
1331 (declare (notinline logeqv apply)
1332 (optimize (safety 3) (speed 0) (debug 0)))
1333 ,form))
1334 (cf1 (compile nil fn1))
1335 (cf2 (compile nil fn2))
1336 (result1 (multiple-value-list (funcall cf1 2 18886)))
1337 (result2 (multiple-value-list (funcall cf2 2 18886))))
1338 (if (equal result1 result2)
1339 :good
1340 (values result1 result2))))
1341 :good)))
1343 ;;; MISC.290
1344 (with-test (:name (compile :misc.290))
1345 (assert (zerop
1346 (funcall
1347 (checked-compile
1348 '(lambda ()
1349 (declare
1350 (optimize (speed 3) (space 3) (safety 1)
1351 (debug 2) (compilation-speed 0)))
1352 (apply (constantly 0) (catch 'ct2 0) 0 (catch 'ct2 0) nil)))))))
1354 ;;; MISC.292
1355 (with-test (:name (compile :misc.292))
1356 (assert (zerop (funcall
1357 (checked-compile
1358 '(lambda (a b)
1359 (declare (optimize (speed 2) (space 0) (safety 3) (debug 1)
1360 (compilation-speed 2)))
1361 (apply (constantly 0)
1364 (catch 'ct6
1365 (apply (constantly 0)
1368 (let* ((v1
1369 (let ((*s7* 0))
1370 b)))
1373 nil))
1375 nil))
1376 :allow-style-warnings t)
1377 1 2))))
1379 ;;; misc.295
1380 (with-test (:name (compile :misc.295))
1381 (assert (eql
1382 (funcall
1383 (checked-compile
1384 '(lambda ()
1385 (declare (optimize (speed 1) (space 0) (safety 0) (debug 0)))
1386 (multiple-value-prog1
1387 (the integer (catch 'ct8 (catch 'ct7 15867134)))
1388 (catch 'ct1 (throw 'ct1 0))))))
1389 15867134)))
1391 ;;; misc.361: replacing CAST with (m-v-call #'%compile-time-type-error)
1392 ;;; could transform known-values LVAR to UVL
1393 (with-test (:name (compile :cast multiple-value-call :misc.361))
1394 (assert (zerop (funcall
1395 (checked-compile
1396 '(lambda (a b c)
1397 (declare (notinline boole values denominator list))
1398 (declare
1399 (optimize (speed 2)
1400 (space 0)
1401 (safety 1)
1402 (debug 0)
1403 (compilation-speed 2)))
1404 (catch 'ct6
1405 (progv
1406 '(*s8*)
1407 (list 0)
1408 (let ((v9 (ignore-errors (throw 'ct6 0))))
1409 (denominator
1410 (progv nil nil (values (boole boole-and 0 v9))))))))
1411 :allow-warnings 'sb-int:type-warning :allow-style-warnings t)
1412 1 2 3))))
1414 ;;; non-continuous dead UVL blocks
1415 (defun non-continuous-stack-test (x)
1416 (multiple-value-call #'list
1417 (eval '(values 11 12))
1418 (eval '(values 13 14))
1419 (block ext
1420 (return-from non-continuous-stack-test
1421 (multiple-value-call #'list
1422 (eval '(values :b1 :b2))
1423 (eval '(values :b3 :b4))
1424 (block int
1425 (return-from ext
1426 (multiple-value-call (eval #'values)
1427 (eval '(values 1 2))
1428 (eval '(values 3 4))
1429 (block ext
1430 (return-from int
1431 (multiple-value-call (eval #'values)
1432 (eval '(values :a1 :a2))
1433 (eval '(values :a3 :a4))
1434 (block int
1435 (return-from ext
1436 (multiple-value-call (eval #'values)
1437 (eval '(values 5 6))
1438 (eval '(values 7 8))
1439 (if x
1440 :ext
1441 (return-from int :int))))))))))))))))
1442 (assert (equal (non-continuous-stack-test t) '(11 12 13 14 1 2 3 4 5 6 7 8 :ext)))
1443 (assert (equal (non-continuous-stack-test nil) '(:b1 :b2 :b3 :b4 :a1 :a2 :a3 :a4 :int)))
1445 ;;; MISC.362: environment of UNWIND-PROTECTor is different from that
1446 ;;; if ENTRY.
1447 (with-test (:name (compile unwind-protect :misc.362))
1448 (assert (equal (multiple-value-list
1449 (funcall
1450 (checked-compile
1451 '(lambda (b g h)
1452 (declare (optimize (speed 3) (space 3) (safety 2)
1453 (debug 2) (compilation-speed 3)))
1454 (catch 'ct5
1455 (unwind-protect
1456 (labels ((%f15 (f15-1 f15-2 f15-3)
1457 (rational (throw 'ct5 0))))
1458 (%f15 0
1459 (apply #'%f15
1462 (progn
1463 (progv '(*s2* *s5*) (list 0 (%f15 0 g 0)) b)
1465 nil)
1467 (common-lisp:handler-case 0))))
1468 :allow-style-warnings t)
1469 1 2 3))
1470 '(0))))
1473 ;;; MISC.275
1474 (with-test (:name (compile :misc.275))
1475 (assert
1476 (zerop
1477 (funcall
1478 (checked-compile
1479 '(lambda (b)
1480 (declare (notinline funcall min coerce))
1481 (declare
1482 (optimize (speed 1)
1483 (space 2)
1484 (safety 2)
1485 (debug 1)
1486 (compilation-speed 1)))
1487 (flet ((%f12 (f12-1)
1488 (coerce
1489 (min
1490 (if f12-1 (multiple-value-prog1
1491 b (return-from %f12 0))
1493 'integer)))
1494 (funcall #'%f12 0))))
1495 -33))))
1497 ;;; Discussion of a CMUCL PCL bug on Sparc with Raymond Toy revealed a
1498 ;;; potential problem: optimizers and type derivers for MAX and MIN
1499 ;;; were not consistent in treating EQUALP, but not EQL, arguments.
1500 (with-test (:name (compile min max :derive-type equalp))
1501 (dolist (f '(min max))
1502 (loop for complex-arg-args in '((1d0 2d0) (0d0 1d0))
1503 for complex-arg = `(if x ,@complex-arg-args)
1505 (loop for args in `((1 ,complex-arg)
1506 (,complex-arg 1))
1507 for form = `(,f ,@args)
1508 for f1 = (checked-compile `(lambda (x) ,form))
1509 and f2 = (checked-compile `(lambda (x)
1510 (declare (notinline min max))
1511 ,form))
1513 (dolist (x '(nil t))
1514 (assert (eql (funcall f1 x) (funcall f2 x))))))))
1517 ;; Ignore the note for the float -> pointer conversion of the
1518 ;; return value.
1519 (defun float->pointer-conversion-note-p (condition)
1520 (string= (car (last (sb-c::simple-condition-format-arguments condition)))
1521 "<return value>"))
1522 (with-test (:name (compile :trust-result-type-declaration))
1523 (checked-compile
1524 '(lambda (x)
1525 (declare (optimize (speed 3) (safety 0)))
1526 (the double-float (sqrt (the double-float x))))
1527 :allow-notes '(satisfies float->pointer-conversion-note-p)))
1529 (with-test (:name (compile block the return))
1530 (let ((f (checked-compile
1531 '(lambda (x)
1532 (declare (optimize speed (safety 0)))
1533 (block nil
1534 (the double-float
1535 (multiple-value-prog1
1536 (sqrt (the double-float x))
1537 (when (< x 0)
1538 (return :minus)))))))))
1539 (assert (eql (funcall f -1d0) :minus))
1540 (assert (eql (funcall f 4d0) 2d0))))
1542 ;;; bug 304: SBCL produced something similar to (/ (ASH x 4) 8)
1543 (defun %ash/right-note-p (condition)
1544 (search "%ASH/RIGHT" (first (simple-condition-format-arguments condition))))
1545 (with-test (:name (compile deref :bug-304))
1546 (checked-compile
1547 '(lambda (a i)
1548 (locally
1549 (declare (optimize (speed 3) (safety 0) (space 0) (debug 0)
1550 (inhibit-warnings 0)))
1551 (declare (type (alien (* (unsigned 8))) a)
1552 (type (unsigned-byte 32) i))
1553 (deref a i)))
1554 :allow-notes '(satisfies %ash/right-note-p)))
1556 (with-test (:name (compile identity :derive-type))
1557 (checked-compile
1558 '(lambda (x)
1559 (declare (type (integer -100 100) x))
1560 (declare (optimize speed))
1561 (declare (notinline identity))
1562 (1+ (identity x)))
1563 :allow-notes nil))
1565 (with-test (:name (compile funcall cddr))
1566 (assert (null (funcall (checked-compile '(lambda (x) (funcall #'cddr x))) nil))))
1568 ;;; MISC.293 = easy variant of bug 303: repeated write to the same
1569 ;;; LVAR; here the first write may be cleared before the second is
1570 ;;; made.
1571 (with-test (:name (compile :repeated-write-to-lvar :misc.293 :easy))
1572 (assert
1573 (zerop
1574 (funcall
1575 (checked-compile
1576 '(lambda ()
1577 (declare (notinline complex))
1578 (declare (optimize (speed 1) (space 0) (safety 1)
1579 (debug 3) (compilation-speed 3)))
1580 (flet ((%f () (multiple-value-prog1 0 (return-from %f 0))))
1581 (complex (%f) 0))))))))
1583 (with-test (:name (compile :misc.293 :harder))
1584 ;; Similar to the above case, but can blow up in stack analysis if
1585 ;; the two blocks in the M-V-P1 are joined (due to both (FUNCALL Y)
1586 ;; forms producing multiple-value results into the same LVAR,
1587 ;; requiring a cleanup to be inserted between the two, yet not
1588 ;; possible due to the lack of a block boundary).
1589 (checked-compile
1590 '(lambda (x)
1591 (declare (notinline complex))
1592 (declare (optimize (speed 1) (space 0) (safety 1)
1593 (debug 3) (compilation-speed 3)))
1594 (flet ((%f (y) (multiple-value-prog1 (funcall y)
1595 (return-from %f (funcall y)))))
1596 (complex (%f x) 0)))))
1598 ;;; MISC.110A: CAST optimizer forgot to flush LVAR derived type
1599 (with-test (:name (compile :cast :flush-lvar-derived-type :misc.110a))
1600 (assert (zerop (funcall
1601 (checked-compile
1602 '(lambda (a c)
1603 (declare (type (integer -1294746569 1640996137) a))
1604 (declare (type (integer -807801310 3) c))
1605 (declare (optimize (speed 3) (space 3) (safety 0) (debug 0) (compilation-speed 3)))
1606 (catch 'ct7
1608 (logbitp 0
1609 (if (/= 0 a)
1611 (ignore-errors
1612 (progn (if (ldb-test (byte 0 0) (rational (throw 'ct7 0))) 0 0) 0))))
1613 0 0)))
1614 :allow-warnings 'sb-int:type-warning)
1615 391833530 -32785211))))
1617 ;;; efficiency notes for ordinary code
1618 (with-test (:name (compile :no-notes))
1619 (macrolet ((frob (arglist &body body)
1620 `(progn
1621 (checked-compile '(lambda ,arglist ,@body) :allow-notes nil)
1622 (unless (nth-value
1623 4 (checked-compile
1624 '(lambda ,arglist (declare (optimize speed))
1625 ,@body)))
1626 (error "missing compiler note for ~S" ',body)))))
1627 (frob (x) (funcall x))
1628 (frob (x y) (find x y))
1629 (frob (x y) (find-if x y))
1630 (frob (x y) (find-if-not x y))
1631 (frob (x y) (position x y))
1632 (frob (x y) (position-if x y))
1633 (frob (x y) (position-if-not x y))
1634 (frob (x) (aref x 0))))
1636 (with-test (:name (compile style-warning :smoke))
1637 (macrolet ((frob (style-warn-p form)
1638 (unless (eq (car form) 'lambda)
1639 (setq form `(lambda () ,form)))
1640 (if style-warn-p
1641 `(unless (nth-value
1642 3 (checked-compile ',form :allow-style-warnings t))
1643 (error "missing style-warning for ~S" ',form))
1644 `(checked-compile ',form))))
1645 (frob t (lambda (x &optional y &key z) (list x y z)))
1646 (frob nil (lambda (x &optional y z) (list x y z)))
1647 (frob nil (lambda (x &key y z) (list x y z)))
1648 (frob t (defgeneric #:foo (x &optional y &key z)))
1649 (frob nil (defgeneric #:foo (x &optional y z)))
1650 (frob nil (defgeneric #:foo (x &key y z)))
1651 (frob t (defun #:foo (x) (flet ((foo (x &optional y &key z) (list x y z))) (foo x x :z x))))))
1653 ;;; this was a bug in the LOGXOR type deriver. The top form gave a
1654 ;;; note, because the system failed to derive the fact that the return
1655 ;;; from LOGXOR was small and negative, though the bottom one worked.
1656 (with-test (:name (compile logxor :derive-type))
1657 (checked-compile
1658 '(lambda ()
1659 (declare (optimize speed (safety 0)))
1660 (lambda (x y)
1661 (declare (type (integer 3 6) x)
1662 (type (integer -6 -3) y))
1663 (+ (logxor x y) most-positive-fixnum)))
1664 :allow-notes nil)
1665 (checked-compile
1666 '(lambda ()
1667 (declare (optimize speed (safety 0)))
1668 (lambda (x y)
1669 (declare (type (integer 3 6) y)
1670 (type (integer -6 -3) x))
1671 (+ (logxor x y) most-positive-fixnum)))
1672 :allow-notes nil))
1674 ;;; check that modular ash gives the right answer, to protect against
1675 ;;; possible misunderstandings about the hardware shift instruction.
1676 (with-test (:name (compile ash :smoke))
1677 (assert (zerop (funcall
1678 (checked-compile '(lambda (x y)
1679 (declare (optimize speed)
1680 (type (unsigned-byte 32) x y))
1681 (logand #xffffffff (ash x y))))
1682 1 257))))
1684 ;;; code instrumenting problems
1685 (checked-compile
1686 '(lambda ()
1687 (declare (optimize (debug 3)))
1688 (list (the integer (if nil 14 t))))
1689 :allow-warnings t)
1691 (checked-compile
1692 '(LAMBDA (A B C D)
1693 (DECLARE (NOTINLINE LOGORC1 BYTE MASK-FIELD))
1694 (DECLARE
1695 (OPTIMIZE (SPEED 1)
1696 (SPACE 1)
1697 (SAFETY 1)
1698 (DEBUG 3)
1699 (COMPILATION-SPEED 0)))
1700 (MASK-FIELD (BYTE 7 26)
1701 (PROGN
1702 (TAGBODY (THE INTEGER (CATCH 'CT4 (LOGORC1 C -15950))) 1)
1703 B)))
1704 :allow-style-warnings t)
1706 (checked-compile
1707 '(lambda (buffer i end)
1708 (declare (optimize (debug 3)))
1709 (loop (when (not (eql 0 end)) (return)))
1710 (let ((s (make-string end)))
1711 (setf (schar s i) (schar buffer i))
1712 s)))
1714 ;;; check that constant string prefix and suffix don't cause the
1715 ;;; compiler to emit code deletion notes.
1716 (with-test (:name (compile pprint-logical-block :prefix :suffix :no-notes))
1717 (checked-compile
1718 '(lambda (s x)
1719 (pprint-logical-block (s x :prefix "(")
1720 (print x s)))
1721 :allow-notes nil)
1722 (checked-compile
1723 '(lambda (s x)
1724 (pprint-logical-block (s x :per-line-prefix ";")
1725 (print x s)))
1726 :allow-notes nil)
1727 (checked-compile
1728 '(lambda (s x)
1729 (pprint-logical-block (s x :suffix ">")
1730 (print x s)))
1731 :allow-notes nil))
1733 ;;; MISC.427: loop analysis requires complete DFO structure
1734 (with-test (:name (compile :loop-analysis :misc.427))
1735 (assert (eql 17 (funcall
1736 (checked-compile
1737 '(lambda (a)
1738 (declare (notinline list reduce logior))
1739 (declare (optimize (safety 2) (compilation-speed 1)
1740 (speed 3) (space 2) (debug 2)))
1741 (logior
1742 (let* ((v5 (reduce #'+ (list 0 a))))
1743 (declare (dynamic-extent v5))
1744 v5))))
1745 17))))
1747 ;;; MISC.434
1748 (with-test (:name (compile :misc.434))
1749 (assert (zerop (funcall
1750 (checked-compile
1751 '(lambda (a b)
1752 (declare (type (integer -8431780939320 1571817471932) a))
1753 (declare (type (integer -4085 0) b))
1754 (declare (ignorable a b))
1755 (declare
1756 (optimize (space 2)
1757 (compilation-speed 0)
1758 #+sbcl (sb-c:insert-step-conditions 0)
1759 (debug 2)
1760 (safety 0)
1761 (speed 3)))
1762 (let ((*s5* 0))
1763 (dotimes (iv1 2 0)
1764 (let ((*s5*
1765 (elt '(1954479092053)
1766 (min 0
1767 (max 0
1768 (if (< iv1 iv1)
1769 (lognand iv1 (ash iv1 (min 53 iv1)))
1770 iv1))))))
1771 0))))
1772 :allow-style-warnings t)
1773 -7639589303599 -1368))))
1775 (checked-compile
1776 '(lambda (a b)
1777 (declare (type (integer) a))
1778 (declare (type (integer) b))
1779 (declare (ignorable a b))
1780 (declare (optimize (space 2) (compilation-speed 0)
1781 (debug 0) (safety 0) (speed 3)))
1782 (dotimes (iv1 2 0)
1783 (when (< iv1 2) (print 'x)) ;; request for second constraint propagation pass
1784 (print (if (< iv1 iv1)
1785 (logand (ash iv1 iv1) 1)
1786 iv1)))))
1788 ;;; MISC.435: lambda var substitution in a deleted code.
1789 (with-test (:name (compile :misc.435))
1790 (assert (zerop (funcall
1791 (checked-compile
1792 '(lambda (a b c d)
1793 (declare (notinline aref logandc2 gcd make-array))
1794 (declare
1795 (optimize (space 0) (safety 0) (compilation-speed 3)
1796 (speed 3) (debug 1)))
1797 (progn
1798 (tagbody
1799 (let* ((v2 (make-array nil :initial-element (catch 'ct1 (go tag2)))))
1800 (declare (dynamic-extent v2))
1801 (gcd (go tag2) (logandc2 (catch 'ct2 c) (aref v2))))
1802 tag2)
1804 :allow-style-warnings t)
1805 3021871717588 -866608 -2 -17194))))
1807 ;;; MISC.436, 438: lost reoptimization
1808 (with-test (:name (compile :lost-reoptimization :misc.436 :misc.438))
1809 (assert (zerop (funcall
1810 (checked-compile
1811 '(lambda (a b)
1812 (declare (type (integer -2917822 2783884) a))
1813 (declare (type (integer 0 160159) b))
1814 (declare (ignorable a b))
1815 (declare
1816 (optimize (compilation-speed 1)
1817 (speed 3)
1818 (safety 3)
1819 (space 0)
1820 ; #+sbcl (sb-c:insert-step-conditions 0)
1821 (debug 0)))
1823 (oddp
1824 (loop for
1826 below
1828 count
1829 (logbitp 0
1831 (ash b
1832 (min 8
1833 (count 0
1834 '(-10197561 486 430631291
1835 9674068))))))))
1837 0)))
1838 1265797 110757))))
1840 (assert (zerop (funcall
1841 (checked-compile
1842 '(lambda (a)
1843 (declare (type (integer 0 1696) a))
1844 ; (declare (ignorable a))
1845 (declare (optimize (space 2) (debug 0) (safety 1)
1846 (compilation-speed 0) (speed 1)))
1847 (if (logbitp 0 (ash (1- a) (min 11 a))) 0 0)))
1848 805)))
1850 ;;; bug #302
1851 (with-test (:name (compile :bug-302))
1852 (assert (checked-compile
1853 '(lambda (s ei x y)
1854 (declare (type (simple-array function (2)) s) (type ei ei))
1855 (funcall (aref s ei) x y))
1856 :allow-style-warnings t)))
1858 ;;; MISC.320: ir1-transform can create an intercomponent reference to
1859 ;;; a DEFINED-FUN.
1860 (with-test (:name (compile :misc.320))
1861 (assert (eql 102 (funcall
1862 (checked-compile
1863 '(lambda ()
1864 (declare (optimize (speed 3) (space 0) (safety 2)
1865 (debug 2) (compilation-speed 0)))
1866 (catch 'ct2
1867 (elt '(102)
1868 (flet ((%f12 () (rem 0 -43)))
1869 (multiple-value-call #'%f12 (values)))))))))))
1871 ;;; MISC.437: lost reoptimization after FLUSH-DEST
1872 (with-test (:name (compile :misc.437))
1873 (assert (zerop (funcall
1874 (checked-compile
1875 '(lambda (a b c d e)
1876 (declare (notinline values complex eql))
1877 (declare
1878 (optimize (compilation-speed 3)
1879 (speed 3)
1880 (debug 1)
1881 (safety 1)
1882 (space 0)))
1883 (flet ((%f10
1884 (f10-1 f10-2 f10-3
1885 &optional (f10-4 (ignore-errors 0)) (f10-5 0)
1886 &key &allow-other-keys)
1887 (if (or (eql 0 0) t) 0 (if f10-1 0 0))))
1888 (complex (multiple-value-call #'%f10 (values a c b 0 0)) 0)))
1889 :allow-style-warnings t)
1890 80043 74953652306 33658947 -63099937105 -27842393))))
1892 ;;; bug #351 -- program-error for malformed LET and LET*, including those
1893 ;;; resulting from SETF of LET.
1894 (with-test (:name (compile let let* :malformed program-error :bug-351))
1895 (dolist (fun (list (checked-compile '(lambda (x) (let :bogus-let :oops))
1896 :allow-failure t :allow-style-warnings t)
1897 (checked-compile '(lambda (x) (let* :bogus-let* :oops))
1898 :allow-failure t :allow-style-warnings t)
1899 (checked-compile '(lambda (x) (push x (let ((y 0)) y)))
1900 :allow-failure t :allow-warnings t)))
1901 (assert (functionp fun))
1902 (multiple-value-bind (res err) (ignore-errors (funcall fun t))
1903 (assert (not res))
1904 (assert (typep err 'program-error))
1905 (assert (not (sequence:emptyp (princ-to-string err)))))))
1907 (with-test (:name (compile random :distribution))
1908 (let ((fun (checked-compile '(lambda (x) (random (if x 10 20))))))
1909 (dotimes (i 100 (error "bad RANDOM distribution"))
1910 (when (> (funcall fun nil) 9)
1911 (return t)))
1912 (dotimes (i 100)
1913 (when (> (funcall fun t) 9)
1914 (error "bad RANDOM event")))))
1916 ;;; 0.8.17.28-sma.1 lost derived type information.
1917 (with-test (:name (compile :0.8.17.28-sma.1) :fails-on :sparc)
1918 (checked-compile
1919 '(lambda (x y v)
1920 (declare (optimize (speed 3) (safety 0)))
1921 (declare (type (integer 0 80) x)
1922 (type (integer 0 11) y)
1923 (type (simple-array (unsigned-byte 32) (*)) v))
1924 (setf (aref v 0) (* (* x #.(floor (ash 1 32) (* 11 80))) y))
1925 nil)
1926 :allow-notes nil))
1928 ;;; Bug reported by Robert J. Macomber: instrumenting of more-entry
1929 ;;; prevented open coding of %LISTIFY-REST-ARGS.
1930 (with-test (:name (compile :more-entry :%listity-rest-args))
1931 (let ((f (checked-compile '(lambda ()
1932 (declare (optimize (debug 3)))
1933 (with-simple-restart (blah "blah") (error "blah"))))))
1934 (handler-bind ((error (lambda (c) (declare (ignore c)) (invoke-restart 'blah))))
1935 (assert (equal (multiple-value-list (funcall f)) '(nil t))))))
1937 ;;; Bug reported by Timmy Douglas: overflow in bit vector setter with
1938 ;;; constant index and value.
1939 (with-test (:name (compile bit-vector setf aref :overflow))
1940 (loop for n-bits = 1 then (* n-bits 2)
1941 for type = `(unsigned-byte ,n-bits)
1942 and v-max = (1- (ash 1 n-bits))
1943 while (<= n-bits sb-vm:n-word-bits)
1945 (let* ((n (* 2 (1+ (- sb-vm::n-word-bits n-bits))))
1946 (array1 (make-array n :element-type type))
1947 (array2 (make-array n :element-type type)))
1948 (dotimes (i n)
1949 (dolist (v (list 0 v-max))
1950 (let ((f (checked-compile
1951 `(lambda (a)
1952 (declare (type (simple-array ,type (,n)) a))
1953 (setf (aref a ,i) ,v)))))
1954 (fill array1 (- v-max v))
1955 (fill array2 (- v-max v))
1956 (funcall f array1)
1957 (setf (aref array2 i) v)
1958 (assert (every #'= array1 array2))))))))
1960 (with-test (:name (compile array bit count))
1961 (let ((fn (checked-compile '(lambda (x)
1962 (declare (type bit x))
1963 (declare (optimize speed))
1964 (let ((b (make-array 64 :element-type 'bit
1965 :initial-element 0)))
1966 (count x b))))))
1967 (assert (= (funcall fn 0) 64))
1968 (assert (= (funcall fn 1) 0))))
1970 (with-test (:name (compile simple-bit-vector equal))
1971 (let ((fn (checked-compile '(lambda (x y)
1972 (declare (type simple-bit-vector x y))
1973 (declare (optimize speed))
1974 (equal x y)))))
1975 (assert (funcall
1977 (make-array 64 :element-type 'bit :initial-element 0)
1978 (make-array 64 :element-type 'bit :initial-element 0)))
1979 (assert (not
1980 (funcall
1982 (make-array 64 :element-type 'bit :initial-element 0)
1983 (let ((b (make-array 64 :element-type 'bit :initial-element 0)))
1984 (setf (sbit b 63) 1)
1985 b))))))
1987 ;;; MISC.535: compiler failure
1988 (with-test (:name (compile :misc.535))
1989 (let ((c0 #c(4196.088977268509d0 -15943.3603515625d0)))
1990 (assert (not (funcall
1991 (checked-compile
1992 `(lambda (p1 p2)
1993 (declare (optimize speed (safety 1))
1994 (type (eql ,c0) p1)
1995 (type number p2))
1996 (eql (the (complex double-float) p1) p2)))
1997 c0 #c(12 612/979))))))
1999 ;;; reported by Lutz Euler: we shouldn't signal a compiler note for
2000 ;;; simple-bit-vector functions.
2001 (with-test (:name (compile simple-bit-vector count :should-not-compiler-note))
2002 (checked-compile '(lambda (x)
2003 (declare (type simple-bit-vector x))
2004 (count 1 x))
2005 :allow-notes nil))
2006 (with-test (:name (compile simple-bit-vector equal :should-not-compiler-note))
2007 (checked-compile '(lambda (x y)
2008 (declare (type simple-bit-vector x y))
2009 (equal x y))
2010 :allow-notes nil))
2012 ;;; MISC.550: CAST merging in IR1 finalization caused unexpected
2013 ;;; code transformations.
2014 (with-test (:name (compile :misc.550))
2015 (assert (eql (funcall
2016 (checked-compile
2017 '(lambda (p1 p2)
2018 (declare (optimize (speed 3) (safety 2) (debug 3) (space 3))
2019 (type atom p1)
2020 (type symbol p2))
2021 (or p1 (the (eql t) p2))))
2022 nil t)
2023 t)))
2025 ;;; MISC.548: type check weakening converts required type into
2026 ;;; optional
2027 (with-test (:name (compile :misc.548))
2028 (assert (eql t
2029 (funcall
2030 (checked-compile
2031 '(lambda (p1)
2032 (declare (optimize (speed 2) (safety 1) (debug 3) (space 2)))
2033 (atom (the (member f assoc-if write-line t w) p1))))
2034 t))))
2036 ;;; Free special bindings only apply to the body of the binding form, not
2037 ;;; the initialization forms.
2038 (with-test (:name (compile declare special))
2039 (assert (eq :good
2040 (funcall (checked-compile
2041 '(lambda ()
2042 (let ((x :bad))
2043 (declare (special x))
2044 (let ((x :good))
2045 ((lambda (&optional (y x))
2046 (declare (special x)) y))))))))))
2048 ;;; Bug from pfdietz's random tester: the compiler knew that IMAGPART of
2049 ;;; a rational was zero, but didn't do the substitution, leading to a
2050 ;;; crash in the ASH vop (since a shift of 57 wouldn't fit in the
2051 ;;; machine's ASH instruction's immediate field) that the compiler
2052 ;;; thought was legitimate.
2053 (with-test (:name :overlarge-immediate-in-ash-vop)
2054 (checked-compile `(lambda (b)
2055 (declare (type (integer -2 14) b))
2056 (declare (ignorable b))
2057 (ash (imagpart b) 57))))
2059 ;;; bug reported by Eduardo Mu\~noz
2060 (with-test (:name (compile vector loop))
2061 (checked-compile
2062 `(lambda (struct first)
2063 (declare (optimize speed))
2064 (let* ((nodes (nodes struct))
2065 (bars (bars struct))
2066 (length (length nodes))
2067 (new (make-array length :fill-pointer 0)))
2068 (vector-push first new)
2069 (loop with i fixnum = 0
2070 for newl fixnum = (length new)
2071 while (< newl length) do
2072 (let ((oldl (length new)))
2073 (loop for j fixnum from i below newl do
2074 (dolist (n (node-neighbours (aref new j) bars))
2075 (unless (find n new)
2076 (vector-push n new))))
2077 (setq i oldl)))
2078 new))
2079 :allow-style-warnings t))
2081 ;;; bug #389: "0.0 can't be converted to type NIL." (Brian Rowe
2082 ;;; sbcl-devel)
2083 (with-test (:name (compile float :bug-389))
2084 (checked-compile `(lambda (x y a b c)
2085 (- y (* (signum x) (sqrt (abs (- (* b x) c))))))
2086 :allow-style-warnings t))
2088 ;;; Type inference from CHECK-TYPE
2089 (with-test (:name (compile check-type :type-inference))
2090 (let ((notes (nth-value
2091 4 (checked-compile '(lambda (x)
2092 (declare (optimize (speed 3)))
2093 (1+ x))))))
2094 ;; forced-to-do GENERIC-+, etc, possible word -> bignum conversion note
2095 (assert (> (length notes) 1)))
2097 (let ((notes (nth-value
2098 4 (checked-compile '(lambda (x)
2099 (declare (optimize (speed 3)))
2100 (check-type x fixnum)
2101 (1+ x))))))
2102 ;; Only the posssible word -> bignum conversion note
2103 (assert (= (length notes) 1))))
2105 ;;; Up to 0.9.8.22 x86-64 had broken return value handling in the
2106 ;;; %SET-SAP-REF-DOUBLE/SINGLE VOPs.
2107 (with-test (:name :sap-ref-float)
2108 (checked-compile '(lambda (sap)
2109 (let ((x (setf (sb-vm::sap-ref-double sap 0) 1d0)))
2110 (1+ x))))
2111 (checked-compile '(lambda (sap)
2112 (let ((x (setf (sb-vm::sap-ref-single sap 0) 1f0)))
2113 (1+ x)))))
2115 ;;; bug #399
2116 (with-test (:name :string-union-types)
2117 (checked-compile '(lambda (x)
2118 (declare (type (or (simple-array character (6))
2119 (simple-array character (5))) x))
2120 (aref x 0))))
2122 ;;; MISC.623: missing functions for constant-folding
2123 (with-test (:name (compile :constant-folding :missing-functions :misc.623))
2124 (assert (eql 0
2125 (funcall
2126 (checked-compile
2127 '(lambda ()
2128 (declare (optimize (space 2) (speed 0) (debug 2)
2129 (compilation-speed 3) (safety 0)))
2130 (loop for lv3 below 1
2131 count (minusp
2132 (loop for lv2 below 2
2133 count (logbitp 0
2134 (bit #*1001101001001
2135 (min 12 (max 0 lv3)))))))))))))
2137 ;;; MISC.624: erroneous AVER in x86's %LOGBITP VOPs
2138 (with-test (:name (compile :%logbitp-vops :misc.624))
2139 (assert (eql 0
2140 (funcall
2141 (checked-compile
2142 '(lambda (a)
2143 (declare (type (integer 21 28) a))
2144 (declare (optimize (compilation-speed 1) (safety 2)
2145 (speed 0) (debug 0) (space 1)))
2146 (let* ((v7 (flet ((%f3 (f3-1 f3-2)
2147 (loop for lv2 below 1
2148 count
2149 (logbitp 29
2150 (sbit #*10101111
2151 (min 7 (max 0 (eval '0))))))))
2152 (%f3 0 a))))
2154 :allow-style-warnings t)
2155 22))))
2157 ;;; MISC.626: bandaged AVER was still wrong
2158 (with-test (:name (compile logbitp :misc.626))
2159 (assert (eql -829253
2160 (funcall
2161 (checked-compile
2162 '(lambda (a)
2163 (declare (type (integer -902970 2) a))
2164 (declare (optimize (space 2) (debug 0) (compilation-speed 1)
2165 (speed 0) (safety 3)))
2166 (prog2 (if (logbitp 30 a) 0 (block b3 0)) a)))
2167 -829253))))
2169 ;; MISC.628: constant-folding %LOGBITP was buggy
2170 (with-test (:name (compile logbitp :constant-folding :misc.628))
2171 (assert (eql t
2172 (funcall
2173 (checked-compile
2174 `(lambda ()
2175 (declare (optimize (safety 3) (space 3) (compilation-speed 3)
2176 (speed 0) (debug 1)))
2177 (not (not (logbitp 0 (floor 2147483651 (min -23 0)))))))))))
2179 ;; mistyping found by random-tester
2180 (with-test (:name (compile :type-derivation))
2181 (assert (zerop
2182 (funcall
2183 (checked-compile
2184 `(lambda ()
2185 (declare (optimize (speed 1) (debug 0)
2186 (space 2) (safety 0) (compilation-speed 0)))
2187 (unwind-protect 0
2188 (* (/ (multiple-value-prog1 -29457482 -5602513511) 1)))))))))
2190 ;; aggressive constant folding (bug #400)
2191 (with-test (:name (compile :aggressive-constant-folding :bug-400))
2192 (assert
2193 (eq t (funcall (checked-compile `(lambda () (or t (the integer (/ 1 0)))))))))
2195 (with-test (:name (:compiler :constraint-propagation :var-eql-to-non-var-1))
2196 (checked-compile `(lambda (x y)
2197 (when (eql x (length y))
2198 (locally
2199 (declare (optimize (speed 3)))
2200 (1+ x))))
2201 :allow-notes '(not compiler-note)))
2203 (with-test (:name (:compiler :constraint-propagation :var-eql-to-non-var-2))
2204 (checked-compile `(lambda (x y)
2205 (when (eql (length y) x)
2206 (locally
2207 (declare (optimize (speed 3)))
2208 (1+ x))))
2209 :allow-notes '(not compiler-note)))
2211 (with-test (:name (:compiler :constraint-propagation :float-bounds-1))
2212 (checked-compile `(lambda (x)
2213 (declare (type (single-float * (3.0)) x))
2214 (when (<= x 2.0)
2215 (when (<= 2.0 x)
2216 x)))
2217 :allow-notes '(not compiler-note)))
2219 (defun assert-code-deletion-note (lambda &optional (howmany 1))
2220 (let ((notes (nth-value
2221 4 (checked-compile lambda :allow-notes 'code-deletion-note))))
2222 (assert (= howmany (length notes)))))
2224 (with-test (:name (:compiler :constraint-propagation :float-bounds-2))
2225 (assert-code-deletion-note
2226 `(lambda (x)
2227 (declare (type single-float x))
2228 (when (< 1.0 x)
2229 (when (<= x 1.0)
2230 (error "This is unreachable."))))))
2232 (with-test (:name (:compiler :constraint-propagation :float-bounds-3
2233 :LP-894498))
2234 (assert-code-deletion-note
2235 `(lambda (x)
2236 (declare (type (single-float 0.0) x))
2237 (when (> x 0.0)
2238 (when (zerop x)
2239 (error "This is unreachable."))))))
2241 (with-test (:name (:compiler :constraint-propagation :float-bounds-4
2242 :LP-894498))
2243 (assert-code-deletion-note
2244 `(lambda (x y)
2245 (declare (type (single-float 0.0) x)
2246 (type (single-float (0.0)) y))
2247 (when (> x y)
2248 (when (zerop x)
2249 (error "This is unreachable."))))))
2251 (with-test (:name (:compiler :constraint-propagation :var-eql-to-var-1))
2252 (assert-code-deletion-note
2253 `(lambda (x y)
2254 (when (typep y 'fixnum)
2255 (when (eql x y)
2256 (unless (typep x 'fixnum)
2257 (error "This is unreachable"))
2258 (setq y nil))))))
2260 (with-test (:name (:compiler :constraint-propagation :var-eql-to-var-2))
2261 (assert-code-deletion-note
2262 `(lambda (x y)
2263 (when (typep y 'fixnum)
2264 (when (eql y x)
2265 (unless (typep x 'fixnum)
2266 (error "This is unreachable"))
2267 (setq y nil))))))
2269 ;; Reported by John Wiseman, sbcl-devel
2270 ;; Subject: [Sbcl-devel] float type derivation bug?
2271 ;; Date: Tue, 4 Apr 2006 15:28:15 -0700
2272 (with-test (:name (compile :type-derivation :float-bounds))
2273 (checked-compile
2274 `(lambda (bits)
2275 (let* ((s (if (= (ash bits -31) 0) 1 -1))
2276 (e (logand (ash bits -23) #xff))
2277 (m (if (= e 0)
2278 (ash (logand bits #x7fffff) 1)
2279 (logior (logand bits #x7fffff) #x800000))))
2280 (float (* s m (expt 2 (- e 150))))))))
2282 ;; Reported by James Knight
2283 ;; Subject: [Sbcl-devel] AVER: "(EQ (SB-NAME (SC-SB (TN-SC TN))) 'REGISTERS)"
2284 ;; Date: Fri, 24 Mar 2006 19:30:00 -0500
2285 (with-test (:name (compile logbitp :vop))
2286 (checked-compile
2287 `(lambda (days shift)
2288 (declare (type fixnum shift days))
2289 (let* ((result 0)
2290 (canonicalized-shift (+ shift 1))
2291 (first-wrapping-day (- 1 canonicalized-shift)))
2292 (declare (type fixnum result))
2293 (dotimes (source-day 7)
2294 (declare (type (integer 0 6) source-day))
2295 (when (logbitp source-day days)
2296 (setf result
2297 (logior result
2298 (the fixnum
2299 (if (< source-day first-wrapping-day)
2300 (+ source-day canonicalized-shift)
2301 (- (+ source-day
2302 canonicalized-shift)
2303 7)))))))
2304 result))))
2306 ;;; MISC.637: incorrect delaying of conversion of optional entries
2307 ;;; with hairy constant defaults
2308 (with-test (:name (compile :optional-entry :hairy-defaults :misc.637))
2309 (let ((fun (checked-compile
2310 `(lambda ()
2311 (labels ((%f11 (f11-2 &key key1)
2312 (labels ((%f8 (f8-2 &optional (f8-5 (if nil (return-from %f11 0) 0)))
2313 :bad1))
2314 (%f8 (%f8 0)))
2315 :bad2))
2316 :good)))))
2317 (assert (eq (funcall fun) :good))))
2319 ;;; MISC.555: new reference to an already-optimized local function
2320 (with-test (:name (compile :already-optimized :local-function :misc.555))
2321 (let ((fun (checked-compile
2322 `(lambda (p1)
2323 (declare (optimize (speed 1) (safety 2) (debug 2) (space 0))
2324 (type keyword p1))
2325 (keywordp p1)))))
2326 (assert (funcall fun :good))
2327 (assert-error (funcall fun 42) type-error)))
2329 ;;; Check that the compiler doesn't munge *RANDOM-STATE*.
2330 (with-test (:name (compile *random-state*))
2331 (let* ((state (make-random-state))
2332 (*random-state* (make-random-state state))
2333 (a (random most-positive-fixnum)))
2334 (setf *random-state* state)
2335 (checked-compile `(lambda (x a)
2336 (declare (single-float x)
2337 (type (simple-array double-float) a))
2338 (+ (loop for i across a
2339 summing i)
2340 x)))
2341 (assert (= a (random most-positive-fixnum)))))
2343 ;;; MISC.641: LET-conversion after physical environment analysis lost NLX-INFOs
2344 (with-test (:name (compile let :conversion :lost :nlx-infos :misc.641))
2345 (let ((fun (checked-compile
2346 `(lambda ()
2347 (declare (optimize (speed 1) (space 0) (debug 2)
2348 (compilation-speed 0) (safety 1)))
2349 (flet ((%f3 (f3-1 &key (key1 (count (floor 0 (min -74 0)) #())))
2351 (apply #'%f3 0 nil)))
2352 :allow-style-warnings t)))
2353 (assert (zerop (funcall fun)))))
2355 ;;; size mismatch: #<SB-VM::EA :DWORD base=#<SB-C:TN t1[RDX]> disp=1> is a :DWORD and #<SB-C:TN t2[RAX]> is a :QWORD. on x86-64
2356 (with-test (:name (compile make-array aref :size-mismatch))
2357 (checked-compile `(lambda ()
2358 (let ((x (make-array '(1) :element-type '(signed-byte 32))))
2359 (setf (aref x 0) 1)))))
2361 ;;; step instrumentation confusing the compiler, reported by Faré
2362 (with-test (:name (compile step))
2363 (checked-compile `(lambda ()
2364 (declare (optimize (debug 2))) ; not debug 3!
2365 (let ((val "foobar"))
2366 (map-into (make-array (list (length val))
2367 :element-type '(unsigned-byte 8))
2368 #'char-code val)))))
2370 ;;; overconfident primitive type computation leading to bogus type
2371 ;;; checking.
2372 (with-test (:name (compile :primitive-type standard-object condition function))
2373 (flet ((test-case/incompatible (type1 type2 object1 object2)
2374 (declare (ignore object1 object2))
2375 (multiple-value-bind (fun failure-p warnings)
2376 (checked-compile
2377 `(lambda (x)
2378 (declare (type (and ,type1 ,type2) x))
2380 :allow-failure t :allow-warnings t)
2381 (declare (ignore fun))
2382 (assert failure-p)
2383 (assert (= (length warnings) 1))
2384 ;; FIXME (declare (type <equivalent-to-empty-type> x)) is
2385 ;; currently dropped instead of compiled into a type
2386 ;; check.
2387 ;; (assert-error (funcall fun object1) type-error)
2388 ;; (assert-error (funcall fun object2) type-error)
2390 (test-case/compatible (type1 type2 object1 object2)
2391 (let ((fun (checked-compile
2392 `(lambda (x)
2393 (declare (type (and ,type1 ,type2) x))
2394 x))))
2395 (when (typep object1 type2)
2396 (assert (typep (funcall fun object1) type1)))
2397 (when (typep object2 type1)
2398 (assert (typep (funcall fun object2) type2))))))
2399 ;; TODO Add structure classes, SEQUENCE and EXTENDED-SEQUENCE
2400 (let ((types `((condition . ,(make-condition 'error))
2401 (sb-kernel:funcallable-instance . ,#'print-object)
2402 (function . ,#'identity)
2403 (sb-kernel:instance . ,(find-class 'class))
2404 (standard-object . ,(find-class 'class))))
2405 (compatible '((sb-kernel:instance . condition)
2406 (sb-kernel:instance . standard-object)
2407 (sb-kernel:funcallable-instance . function)
2408 (sb-kernel:funcallable-instance . standard-object)
2409 (function . standard-object))))
2410 (loop :for (type1 . object1) :in types :do
2411 (loop :for (type2 . object2) :in types :do
2412 (funcall
2413 (if (or (eq type1 type2)
2414 (find-if (lambda (cell)
2415 (or (and (eq type1 (car cell))
2416 (eq type2 (cdr cell)))
2417 (and (eq type2 (car cell))
2418 (eq type1 (cdr cell)))))
2419 compatible))
2420 #'test-case/compatible
2421 #'test-case/incompatible)
2422 type1 type2 object1 object2))))))
2424 ;;; VALUES declaration: while the declaration is a non-standard and
2425 ;;; possibly a non-conforming extension, as long as we do support it,
2426 ;;; we might as well get it right.
2428 ;;; The first of the following two tests originally asserted that the
2429 ;;; declaration _was_ allowed in a LET* form (The test was originally
2430 ;;; added in reaction to a bug reported by Kaersten Poeck on
2431 ;;; sbcl-devel 20061023). After commit
2432 ;;; 498e00334f2b1ba87c3edd557bbce4247977a11d, the declaration is
2433 ;;; accepted in LAMBDA but not LET*. The current form of the tests
2434 ;;; reflects this.
2435 (with-test (:name (compile let* declare values))
2436 (multiple-value-bind (fun failure-p warnings)
2437 (checked-compile '(lambda () (let* () (declare (values list))))
2438 :allow-warnings t)
2439 (declare (ignore fun failure-p))
2440 (assert (= (length warnings) 1))))
2442 (with-test (:name (compile lambda declare values))
2443 (let ((fun (checked-compile '(lambda (x) (declare (values list)) x))))
2444 (assert (equal (sb-impl::%fun-type fun)
2445 '(function (t) (values list &optional))))))
2447 ;;; test for some problems with too large immediates in x86-64 modular
2448 ;;; arithmetic vops
2449 (with-test (:name (compile :modular-arithmetic-vops))
2450 (checked-compile
2451 '(lambda (x) (declare (fixnum x))
2452 (logand most-positive-fixnum (logxor x most-positive-fixnum))))
2454 (checked-compile
2455 '(lambda (x) (declare (fixnum x))
2456 (logand most-positive-fixnum (+ x most-positive-fixnum))))
2458 (checked-compile
2459 '(lambda (x) (declare (fixnum x))
2460 (logand most-positive-fixnum (* x most-positive-fixnum)))))
2462 ;;; bug 256.b
2463 (with-test (:name :propagate-type-through-error-and-binding)
2464 (assert (nth-value
2465 2 (checked-compile '(lambda (x)
2466 (list (let ((y (the real x)))
2467 (unless (floatp y) (error ""))
2469 (integer-length x)))
2470 :allow-warnings 'sb-int:type-warning))))
2472 ;; Dead / in safe code
2473 (with-test (:name (compile / :dead :safe))
2474 (assert-error (funcall (checked-compile
2475 '(lambda (x y)
2476 (declare (optimize (safety 3)))
2477 (/ x y)
2478 (+ x y)))
2481 division-by-zero))
2483 ;;; Dead unbound variable (bug 412)
2484 (with-test (:name (compile :dead-unbound :bug-412))
2485 (assert-error
2486 (funcall (checked-compile '(lambda ()
2487 #:unbound
2489 :allow-warnings t))
2490 unbound-variable))
2492 ;;; No compiler notes from compiling SUBSEQ SIMPLE-VECTOR.
2493 (with-test (:name (compile subseq simple-vector :no-notes))
2494 (assert
2495 (equalp #(2 3)
2496 (funcall (checked-compile
2497 `(lambda (s p e)
2498 (declare (optimize speed)
2499 (simple-vector s))
2500 (subseq s p e))
2501 :allow-notes nil)
2502 (vector 1 2 3 4)
2504 3))))
2506 ;;; No compiler notes from compiling COPY-SEQ SIMPLE-VECTOR.
2507 (with-test (:name (compile copy-seq simple-bit-vector :if-input-does-not-exist))
2508 (assert
2509 (equalp #(1 2 3 4)
2510 (funcall (checked-compile
2511 `(lambda (s)
2512 (declare (optimize speed)
2513 (simple-vector s))
2514 (copy-seq s))
2515 :allow-notes nil)
2516 (vector 1 2 3 4)))))
2518 ;;; bug in adding DATA-VECTOR-REF-WITH-OFFSET to x86-64
2519 (with-test (:name (mismatch :data-vector-ref-with-offset))
2520 (assert (not (mismatch #(1.0f0 2.0f0)
2521 (make-array 2 :element-type 'single-float
2522 :initial-contents (list 1.0f0 2.0f0))))))
2524 ;;; bug in interval-arithmetic used by the compiler: needless attempt to coerce too
2525 ;;; large bignums to floats
2526 (with-test (:name (compile * / + - :interval-arithmetic))
2527 (dolist (op '(* / + -))
2528 (let ((fun (checked-compile
2529 `(lambda (x)
2530 (declare (type (integer 0 #.(* 2 (truncate most-positive-double-float))) x))
2531 (,op 0.0d0 x)))))
2532 (loop repeat 10
2533 do (let ((arg (random (truncate most-positive-double-float))))
2534 (assert (eql (funcall fun arg)
2535 (funcall op 0.0d0 arg))))))))
2537 (with-test (:name (compile :high-debug-known-function-inlining))
2538 (funcall (checked-compile
2539 '(lambda ()
2540 (declare (optimize (debug 3)) (inline append))
2541 (let ((fun (lambda (body)
2542 (append
2543 (first body)
2544 nil))))
2545 (funcall fun '((foo (bar)))))))))
2547 (with-test (:name (compile :high-debug-known-function-transform-with-optional-arguments))
2548 (checked-compile '(lambda (x y)
2549 (declare (optimize sb-c::preserve-single-use-debug-variables))
2550 (if (block nil
2551 (some-unknown-function
2552 (lambda ()
2553 (return (member x y))))
2556 (error "~a" y)))
2557 :allow-style-warnings t))
2559 ;;; Compiling W-P-O when the pinned objects are known to be fixnums
2560 ;;; or characters.
2561 (with-test (:name (compile sb-sys:with-pinned-objects :known-type fixnum character))
2562 (checked-compile '(lambda (x y)
2563 (declare (fixnum y) (character x))
2564 (sb-sys:with-pinned-objects (x y)
2565 (some-random-function)))
2566 :allow-style-warnings t))
2568 ;;; *CHECK-CONSISTENCY* and TRULY-THE
2570 (with-test (:name (compile :bug-423))
2571 (let ((sb-c::*check-consistency* t))
2572 (flet ((make-lambda (type)
2573 `(lambda (x)
2574 ((lambda (z)
2575 (if (listp z)
2576 (let ((q (truly-the list z)))
2577 (length q))
2578 (if (arrayp z)
2579 (let ((q (truly-the vector z)))
2580 (length q))
2581 (error "oops"))))
2582 (the ,type x)))))
2583 (checked-compile (make-lambda 'list))
2584 (checked-compile (make-lambda 'vector)))))
2586 ;;; this caused a momentary regression when an ill-adviced fix to
2587 ;;; bug 427 made ANY-REG suitable for primitive-type T:
2589 ;;; no :MOVE-ARG VOP defined to move #<SB-C:TN t1> (SC SB-VM::SINGLE-REG) to #<SB-C:TN t2> (SC SB-VM::ANY-REG)
2590 ;;; [Condition of type SIMPLE-ERROR]
2591 (with-test (:name (compile :bug-427))
2592 (checked-compile
2593 '(lambda (frob)
2594 (labels
2595 ((%zig (frob)
2596 (typecase frob
2597 (double-float
2598 (setf (sb-alien:deref (sb-alien:cast (sb-alien:sap-alien (unknown1) (* unsigned-char))
2599 (* double-float))) frob))
2600 (hash-table
2601 (%zig (the (values (single-float (0.0) 1.0) &optional) (unknown2)))
2602 nil))))
2603 (%zig)))
2604 :allow-style-warnings t
2605 :allow-warnings 'sb-int:local-argument-mismatch))
2607 ;;; non-required arguments in HANDLER-BIND
2608 (with-test (:name (compile handler-bind :lambda-list))
2609 (let ((fun (checked-compile
2610 '(lambda (x)
2611 (block nil
2612 (handler-bind ((error (lambda (&rest args) (return (cons :oops args)))))
2613 (/ 2 x)))))))
2614 (assert (eq :oops (car (funcall fun 0))))))
2616 ;;; NIL is a legal function name
2617 (assert (eq 'a (flet ((nil () 'a)) (nil))))
2619 ;;; misc.528
2620 (with-test (:name (compile :misc.528))
2621 (assert (null (let* ((x 296.3066f0)
2622 (y 22717067)
2623 (form `(lambda (r p2)
2624 (declare (optimize speed (safety 1))
2625 (type (simple-array single-float nil) r)
2626 (type (integer -9369756340 22717335) p2))
2627 (setf (aref r) (* ,x (the (eql 22717067) p2)))
2628 (values)))
2629 (r (make-array nil :element-type 'single-float))
2630 (expected (* x y)))
2631 (funcall (checked-compile form) r y)
2632 (let ((actual (aref r)))
2633 (unless (eql expected actual)
2634 (list expected actual)))))))
2635 ;;; misc.529
2636 (with-test (:name (compile :misc.529))
2637 (assert (null (let* ((x -2367.3296f0)
2638 (y 46790178)
2639 (form `(lambda (r p2)
2640 (declare (optimize speed (safety 1))
2641 (type (simple-array single-float nil) r)
2642 (type (eql 46790178) p2))
2643 (setf (aref r) (+ ,x (the (integer 45893897) p2)))
2644 (values)))
2645 (r (make-array nil :element-type 'single-float))
2646 (expected (+ x y)))
2647 (funcall (checked-compile form) r y)
2648 (let ((actual (aref r)))
2649 (unless (eql expected actual)
2650 (list expected actual)))))))
2652 ;;; misc.556
2653 (with-test (:name (compile :misc.556))
2654 (assert (eql -1
2655 (funcall
2656 (checked-compile
2657 '(lambda (p1 p2)
2658 (declare
2659 (optimize (speed 1) (safety 0)
2660 (debug 0) (space 0))
2661 (type (member 8174.8604) p1)
2662 (type (member -95195347) p2))
2663 (floor p1 p2)))
2664 8174.8604 -95195347))))
2666 ;;; misc.557
2667 (with-test (:name (compile :misc.557))
2668 (assert (eql -1
2669 (funcall
2670 (checked-compile
2671 '(lambda (p1)
2672 (declare (optimize (speed 3) (safety 0) (debug 3) (space 1))
2673 (type (member -94430.086f0) p1))
2674 (floor (the single-float p1) 19311235)))
2675 -94430.086f0))))
2677 ;;; misc.558
2678 (with-test (:name (compile :misc.558))
2679 (assert (eql -1.0f0
2680 (funcall
2681 (checked-compile
2682 '(lambda (p1)
2683 (declare (optimize (speed 1) (safety 2)
2684 (debug 2) (space 3))
2685 (type (eql -39466.56f0) p1))
2686 (ffloor p1 305598613)))
2687 -39466.56f0))))
2689 ;;; misc.559
2690 (with-test (:name (compile :misc.559))
2691 (assert (eql 1
2692 (funcall
2693 (checked-compile
2694 '(lambda (p1)
2695 (declare (optimize (speed 1) (safety 1) (debug 1) (space 2))
2696 (type (eql -83232.09f0) p1))
2697 (ceiling p1 -83381228)))
2698 -83232.09f0))))
2700 ;;; misc.560
2701 (with-test (:name (compile :misc.560))
2702 (assert (eql 1
2703 (funcall
2704 (checked-compile
2705 '(lambda (p1)
2706 (declare (optimize (speed 1) (safety 1)
2707 (debug 1) (space 0))
2708 (type (member -66414.414f0) p1))
2709 (ceiling p1 -63019173f0)))
2710 -66414.414f0))))
2712 ;;; misc.561
2713 (with-test (:name (compile :misc.561))
2714 (assert (eql 1.0f0
2715 (funcall
2716 (checked-compile
2717 '(lambda (p1)
2718 (declare (optimize (speed 0) (safety 1)
2719 (debug 0) (space 1))
2720 (type (eql 20851.398f0) p1))
2721 (fceiling p1 80839863)))
2722 20851.398f0))))
2724 ;;; misc.581
2725 (with-test (:name (compile :misc.581))
2726 (assert (floatp
2727 (funcall
2728 (checked-compile '(lambda (x)
2729 (declare (type (eql -5067.2056) x))
2730 (+ 213734822 x)))
2731 -5067.2056))))
2733 ;;; misc.581a
2734 (with-test (:name (compile :misc.581a))
2735 (assert (typep
2736 (funcall
2737 (checked-compile '(lambda (x) (declare (type (eql -1.0) x))
2738 (+ #x1000001 x)))
2739 -1.0f0)
2740 'single-float)))
2742 ;;; misc.582
2743 (with-test (:name (compile :misc.582))
2744 (assert (plusp (funcall
2745 (checked-compile
2746 '(lambda (p1)
2747 (declare (optimize (speed 0) (safety 1) (debug 1) (space 1))
2748 (type (eql -39887.645) p1))
2749 (mod p1 382352925)))
2750 -39887.645))))
2752 ;;; misc.587
2753 (with-test (:name (compile :misc.587))
2754 (assert (let ((result (funcall
2755 (checked-compile
2756 '(lambda (p2)
2757 (declare (optimize (speed 0) (safety 3) (debug 1) (space 0))
2758 (type (eql 33558541) p2))
2759 (- 92215.266 p2)))
2760 33558541)))
2761 (typep result 'single-float))))
2763 ;;; misc.635
2764 (with-test (:name (compile :misc.635))
2765 (assert (eql 1
2766 (let* ((form '(lambda (p2)
2767 (declare (optimize (speed 0) (safety 1)
2768 (debug 2) (space 2))
2769 (type (member -19261719) p2))
2770 (ceiling -46022.094 p2))))
2771 (values (funcall (checked-compile form) -19261719))))))
2773 ;;; misc.636
2774 (with-test (:name (compile :misc.636))
2775 (assert (let* ((x 26899.875)
2776 (form `(lambda (p2)
2777 (declare (optimize (speed 3) (safety 1) (debug 3) (space 1))
2778 (type (member ,x #:g5437 char-code #:g5438) p2))
2779 (* 104102267 p2))))
2780 (floatp (funcall (checked-compile form) x)))))
2782 ;;; misc.622
2783 (with-test (:name (compile :misc.622))
2784 (assert (eql
2785 (funcall
2786 (checked-compile
2787 '(lambda (p2)
2788 (declare (optimize (speed 3) (safety 2) (debug 3) (space 0))
2789 (type real p2))
2790 (+ 81535869 (the (member 17549.955 #:g35917) p2))))
2791 17549.955)
2792 (+ 81535869 17549.955))))
2794 ;;; misc.654
2795 (with-test (:name (compile :misc.654))
2796 (assert (eql 2
2797 (let ((form '(lambda (p2)
2798 (declare (optimize (speed 0) (safety 2) (debug 0) (space 2))
2799 (type (member integer eql) p2))
2800 (coerce 2 p2))))
2801 (funcall (checked-compile form) 'integer)))))
2803 ;;; misc.656
2804 (with-test (:name (compile :misc.656))
2805 (assert (eql 2
2806 (let ((form '(lambda (p2)
2807 (declare (optimize (speed 0) (safety 2) (debug 0) (space 2))
2808 (type (member integer mod) p2))
2809 (coerce 2 p2))))
2810 (funcall (checked-compile form) 'integer)))))
2812 ;;; misc.657
2813 (with-test (:name (compile :misc.657))
2814 (assert (eql 2
2815 (let ((form '(lambda (p2)
2816 (declare (optimize (speed 0) (safety 2) (debug 0) (space 2))
2817 (type (member integer values) p2))
2818 (coerce 2 p2))))
2819 (funcall (checked-compile form) 'integer)))))
2821 (with-test (:name (compile aref string :derive-type))
2822 (assert (eq 'character
2823 (funcall (checked-compile
2824 '(lambda (s)
2825 (ctu:compiler-derived-type (aref (the string s) 0))))
2826 "foo"))))
2828 (with-test (:name (compile aref base-string :derive-type))
2829 (assert (eq #+sb-unicode 'base-char
2830 #-sb-unicode 'character
2831 (funcall (checked-compile
2832 '(lambda (s)
2833 (ctu:compiler-derived-type (aref (the base-string s) 0))))
2834 (coerce "foo" 'base-string)))))
2836 (with-test (:name (compile dolist :constant :derive-type))
2837 (assert (equal '(integer 1 3)
2838 (funcall (checked-compile
2839 '(lambda (x)
2840 (dolist (y '(1 2 3))
2841 (when x
2842 (return (ctu:compiler-derived-type y))))))
2843 t))))
2845 (with-test (:name (compile dolist :simple list :derive-type))
2846 (assert (equal '(integer 1 3)
2847 (funcall (checked-compile
2848 '(lambda (x)
2849 (dolist (y (list 1 2 3))
2850 (when x
2851 (return (ctu:compiler-derived-type y))))))
2852 t))))
2854 (with-test (:name (compile dolist :dotted-constant-list :derive-type))
2855 (multiple-value-bind (fun failure-p warnings style-warnings)
2856 (checked-compile
2857 '(lambda (x)
2858 (dolist (y '(1 2 3 . 4) :foo)
2859 (when x
2860 (return (ctu:compiler-derived-type y)))))
2861 :allow-style-warnings t)
2862 (declare (ignore failure-p warnings))
2863 (assert (= 1 (length style-warnings)))
2864 (assert (equal '(integer 1 3) (funcall fun t)))
2865 (assert-error (funcall fun nil) type-error)))
2867 (with-test (:name (compile destructuring-bind :constant list))
2868 (assert (= 10
2869 (funcall
2870 (checked-compile
2871 '(lambda ()
2872 (destructuring-bind (a (b c) d) '(1 (2 3) 4)
2873 (+ a b c d)))
2874 :allow-notes nil))))
2875 (assert (eq :feh
2876 (funcall
2877 (checked-compile
2878 '(lambda (x)
2879 (or x
2880 (destructuring-bind (a (b c) d) '(1 "foo" 4)
2881 (+ a b c d))))
2882 :allow-notes nil)
2883 :feh))))
2885 ;;; Functions with non-required arguments used to end up with
2886 ;;; (&OPTIONAL-DISPATCH ...) as their names.
2887 (with-test (:name :hairy-function-name)
2888 (assert (eq 'read-line (nth-value 2 (function-lambda-expression #'read-line))))
2889 (assert (equal "#<FUNCTION READ-LINE>" (princ-to-string #'read-line))))
2891 ;;; PROGV + RESTRICT-COMPILER-POLICY
2892 ;; META: there's a test in compiler.impure.lisp that also tests
2893 ;; interaction of PROGV with (debug 3). These tests should be together.
2894 (with-test (:name (compile progv sb-ext:restrict-compiler-policy))
2895 (let ((sb-c::*policy-min* sb-c::*policy-min*)
2896 (sb-c::*policy-max* sb-c::*policy-max*))
2897 (restrict-compiler-policy 'debug 3)
2898 (let ((fun (checked-compile
2899 '(lambda (x)
2900 (let ((i x))
2901 (declare (special i))
2902 (list i
2903 (progv '(i) (list (+ i 1))
2905 i))))))
2906 (assert (equal '(1 2 1) (funcall fun 1))))))
2908 ;;; It used to be possible to confuse the compiler into
2909 ;;; IR2-converting such a call to CONS
2910 (with-test (:name (compile :late-bound-primitive))
2911 (checked-compile `(lambda ()
2912 (funcall 'cons 1))
2913 :allow-warnings t))
2915 (with-test (:name (compile :hairy-array-element-type-derivation))
2916 (checked-compile
2917 '(lambda (x)
2918 (declare (type (and simple-string (satisfies array-has-fill-pointer-p)) x))
2919 (array-element-type x))))
2921 (with-test (:name (compile &rest :derive-type 1))
2922 (multiple-value-bind (type derivedp)
2923 (funcall (checked-compile `(lambda (&rest args)
2924 (ctu:compiler-derived-type args)))
2925 nil)
2926 (assert (eq 'list type))
2927 (assert derivedp)))
2929 (with-test (:name (compile &rest :derive-type 2))
2930 (multiple-value-bind (type derivedp)
2931 (funcall (funcall (checked-compile `
2932 (lambda ()
2933 (lambda (&rest args)
2934 (ctu:compiler-derived-type args))))))
2935 (assert (eq 'list type))
2936 (assert derivedp)))
2938 (with-test (:name (compile &rest :derive-type 3))
2939 (multiple-value-bind (type derivedp)
2940 (funcall (funcall (checked-compile
2941 `(lambda ()
2942 (lambda (&optional x &rest args)
2943 (unless x (error "oops"))
2944 (ctu:compiler-derived-type args)))))
2946 (assert (eq 'list type))
2947 (assert derivedp)))
2949 (with-test (:name (compile &rest :derive-type 4))
2950 (multiple-value-bind (type derivedp)
2951 (funcall (funcall (checked-compile
2952 `(lambda ()
2953 (lambda (&optional x &rest args)
2954 (declare (type (or null integer) x))
2955 (when x (setf args x))
2956 (ctu:compiler-derived-type args)))))
2958 (assert (equal '(or cons null integer) type))
2959 (assert derivedp)))
2961 (with-test (:name (compile base-char typep :elimination))
2962 (assert (eq (funcall (checked-compile
2963 `(lambda (ch)
2964 (declare (type base-char ch) (optimize (speed 3) (safety 0)))
2965 (typep ch 'base-char)))
2967 t)))
2969 (with-test (:name :regression-1.0.24.37)
2970 (checked-compile `(lambda (&key (test (constantly t)))
2971 (when (funcall test)
2972 :quux))))
2974 ;;; Attempt to test a decent cross section of conditions
2975 ;;; and values types to move conditionally.
2976 (macrolet
2977 ((test-comparison (comparator type x y)
2978 `(progn
2979 ,@(loop for (result-type a b)
2980 in '((nil t nil)
2981 (nil 0 1)
2982 (nil 0.0 1.0)
2983 (nil 0d0 0d0)
2984 (nil 0.0 0d0)
2985 (nil #c(1.0 1.0) #c(2.0 2.0))
2987 (t t nil)
2988 (fixnum 0 1)
2989 ((unsigned-byte #.sb-vm:n-word-bits)
2990 (1+ most-positive-fixnum)
2991 (+ 2 most-positive-fixnum))
2992 ((signed-byte #.sb-vm:n-word-bits)
2993 -1 (* 2 most-negative-fixnum))
2994 (single-float 0.0 1.0)
2995 (double-float 0d0 1d0))
2996 for lambda = (if result-type
2997 `(lambda (x y a b)
2998 (declare (,type x y)
2999 (,result-type a b))
3000 (if (,comparator x y)
3001 a b))
3002 `(lambda (x y)
3003 (declare (,type x y))
3004 (if (,comparator x y)
3005 ,a ,b)))
3006 for args = `(,x ,y ,@(and result-type
3007 `(,a ,b)))
3008 collect
3009 `(progn
3010 (eql (funcall (checked-compile ',lambda)
3011 ,@args)
3012 (eval '(,lambda ,@args))))))))
3013 (sb-vm::with-float-traps-masked
3014 (:divide-by-zero :overflow :inexact :invalid)
3015 (let (#+sb-eval (sb-ext:*evaluator-mode* :interpret))
3016 (declare (sb-ext:muffle-conditions style-warning))
3017 (test-comparison eql t t nil)
3018 (test-comparison eql t t t)
3020 (test-comparison = t 1 0)
3021 (test-comparison = t 1 1)
3022 (test-comparison = t (1+ most-positive-fixnum) (+ 2 most-positive-fixnum))
3023 (test-comparison = fixnum 1 0)
3024 (test-comparison = fixnum 0 0)
3025 (test-comparison = (unsigned-byte #.sb-vm:n-word-bits) 1 0)
3026 (test-comparison = (unsigned-byte #.sb-vm:n-word-bits) 0 0)
3027 (test-comparison = (signed-byte #.sb-vm:n-word-bits) 1 0)
3028 (test-comparison = (signed-byte #.sb-vm:n-word-bits) 1 1)
3030 (test-comparison = single-float 0.0 1.0)
3031 (test-comparison = single-float 1.0 1.0)
3032 (test-comparison = single-float (/ 1.0 0.0) (/ 1.0 0.0))
3033 (test-comparison = single-float (/ 1.0 0.0) 1.0)
3034 (test-comparison = single-float (/ 0.0 0.0) (/ 0.0 0.0))
3035 (test-comparison = single-float (/ 0.0 0.0) 0.0)
3037 (test-comparison = double-float 0d0 1d0)
3038 (test-comparison = double-float 1d0 1d0)
3039 (test-comparison = double-float (/ 1d0 0d0) (/ 1d0 0d0))
3040 (test-comparison = double-float (/ 1d0 0d0) 1d0)
3041 (test-comparison = double-float (/ 0d0 0d0) (/ 0d0 0d0))
3042 (test-comparison = double-float (/ 0d0 0d0) 0d0)
3044 (test-comparison < t 1 0)
3045 (test-comparison < t 0 1)
3046 (test-comparison < t 1 1)
3047 (test-comparison < t (1+ most-positive-fixnum) (+ 2 most-positive-fixnum))
3048 (test-comparison < t (+ 2 most-positive-fixnum) (1+ most-positive-fixnum))
3049 (test-comparison < fixnum 1 0)
3050 (test-comparison < fixnum 0 1)
3051 (test-comparison < fixnum 0 0)
3052 (test-comparison < (unsigned-byte #.sb-vm:n-word-bits) 1 0)
3053 (test-comparison < (unsigned-byte #.sb-vm:n-word-bits) 0 1)
3054 (test-comparison < (unsigned-byte #.sb-vm:n-word-bits) 0 0)
3055 (test-comparison < (signed-byte #.sb-vm:n-word-bits) 1 0)
3056 (test-comparison < (signed-byte #.sb-vm:n-word-bits) 0 1)
3057 (test-comparison < (signed-byte #.sb-vm:n-word-bits) 1 1)
3059 (test-comparison < single-float 0.0 1.0)
3060 (test-comparison < single-float 1.0 0.0)
3061 (test-comparison < single-float 1.0 1.0)
3062 (test-comparison < single-float (/ 1.0 0.0) (/ 1.0 0.0))
3063 (test-comparison < single-float (/ 1.0 0.0) 1.0)
3064 (test-comparison < single-float 1.0 (/ 1.0 0.0))
3065 (test-comparison < single-float (/ 0.0 0.0) (/ 0.0 0.0))
3066 (test-comparison < single-float (/ 0.0 0.0) 0.0)
3068 (test-comparison < double-float 0d0 1d0)
3069 (test-comparison < double-float 1d0 0d0)
3070 (test-comparison < double-float 1d0 1d0)
3071 (test-comparison < double-float (/ 1d0 0d0) (/ 1d0 0d0))
3072 (test-comparison < double-float (/ 1d0 0d0) 1d0)
3073 (test-comparison < double-float 1d0 (/ 1d0 0d0))
3074 (test-comparison < double-float (/ 0d0 0d0) (/ 0d0 0d0))
3075 (test-comparison < double-float (/ 0d0 0d0) 0d0)
3076 (test-comparison < double-float 0d0 (/ 0d0 0d0))
3078 (test-comparison > t 1 0)
3079 (test-comparison > t 0 1)
3080 (test-comparison > t 1 1)
3081 (test-comparison > t (1+ most-positive-fixnum) (+ 2 most-positive-fixnum))
3082 (test-comparison > t (+ 2 most-positive-fixnum) (1+ most-positive-fixnum))
3083 (test-comparison > fixnum 1 0)
3084 (test-comparison > fixnum 0 1)
3085 (test-comparison > fixnum 0 0)
3086 (test-comparison > (unsigned-byte #.sb-vm:n-word-bits) 1 0)
3087 (test-comparison > (unsigned-byte #.sb-vm:n-word-bits) 0 1)
3088 (test-comparison > (unsigned-byte #.sb-vm:n-word-bits) 0 0)
3089 (test-comparison > (signed-byte #.sb-vm:n-word-bits) 1 0)
3090 (test-comparison > (signed-byte #.sb-vm:n-word-bits) 0 1)
3091 (test-comparison > (signed-byte #.sb-vm:n-word-bits) 1 1)
3093 (test-comparison > single-float 0.0 1.0)
3094 (test-comparison > single-float 1.0 0.0)
3095 (test-comparison > single-float 1.0 1.0)
3096 (test-comparison > single-float (/ 1.0 0.0) (/ 1.0 0.0))
3097 (test-comparison > single-float (/ 1.0 0.0) 1.0)
3098 (test-comparison > single-float 1.0 (/ 1.0 0.0))
3099 (test-comparison > single-float (/ 0.0 0.0) (/ 0.0 0.0))
3100 (test-comparison > single-float (/ 0.0 0.0) 0.0)
3102 (test-comparison > double-float 0d0 1d0)
3103 (test-comparison > double-float 1d0 0d0)
3104 (test-comparison > double-float 1d0 1d0)
3105 (test-comparison > double-float (/ 1d0 0d0) (/ 1d0 0d0))
3106 (test-comparison > double-float (/ 1d0 0d0) 1d0)
3107 (test-comparison > double-float 1d0 (/ 1d0 0d0))
3108 (test-comparison > double-float (/ 0d0 0d0) (/ 0d0 0d0))
3109 (test-comparison > double-float (/ 0d0 0d0) 0d0)
3110 (test-comparison > double-float 0d0 (/ 0d0 0d0)))))
3112 (with-test (:name :car-and-cdr-type-derivation-conservative)
3113 (let ((f1 (checked-compile
3114 `(lambda (y)
3115 (declare (optimize speed))
3116 (let ((x (the (cons fixnum fixnum) (cons 1 2))))
3117 (declare (type (cons t fixnum) x))
3118 (rplaca x y)
3119 (+ (car x) (cdr x))))))
3120 (f2 (checked-compile
3121 `(lambda (y)
3122 (declare (optimize speed))
3123 (let ((x (the (cons fixnum fixnum) (cons 1 2))))
3124 (setf (cdr x) y)
3125 (+ (car x) (cdr x)))))))
3126 (flet ((test-error (e value)
3127 (assert (typep e 'type-error))
3128 (assert (eq 'number (type-error-expected-type e)))
3129 (assert (eq value (type-error-datum e)))))
3130 (let ((v1 "foo")
3131 (v2 "bar"))
3132 (multiple-value-bind (res err) (ignore-errors (funcall f1 v1))
3133 (assert (not res))
3134 (test-error err v1))
3135 (multiple-value-bind (res err) (ignore-errors (funcall f2 v2))
3136 (assert (not res))
3137 (test-error err v2))))))
3139 (with-test (:name :array-dimension-derivation-conservative)
3140 (let ((f (checked-compile `(lambda (x)
3141 (declare (optimize speed))
3142 (declare (type (array * (4 4)) x))
3143 (let ((y x))
3144 (setq x (make-array '(4 4)))
3145 (adjust-array y '(3 5))
3146 (array-dimension y 0))))))
3147 (assert (= 3 (funcall f (make-array '(4 4) :adjustable t))))))
3149 (with-test (:name :with-timeout-code-deletion-note)
3150 (checked-compile `(lambda ()
3151 (sb-ext:with-timeout 0
3152 (sleep 1)))
3153 :allow-notes nil))
3155 (with-test (:name :full-warning-for-undefined-type-in-cl)
3156 (multiple-value-bind (fun failure-p warnings)
3157 (checked-compile `(lambda (x) (the replace x)) :allow-warnings t)
3158 (declare (ignore fun failure-p))
3159 (assert (= 1 (length warnings)))))
3161 (with-test (:name :single-warning-for-single-undefined-type)
3162 ;; STYLE-WARNING for symbol not in cl package.
3163 (multiple-value-bind (fun failure-p warnings style-warnings)
3164 (checked-compile `(lambda (x) (the #:no-type x))
3165 :allow-style-warnings t)
3166 (declare (ignore fun failure-p warnings))
3167 (assert (= 1 (length style-warnings))))
3169 ;; Full WARNING for invalid type specifier starting with QUOTE.
3170 (multiple-value-bind (fun failure-p warnings)
3171 (checked-compile `(lambda (x) (the 'fixnum x)) :allow-warnings t)
3172 (declare (ignore fun failure-p))
3173 (assert (= 1 (length warnings)))))
3175 (with-test (:name :complex-subtype-dumping-in-xc)
3176 (assert
3177 (= sb-vm:complex-single-float-widetag
3178 (sb-kernel:widetag-of
3179 (sb-vm:saetp-initial-element-default (sb-c::find-saetp '(complex single-float))))))
3180 (assert
3181 (= sb-vm:complex-double-float-widetag
3182 (sb-kernel:widetag-of
3183 (sb-vm:saetp-initial-element-default (sb-c::find-saetp '(complex double-float)))))))
3185 (with-test (:name (compile complex single-float make-array :fill))
3186 (assert (every (lambda (x) (= #c(1.0 2.0) x))
3187 (funcall
3188 (checked-compile
3189 `(lambda (n x)
3190 (make-array (list n)
3191 :element-type '(complex single-float)
3192 :initial-element x)))
3194 #c(1.0 2.0)))))
3196 (with-test (:name :regression-1.0.28.21)
3197 (let ((fun (checked-compile `(lambda (x) (typep x '(simple-array * 1))))))
3198 (assert (funcall fun (vector 1 2 3)))
3199 (assert (funcall fun "abc"))
3200 (assert (not (funcall fun (make-array '(2 2)))))))
3202 (with-test (:name :no-silly-compiler-notes-from-character-function)
3203 (dolist (name '(char-code char-int character char-name standard-char-p
3204 graphic-char-p alpha-char-p upper-case-p lower-case-p
3205 both-case-p digit-char-p alphanumericp digit-char-p))
3206 (checked-compile `(lambda (x)
3207 (declare (character x) (optimize (speed 3)))
3208 (,name x))
3209 :allow-notes nil))
3210 (dolist (name '(char= char/= char< char> char<= char>=
3211 char-lessp char-greaterp char-not-greaterp
3212 char-not-lessp))
3213 (checked-compile `(lambda (x y)
3214 (declare (character x y) (optimize speed))
3215 (,name x y))
3216 :allow-notes nil)))
3218 ;;; optimizing make-array
3219 (with-test (:name (make-array :open-code-initial-contents))
3220 (flet ((test (form)
3221 (assert (not (ctu:find-named-callees
3222 (checked-compile form))))))
3223 (test `(lambda (x y z)
3224 (make-array '(3) :initial-contents (list x y z))))
3225 (test `(lambda (x y z)
3226 (make-array '3 :initial-contents (vector x y z))))
3227 (test `(lambda (x y z)
3228 (make-array '3 :initial-contents `(,x ,y ,z))))
3229 (test `(lambda (x y z)
3230 ;; Single-use FLET is eliminated,
3231 ;; so MAKE-ARRAY's result is obviously a vector.
3232 (flet ((size () '(3)))
3233 (make-array (size) :initial-contents `(,x ,y ,z)))))
3234 (test `(lambda (x y z)
3235 (flet ((size () (list 3))) ; here too
3236 (make-array (size) :initial-contents `(,x ,y ,z)))))))
3238 ;;; optimizing array-in-bounds-p
3239 (with-test (:name :optimize-array-in-bounds-p)
3240 (locally
3241 (macrolet ((find-callees (&body body)
3242 `(ctu:find-named-callees
3243 (checked-compile '(lambda () ,@body))
3244 :name 'array-in-bounds-p))
3245 (must-optimize (&body exprs)
3246 `(progn
3247 ,@(loop for expr in exprs
3248 collect `(assert (not (find-callees
3249 ,expr))))))
3250 (must-not-optimize (&body exprs)
3251 `(progn
3252 ,@(loop for expr in exprs
3253 collect `(assert (find-callees
3254 ,expr))))))
3255 (must-optimize
3256 ;; in bounds
3257 (let ((a (make-array '(1))))
3258 (array-in-bounds-p a 0))
3259 ;; exceeds upper bound (constant)
3260 (let ((a (make-array '(1))))
3261 (array-in-bounds-p a 1))
3262 ;; exceeds upper bound (interval)
3263 (let ((a (make-array '(1))))
3264 (array-in-bounds-p a (+ 1 (random 2))))
3265 ;; negative lower bound (constant)
3266 (let ((a (make-array '(1))))
3267 (array-in-bounds-p a -1))
3268 ;; negative lower bound (interval)
3269 (let ((a (make-array 3))
3270 (i (- (random 1) 20)))
3271 (array-in-bounds-p a i))
3272 ;; multiple known dimensions
3273 (let ((a (make-array '(1 1))))
3274 (array-in-bounds-p a 0 0))
3275 ;; union types
3276 (let ((s (the (simple-string 10) (eval "0123456789"))))
3277 (array-in-bounds-p s 9)))
3278 (must-not-optimize
3279 ;; don't trust non-simple array length in safety=1
3280 (let ((a (the (array * (10 20)) (make-array '(10 20) :adjustable t))))
3281 (eval `(adjust-array ,a '(0 0)))
3282 (array-in-bounds-p a 9 0))
3283 ;; multiple unknown dimensions
3284 (let ((a (make-array (list (random 20) (random 5)))))
3285 (array-in-bounds-p a 5 2))
3286 ;; some other known dimensions
3287 (let ((a (make-array (list 1 (random 5)))))
3288 (array-in-bounds-p a 0 2))
3289 ;; subscript might be negative
3290 (let ((a (make-array '(5 10))))
3291 (array-in-bounds-p a 1 (- (random 3) 2)))
3292 ;; subscript might be too large
3293 (let ((a (make-array '(5 10))))
3294 (array-in-bounds-p a (random 6) 1))
3295 ;; unknown upper bound
3296 (let ((a (make-array '(5 10))))
3297 (array-in-bounds-p a (get-universal-time) 1))
3298 ;; unknown lower bound
3299 (let ((a (make-array '(5 30))))
3300 (array-in-bounds-p a 0 (- (get-universal-time))))
3301 ;; in theory we should be able to optimize
3302 ;; the following but the current implementation
3303 ;; doesn't cut it because the array type's
3304 ;; dimensions get reported as (* *).
3305 (let ((a (make-array (list (random 20) 1))))
3306 (array-in-bounds-p a 5 2))))))
3308 ;;; optimizing (EXPT -1 INTEGER)
3309 (with-test (:name (expt -1 integer))
3310 (dolist (x '(-1 -1.0 -1.0d0))
3311 (let ((fun (checked-compile `(lambda (x) (expt ,x (the fixnum x))))))
3312 (assert (not (ctu:find-named-callees fun)))
3313 (dotimes (i 12)
3314 (if (oddp i)
3315 (assert (eql x (funcall fun i)))
3316 (assert (eql (- x) (funcall fun i))))))))
3318 (with-test (:name :float-division-using-exact-reciprocal)
3319 (flet ((test (lambda-form arg res &key (check-insts t))
3320 (let* ((fun (checked-compile lambda-form))
3321 (disassembly (with-output-to-string (s)
3322 (disassemble fun :stream s))))
3323 ;; Let's make sure there is no division at runtime: for x86 and
3324 ;; x86-64 that implies an FDIV, DIVSS, or DIVSD instruction, so
3325 ;; look for DIV in the disassembly. It's a terrible KLUDGE, but
3326 ;; it works.
3327 #+(or x86 x86-64)
3328 (when check-insts
3329 (assert (not (search "DIV" disassembly))))
3330 ;; No generic arithmetic!
3331 (assert (not (search "GENERIC" disassembly)))
3332 (assert (eql res (funcall fun arg))))))
3333 (dolist (c '(128 64 32 16 8 4 2 1 1/2 1/4 1/8 1/16 1/32 1/64))
3334 (dolist (type '(single-float double-float))
3335 (let* ((cf (coerce c type))
3336 (arg (- (random (* 2 cf)) cf))
3337 (r1 (eval `(/ ,arg ,cf)))
3338 (r2 (eval `(/ ,arg ,(- cf)))))
3339 (test `(lambda (x) (declare (,type x)) (/ x ,cf)) arg r1)
3340 (test `(lambda (x) (declare (,type x)) (/ x ,(- cf))) arg r2)
3341 ;; rational args should get optimized as well
3342 (test `(lambda (x) (declare (,type x)) (/ x ,c)) arg r1)
3343 (test `(lambda (x) (declare (,type x)) (/ x ,(- c))) arg r2))))
3344 ;; Also check that inexact reciprocals (1) are not used by default (2) are
3345 ;; used with FLOAT-ACCURACY=0.
3346 (dolist (type '(single-float double-float))
3347 (let ((trey (coerce 3 type))
3348 (one (coerce 1 type)))
3349 (test `(lambda (x) (declare (,type x)) (/ x 3)) trey one
3350 :check-insts nil)
3351 (test `(lambda (x)
3352 (declare (,type x)
3353 (optimize (sb-c::float-accuracy 0)))
3354 (/ x 3))
3355 trey (eval `(* ,trey (/ ,trey))))))))
3357 (with-test (:name :float-multiplication-by-one)
3358 (flet ((test (lambda-form arg &optional (result arg))
3359 (let* ((fun1 (checked-compile lambda-form))
3360 (fun2 (funcall (checked-compile
3361 `(lambda ()
3362 (declare (optimize (sb-c::float-accuracy 0)))
3363 ,lambda-form))))
3364 (disassembly1 (with-output-to-string (s)
3365 (disassemble fun1 :stream s)))
3366 (disassembly2 (with-output-to-string (s)
3367 (disassemble fun2 :stream s))))
3368 ;; Multiplication at runtime should be eliminated only with
3369 ;; FLOAT-ACCURACY=0. (To catch SNaNs.)
3370 #+(or x86 x86-64)
3371 (assert (and (search "MUL" disassembly1)
3372 (not (search "MUL" disassembly2))))
3373 ;; Not generic arithmetic, please!
3374 (assert (and (not (search "GENERIC" disassembly1))
3375 (not (search "GENERIC" disassembly2))))
3376 (assert (eql result (funcall fun1 arg)))
3377 (assert (eql result (funcall fun2 arg))))))
3378 (dolist (type '(single-float double-float))
3379 (let* ((one (coerce 1 type))
3380 (arg (random (* 2 one)))
3381 (-r (- arg)))
3382 (test `(lambda (x) (declare (,type x)) (* x 1)) arg)
3383 (test `(lambda (x) (declare (,type x)) (* x -1)) arg -r)
3384 (test `(lambda (x) (declare (,type x)) (* x ,one)) arg)
3385 (test `(lambda (x) (declare (,type x)) (* x ,(- one))) arg -r)))))
3387 (with-test (:name :float-addition-of-zero)
3388 (flet ((test (lambda-form arg &optional (result arg))
3389 (let* ((fun1 (checked-compile lambda-form))
3390 (fun2 (funcall (checked-compile
3391 `(lambda ()
3392 (declare (optimize (sb-c::float-accuracy 0)))
3393 ,lambda-form))))
3394 (disassembly1 (with-output-to-string (s)
3395 (disassemble fun1 :stream s)))
3396 (disassembly2 (with-output-to-string (s)
3397 (disassemble fun2 :stream s))))
3398 ;; Let's make sure there is no addition at runtime: for x86 and
3399 ;; x86-64 that implies an FADD, ADDSS, or ADDSD instruction, so
3400 ;; look for the ADDs in the disassembly. It's a terrible KLUDGE,
3401 ;; but it works. Unless FLOAT-ACCURACY is zero, we leave the
3402 ;; addition in to catch SNaNs.
3403 #+x86
3404 (assert (and (search "FADD" disassembly1)
3405 (not (search "FADD" disassembly2))))
3406 #+x86-64
3407 (let ((inst (if (typep result 'double-float)
3408 "ADDSD" "ADDSS")))
3409 (assert (and (search inst disassembly1)
3410 (not (search inst disassembly2)))))
3411 (assert (eql result (funcall fun1 arg)))
3412 (assert (eql result (funcall fun2 arg))))))
3413 (test `(lambda (x) (declare (single-float x)) (+ x 0)) 123.45)
3414 (test `(lambda (x) (declare (single-float x)) (+ x 0.0)) 543.21)
3415 (test `(lambda (x) (declare (single-float x)) (+ x 0.0d0)) 42.00 42.d0)
3416 (test `(lambda (x) (declare (double-float x)) (+ x 0)) 123.45d0)
3417 (test `(lambda (x) (declare (double-float x)) (+ x 0.0)) 543.21d0)
3418 (test `(lambda (x) (declare (double-float x)) (+ x 0.0d0)) 42.d0)))
3420 (with-test (:name :float-substraction-of-zero)
3421 (flet ((test (lambda-form arg &optional (result arg))
3422 (let* ((fun1 (checked-compile lambda-form))
3423 (fun2 (funcall (checked-compile
3424 `(lambda ()
3425 (declare (optimize (sb-c::float-accuracy 0)))
3426 ,lambda-form))))
3427 (disassembly1 (with-output-to-string (s)
3428 (disassemble fun1 :stream s)))
3429 (disassembly2 (with-output-to-string (s)
3430 (disassemble fun2 :stream s))))
3431 ;; Let's make sure there is no substraction at runtime: for x86
3432 ;; and x86-64 that implies an FSUB, SUBSS, or SUBSD instruction,
3433 ;; so look for SUB in the disassembly. It's a terrible KLUDGE,
3434 ;; but it works. Unless FLOAT-ACCURACY is zero, we leave the
3435 ;; substraction in in to catch SNaNs.
3436 #+x86
3437 (assert (and (search "FSUB" disassembly1)
3438 (not (search "FSUB" disassembly2))))
3439 #+x86-64
3440 (let ((inst (if (typep result 'double-float)
3441 "SUBSD" "SUBSS")))
3442 (assert (and (search inst disassembly1)
3443 (not (search inst disassembly2)))))
3444 (assert (eql result (funcall fun1 arg)))
3445 (assert (eql result (funcall fun2 arg))))))
3446 (test `(lambda (x) (declare (single-float x)) (- x 0)) 123.45)
3447 (test `(lambda (x) (declare (single-float x)) (- x 0.0)) 543.21)
3448 (test `(lambda (x) (declare (single-float x)) (- x 0.0d0)) 42.00 42.d0)
3449 (test `(lambda (x) (declare (double-float x)) (- x 0)) 123.45d0)
3450 (test `(lambda (x) (declare (double-float x)) (- x 0.0)) 543.21d0)
3451 (test `(lambda (x) (declare (double-float x)) (- x 0.0d0)) 42.d0)))
3453 (with-test (:name :float-multiplication-by-two)
3454 (flet ((test (lambda-form arg &optional (result arg))
3455 (let* ((fun1 (checked-compile lambda-form))
3456 (fun2 (funcall (checked-compile
3457 `(lambda ()
3458 (declare (optimize (sb-c::float-accuracy 0)))
3459 ,lambda-form))))
3460 (disassembly1 (with-output-to-string (s)
3461 (disassemble fun1 :stream s)))
3462 (disassembly2 (with-output-to-string (s)
3463 (disassemble fun2 :stream s))))
3464 ;; Let's make sure there is no multiplication at runtime: for x86
3465 ;; and x86-64 that implies an FMUL, MULSS, or MULSD instruction,
3466 ;; so look for MUL in the disassembly. It's a terrible KLUDGE,
3467 ;; but it works.
3468 #+(or x86 x86-64)
3469 (assert (and (not (search "MUL" disassembly1))
3470 (not (search "MUL" disassembly2))))
3471 (assert (eql result (funcall fun1 arg)))
3472 (assert (eql result (funcall fun2 arg))))))
3473 (test `(lambda (x) (declare (single-float x)) (* x 2)) 123.45 246.9)
3474 (test `(lambda (x) (declare (single-float x)) (* x 2.0)) 543.21 1086.42)
3475 (test `(lambda (x) (declare (single-float x)) (* x 2.0d0)) 42.00 84.d0)
3476 (test `(lambda (x) (declare (double-float x)) (* x 2)) 123.45d0 246.9d0)
3477 (test `(lambda (x) (declare (double-float x)) (* x 2.0)) 543.21d0 1086.42d0)
3478 (test `(lambda (x) (declare (double-float x)) (* x 2.0d0)) 42.0d0 84.0d0)))
3480 (with-test (:name :bug-392203)
3481 ;; Used to hit an AVER in COMVERT-MV-CALL.
3482 (assert (zerop (funcall
3483 (checked-compile
3484 `(lambda ()
3485 (flet ((k (&rest x) (declare (ignore x)) 0))
3486 (multiple-value-call #'k #'k))))))))
3488 (with-test (:name :allocate-closures-failing-aver)
3489 (let ((f (checked-compile `(lambda ()
3490 (labels ((k (&optional x) #'k))))
3491 :allow-style-warnings t)))
3492 (assert (null (funcall f)))))
3494 (with-test (:name :flush-vector-creation :skipped-on :interpreter)
3495 (let ((f (checked-compile `(lambda ()
3496 (dotimes (i 1024)
3497 (vector i i i))
3498 t))))
3499 (ctu:assert-no-consing (funcall f))))
3501 (with-test (:name :array-type-predicates)
3502 (dolist (et (list* '(integer -1 200) '(integer -256 1)
3503 '(integer 0 128)
3504 '(integer 0 (128))
3505 '(double-float 0d0 (1d0))
3506 '(single-float (0s0) (1s0))
3507 '(or (eql 1d0) (eql 10d0))
3508 '(member 1 2 10)
3509 '(complex (member 10 20))
3510 '(complex (member 10d0 20d0))
3511 '(complex (member 10s0 20s0))
3512 '(or integer double-float)
3513 '(mod 1)
3514 '(member #\a #\b)
3515 '(eql #\a)
3516 #+sb-unicode 'extended-char
3517 #+sb-unicode '(eql #\cyrillic_small_letter_yu)
3518 sb-kernel::*specialized-array-element-types*))
3519 (when et
3520 (let* ((v (make-array 3 :element-type et))
3521 (fun (checked-compile
3522 `(lambda ()
3523 (list (if (typep ,v '(simple-array ,et (*)))
3524 :good
3525 :bad)
3526 (if (typep (elt ,v 0) '(simple-array ,et (*)))
3527 :bad
3528 :good))))))
3529 (assert (equal '(:good :good) (funcall fun)))))))
3531 (with-test (:name :truncate-float)
3532 (let ((s (checked-compile `(lambda (x)
3533 (declare (single-float x))
3534 (truncate x))))
3535 (d (checked-compile `(lambda (x)
3536 (declare (double-float x))
3537 (truncate x))))
3538 (s-inlined (checked-compile
3539 `(lambda (x)
3540 (declare (type (single-float 0.0s0 1.0s0) x))
3541 (truncate x))))
3542 (d-inlined (checked-compile
3543 `(lambda (x)
3544 (declare (type (double-float 0.0d0 1.0d0) x))
3545 (truncate x)))))
3546 ;; Check that there is no generic arithmetic
3547 (assert (not (search "GENERIC"
3548 (with-output-to-string (out)
3549 (disassemble s :stream out)))))
3550 (assert (not (search "GENERIC"
3551 (with-output-to-string (out)
3552 (disassemble d :stream out)))))
3553 ;; Check that we actually inlined the call when we were supposed to.
3554 (assert (not (search "UNARY-TRUNCATE"
3555 (with-output-to-string (out)
3556 (disassemble s-inlined :stream out)))))
3557 (assert (not (search "UNARY-TRUNCATE"
3558 (with-output-to-string (out)
3559 (disassemble d-inlined :stream out)))))))
3561 (with-test (:name (make-array :unnamed-dimension-leaf))
3562 (let ((fun (checked-compile `(lambda (stuff)
3563 (make-array (map 'list 'length stuff))))))
3564 (assert (equalp #2A((0 0 0) (0 0 0))
3565 (funcall fun '((1 2) (1 2 3)))))))
3567 (with-test (:name :fp-decoding-funs-not-flushable-in-safe-code)
3568 (dolist (name '(float-sign float-radix float-digits float-precision decode-float
3569 integer-decode-float))
3570 (let ((fun (checked-compile `(lambda (x)
3571 (declare (optimize safety))
3572 (,name x)
3573 nil))))
3574 (flet ((test (arg)
3575 (unless (eq :error
3576 (handler-case
3577 (funcall fun arg)
3578 (error () :error)))
3579 (error "(~S ~S) did not error"
3580 name arg))))
3581 ;; No error
3582 (funcall fun 1.0)
3583 ;; Error
3584 (test 'not-a-float)
3585 (when (member name '(decode-float integer-decode-float))
3586 (test sb-ext:single-float-positive-infinity))))))
3588 (with-test (:name :sap-ref-16)
3589 (let* ((fun (checked-compile
3590 `(lambda (x y)
3591 (declare (type sb-sys:system-area-pointer x)
3592 (type (integer 0 100) y))
3593 (sb-sys:sap-ref-16 x (+ 4 y)))))
3594 (vector (coerce '(0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15)
3595 '(simple-array (unsigned-byte 8) (*))))
3596 (sap (sb-sys:vector-sap vector))
3597 (ret (funcall fun sap 0)))
3598 ;; test for either endianness
3599 (assert (or (= ret (+ (* 5 256) 4)) (= ret (+ (* 4 256) 5))))))
3601 (with-test (:name (compile coerce :type-warning))
3602 (dolist (type '(t (unsigned-byte 8) (unsigned-byte 16) (unsigned-byte 32)
3603 (signed-byte 8) (signed-byte 16) (signed-byte 32)))
3604 (let ((fun (checked-compile `(lambda (x)
3605 (declare (type simple-vector x))
3606 (coerce x '(vector ,type))))))
3607 (assert (typep (funcall fun #(1)) `(simple-array ,type (*)))))))
3609 (with-test (:name (compile truncate double-float))
3610 (let ((fun (checked-compile `(lambda (x)
3611 (multiple-value-bind (q r)
3612 (truncate (coerce x 'double-float))
3613 (declare (type unsigned-byte q)
3614 (type double-float r))
3615 (list q r))))))
3616 (assert (equal (funcall fun 1.0d0) '(1 0.0d0)))))
3618 (with-test (:name :set-slot-value-no-warning)
3619 (let ((notes (nth-value
3620 4 (checked-compile `(lambda (x y)
3621 (declare (optimize speed safety))
3622 (setf (slot-value x 'bar) y))))))
3623 (assert (= 1 (length notes)))))
3625 (with-test (:name (concatenate :string-opt))
3626 (flet ((test (type grep)
3627 (let* ((fun (checked-compile `(lambda (a b c d e)
3628 (concatenate ',type a b c d e))))
3629 (args '("foo" #(#\.) "bar" (#\-) "quux"))
3630 (res (apply fun args)))
3631 (assert (search grep (with-output-to-string (out)
3632 (disassemble fun :stream out))))
3633 (assert (equal (apply #'concatenate type args)
3634 res))
3635 (assert (typep res type)))))
3636 #+sb-unicode
3637 (test 'string "%CONCATENATE-TO-STRING")
3638 #+sb-unicode
3639 (test 'simple-string "%CONCATENATE-TO-STRING")
3640 (test 'base-string "%CONCATENATE-TO-BASE-STRING")
3641 (test 'simple-base-string "%CONCATENATE-TO-BASE-STRING")))
3643 (with-test (:name (satisfies :no-local-fun))
3644 (let ((fun (checked-compile
3645 `(lambda (arg)
3646 (labels ((local-not-global-bug (x)
3648 (bar (x)
3649 (typep x '(satisfies local-not-global-bug))))
3650 (bar arg))))))
3651 (assert (eq 'local-not-global-bug
3652 (handler-case
3653 (funcall fun 42)
3654 (undefined-function (c)
3655 (cell-error-name c)))))))
3657 ;;; Prior to 1.0.32.x, dumping a fasl with a function with a default
3658 ;;; argument that is a complex structure (needing make-load-form
3659 ;;; processing) failed an AVER. The first attempt at a fix caused
3660 ;;; doing the same in-core to break.
3661 (with-test (:name :bug-310132)
3662 (checked-compile `(lambda (&optional (foo #p"foo/bar")))
3663 :allow-style-warnings t))
3665 (with-test (:name :bug-309129)
3666 (multiple-value-bind (fun failurep warnings)
3667 (checked-compile `(lambda (v) (values (svref v 0) (vector-pop v)))
3668 :allow-failure t :allow-warnings t)
3669 (assert failurep)
3670 (assert (= 1 (length warnings)))
3671 (handler-case (funcall fun #(1))
3672 (type-error (c)
3673 ;; we used to put simply VECTOR into EXPECTED-TYPE, rather
3674 ;; than explicitly (AND VECTOR (NOT SIMPLE-ARRAY))
3675 (assert (not (typep (type-error-datum c) (type-error-expected-type c)))))
3676 (:no-error (&rest values)
3677 (declare (ignore values))
3678 (error "no error")))))
3680 (with-test (:name (round :unary :type-derivation))
3681 (let ((fun (checked-compile
3682 `(lambda (zone)
3683 (multiple-value-bind (h m) (truncate (abs zone) 1.0)
3684 (declare (ignore h))
3685 (round (* 60.0 m)))))))
3686 (assert (= (funcall fun 0.5) 30))))
3688 (with-test (:name :bug-525949)
3689 (let ((fun (checked-compile
3690 `(lambda ()
3691 (labels ((always-one () 1)
3692 (f (z)
3693 (let ((n (funcall z)))
3694 (declare (fixnum n))
3695 (the double-float (expt n 1.0d0)))))
3696 (f #'always-one))))))
3697 (assert (= 1.0d0 (funcall fun)))))
3699 (with-test (:name :%array-data-type-derivation)
3700 (let* ((f (checked-compile
3701 `(lambda (ary)
3702 (declare (type (simple-array (unsigned-byte 32) (3 3)) ary))
3703 (setf (aref ary 0 0) 0))))
3704 (text (with-output-to-string (s)
3705 (disassemble f :stream s))))
3706 (assert (not (search "OBJECT-NOT-SIMPLE-ARRAY-UNSIGNED-BYTE-32-ERROR" text)))))
3708 (with-test (:name :array-storage-vector-type-derivation)
3709 (let ((f (checked-compile
3710 `(lambda (ary)
3711 (declare (type (simple-array (unsigned-byte 32) (3 3)) ary))
3712 (ctu:compiler-derived-type (array-storage-vector ary))))))
3713 (assert (equal '(simple-array (unsigned-byte 32) (9))
3714 (funcall f (make-array '(3 3) :element-type '(unsigned-byte 32)))))))
3716 (with-test (:name :bug-523612)
3717 (let ((fun (checked-compile
3718 `(lambda (&key toff)
3719 (make-array 3 :element-type 'double-float
3720 :initial-contents
3721 (if toff (list toff 0d0 0d0) (list 0d0 0d0 0d0)))))))
3722 (assert (equalp (vector 0.0d0 0.0d0 0.0d0) (funcall fun :toff nil)))
3723 (assert (equalp (vector 2.3d0 0.0d0 0.0d0) (funcall fun :toff 2.3d0)))))
3725 (with-test (:name :bug-309788)
3726 (let ((fun (checked-compile `(lambda (x)
3727 (declare (optimize speed))
3728 (let ((env nil))
3729 (typep x 'fixnum env))))))
3730 (assert (not (ctu:find-named-callees fun)))))
3732 (with-test (:name :bug-309124)
3733 (let ((fun (checked-compile `(lambda (x)
3734 (declare (integer x))
3735 (declare (optimize speed))
3736 (cond ((typep x 'fixnum)
3737 "hala")
3738 ((typep x 'fixnum)
3739 "buba")
3740 ((typep x 'bignum)
3741 "hip")
3743 "zuz"))))))
3744 (assert (equal (list "hala" "hip")
3745 (sort (ctu:find-code-constants fun :type 'string)
3746 #'string<)))))
3748 (with-test (:name :bug-316078)
3749 (let ((fun (checked-compile
3750 `(lambda (x)
3751 (declare (type (and simple-bit-vector (satisfies bar)) x)
3752 (optimize speed))
3753 (elt x 5)))))
3754 (assert (not (ctu:find-named-callees fun)))
3755 (assert (= 1 (funcall fun #*000001)))
3756 (assert (= 0 (funcall fun #*000010)))))
3758 (with-test (:name :mult-by-one-in-float-acc-zero)
3759 (assert (eql 1.0 (funcall (checked-compile
3760 `(lambda (x)
3761 (declare (optimize (sb-c::float-accuracy 0)))
3762 (* x 1.0)))
3763 1)))
3764 (assert (eql -1.0 (funcall (checked-compile
3765 `(lambda (x)
3766 (declare (optimize (sb-c::float-accuracy 0)))
3767 (* x -1.0)))
3768 1)))
3769 (assert (eql 1.0d0 (funcall (checked-compile
3770 `(lambda (x)
3771 (declare (optimize (sb-c::float-accuracy 0)))
3772 (* x 1.0d0)))
3773 1)))
3774 (assert (eql -1.0d0 (funcall (checked-compile
3775 `(lambda (x)
3776 (declare (optimize (sb-c::float-accuracy 0)))
3777 (* x -1.0d0)))
3778 1))))
3780 (with-test (:name :dotimes-non-integer-counter-value)
3781 (multiple-value-bind (fun failure-p warnings)
3782 (checked-compile `(lambda () (dotimes (i 8.6)))
3783 :allow-warnings 'sb-int:type-warning)
3784 (declare (ignore failure-p))
3785 (assert warnings)
3786 (assert-error (funcall fun) type-error)))
3788 (with-test (:name :bug-454681)
3789 ;; This used to break due to reference to a dead lambda-var during
3790 ;; inline expansion.
3791 (assert (checked-compile
3792 `(lambda ()
3793 (multiple-value-bind (iterator+977 getter+978)
3794 (does-not-exist-but-does-not-matter)
3795 (flet ((iterator+976 ()
3796 (funcall iterator+977)))
3797 (declare (inline iterator+976))
3798 (let ((iterator+976 #'iterator+976))
3799 (funcall iterator+976)))))
3800 :allow-style-warnings t)))
3802 (with-test (:name :complex-float-local-fun-args)
3803 ;; As of 1.0.27.14, the lambda below failed to compile due to the
3804 ;; compiler attempting to pass unboxed complex floats to Z and the
3805 ;; MOVE-ARG method not expecting the register being used as a
3806 ;; temporary frame pointer. Reported by sykopomp in #lispgames,
3807 ;; reduced test case provided by _3b`.
3808 (checked-compile `(lambda (a)
3809 (labels ((z (b c)
3810 (declare ((complex double-float) b c))
3811 (* b (z b c))))
3812 (loop for i below 10 do
3813 (setf a (z a a)))))))
3815 (with-test (:name (compile :bug-309130))
3816 (flet ((test (form)
3817 (let ((warnings (nth-value
3818 2 (checked-compile form :allow-warnings t))))
3819 (assert (= 1 (length warnings))))))
3820 (test `(lambda () (svref (make-array 8 :adjustable t) 1)))
3821 (test `(lambda (x)
3822 (declare (optimize (debug 0)))
3823 (declare (type vector x))
3824 (list (fill-pointer x) (svref x 1))))
3825 (test `(lambda (x)
3826 (list (vector-push (svref x 0) x))))
3827 (test `(lambda (x)
3828 (list (vector-push-extend (svref x 0) x))))))
3830 (with-test (:name (compile :bug-646796))
3831 (assert (= 42 (funcall (checked-compile
3832 `(lambda ()
3833 (load-time-value (the (values fixnum) 42))))))))
3835 (with-test (:name (compile :bug-654289))
3836 ;; Test that compile-times don't explode when quoted constants
3837 ;; get big.
3838 (labels ((time-n (n)
3839 (gc :full t) ; Let's not confuse the issue with GC
3840 (let* ((tree (make-tree (expt 10 n) nil))
3841 (t0 (get-internal-run-time))
3842 (f (checked-compile `(lambda (x) (eq x (quote ,tree)))))
3843 (t1 (get-internal-run-time)))
3844 (assert (funcall f tree))
3845 (- t1 t0)))
3846 (make-tree (n acc)
3847 (cond ((zerop n) acc)
3848 (t (make-tree (1- n) (cons acc acc))))))
3849 (let* ((times (loop for i from 0 upto 4
3850 collect (time-n i)))
3851 (max-small (reduce #'max times :end 3))
3852 (max-big (reduce #'max times :start 3)))
3853 ;; This way is hopefully fairly CPU-performance insensitive.
3854 (unless (> (+ (truncate internal-time-units-per-second 10)
3855 (* 2 max-small))
3856 max-big)
3857 (error "Bad scaling or test? ~S" times)))))
3859 (with-test (:name (compile :bug-309063))
3860 (let ((fun (checked-compile `(lambda (x)
3861 (declare (type (integer 0 0) x))
3862 (ash x 100)))))
3863 (assert (zerop (funcall fun 0)))))
3865 (with-test (:name (compile :bug-655872))
3866 (let ((f (checked-compile
3867 `(lambda (x)
3868 (declare (optimize (safety 3)))
3869 (aref (locally (declare (optimize (safety 0)))
3870 (coerce x '(simple-vector 128)))
3871 60))))
3872 (long (make-array 100 :element-type 'fixnum)))
3873 (dotimes (i 100)
3874 (setf (aref long i) i))
3875 ;; 1. COERCE doesn't check the length in unsafe code.
3876 (assert (eql 60 (funcall f long)))
3877 ;; 2. The compiler doesn't trust the length from COERCE
3878 (assert (eq :caught
3879 (handler-case
3880 (funcall f (list 1 2 3))
3881 (sb-int:invalid-array-index-error (e)
3882 (assert (eql 60 (type-error-datum e)))
3883 (assert (equal '(integer 0 (3)) (type-error-expected-type e)))
3884 :caught))))))
3886 (with-test (:name (compile :bug-655203-regression))
3887 (let ((fun (checked-compile
3888 `(LAMBDA (VARIABLE)
3889 (LET ((CONTINUATION
3890 (LAMBDA
3891 (&OPTIONAL DUMMY &REST OTHER)
3892 (DECLARE (IGNORE OTHER))
3893 (PRIN1 DUMMY)
3894 (PRIN1 VARIABLE))))
3895 (FUNCALL CONTINUATION (LIST 1 2)))))))
3896 ;; This used to signal a bogus type-error.
3897 (assert (equal (with-output-to-string (*standard-output*)
3898 (funcall fun t))
3899 "(1 2)T"))))
3901 (with-test (:name :constant-concatenate-compile-time)
3902 (flet ((make-lambda (n)
3903 `(lambda (x)
3904 (declare (optimize (speed 3) (space 0)))
3905 (concatenate 'string x ,(make-string n)))))
3906 (let* ((l0 (make-lambda 1))
3907 (l1 (make-lambda 10))
3908 (l2 (make-lambda 100))
3909 (l3 (make-lambda 1000))
3910 (t0 (get-internal-run-time))
3911 (f0 (checked-compile l0))
3912 (t1 (get-internal-run-time))
3913 (f1 (checked-compile l1))
3914 (t2 (get-internal-run-time))
3915 (f2 (checked-compile l2))
3916 (t3 (get-internal-run-time))
3917 (f3 (checked-compile l3))
3918 (t4 (get-internal-run-time))
3919 (d0 (- t1 t0))
3920 (d1 (- t2 t1))
3921 (d2 (- t3 t2))
3922 (d3 (- t4 t3))
3923 (short-avg (/ (+ d0 d1 d2) 3)))
3924 (assert (and f0 f1 f2 f3))
3925 (assert (< d3 (* 10 short-avg))))))
3927 (with-test (:name :bug-384892)
3928 (assert (equal
3929 '(function (fixnum fixnum &key (:k1 boolean))
3930 (values (member t) &optional))
3931 (sb-kernel:%simple-fun-type
3932 (checked-compile `(lambda (x y &key k1)
3933 (declare (fixnum x y))
3934 (declare (boolean k1))
3935 (declare (ignore x y k1))
3936 t))))))
3938 (with-test (:name :bug-309448)
3939 ;; Like all tests trying to verify that something doesn't blow up
3940 ;; compile-times this is bound to be a bit brittle, but at least
3941 ;; here we try to establish a decent baseline.
3942 (labels ((time-it (lambda want &optional times)
3943 (gc :full t) ; let's keep GCs coming from other code out...
3944 (let* ((start (get-internal-run-time))
3945 (iterations 0)
3946 (fun (if times
3947 (loop repeat times
3948 for result = (checked-compile lambda)
3949 finally (return result))
3950 (loop for result = (checked-compile lambda)
3951 do (incf iterations)
3952 until (> (get-internal-run-time) (+ start 10))
3953 finally (return result))))
3954 (end (get-internal-run-time))
3955 (got (funcall fun)))
3956 (unless (eql want got)
3957 (error "wanted ~S, got ~S" want got))
3958 (values (- end start) iterations)))
3959 (test-it (simple result1 complex result2)
3960 (multiple-value-bind (time-simple iterations)
3961 (time-it simple result1)
3962 (assert (>= (* 10 (1+ time-simple))
3963 (time-it complex result2 iterations))))))
3964 ;; This is mostly identical as the next one, but doesn't create
3965 ;; hairy unions of numeric types.
3966 (test-it `(lambda ()
3967 (labels ((bar (baz bim)
3968 (let ((n (+ baz bim)))
3969 (* n (+ n 1) bim))))
3970 (let ((a (bar 1 1))
3971 (b (bar 1 1))
3972 (c (bar 1 1)))
3973 (- (+ a b) c))))
3975 `(lambda ()
3976 (labels ((bar (baz bim)
3977 (let ((n (+ baz bim)))
3978 (* n (+ n 1) bim))))
3979 (let ((a (bar 1 1))
3980 (b (bar 1 5))
3981 (c (bar 1 15)))
3982 (- (+ a b) c))))
3983 -3864)
3984 (test-it `(lambda ()
3985 (labels ((sum-d (n)
3986 (let ((m (truncate 999 n)))
3987 (/ (* n m (1+ m)) 2))))
3988 (- (+ (sum-d 3)
3989 (sum-d 3))
3990 (sum-d 3))))
3991 166833
3992 `(lambda ()
3993 (labels ((sum-d (n)
3994 (let ((m (truncate 999 n)))
3995 (/ (* n m (1+ m)) 2))))
3996 (- (+ (sum-d 3)
3997 (sum-d 5))
3998 (sum-d 15))))
3999 233168)))
4001 (with-test (:name :regression-1.0.44.34)
4002 (checked-compile
4003 `(lambda (z &rest args)
4004 (declare (dynamic-extent args))
4005 (flet ((foo (w v) (list v w)))
4006 (setq z 0)
4007 (flet ((foo ()
4008 (foo z args)))
4009 (declare (sb-int:truly-dynamic-extent #'foo))
4010 (call #'foo nil))))
4011 :allow-style-warnings t))
4013 (with-test (:name :bug-713626)
4014 (let ((f (eval '(constantly 42))))
4015 (assert (= 42 (funcall (checked-compile
4016 `(lambda () (funcall ,f 1 2 3))))))))
4018 (with-test (:name :known-fun-allows-other-keys)
4019 (funcall (checked-compile
4020 `(lambda () (directory "." :allow-other-keys t))))
4021 (funcall (checked-compile
4022 `(lambda () (directory "." :bar t :allow-other-keys t)))))
4024 (with-test (:name :bug-551227)
4025 ;; This function causes constraint analysis to perform a
4026 ;; ref-substitution that alters the A referred to in (G A) at in the
4027 ;; consequent of the IF to refer to be NUMBER, from the
4028 ;; LET-converted inline-expansion of MOD. This leads to attempting
4029 ;; to CLOSE-OVER a variable that simply isn't in scope when it is
4030 ;; referenced.
4031 (checked-compile
4032 `(lambda (a)
4033 (if (let ((s a))
4034 (block :block
4035 (map nil
4036 (lambda (e)
4037 (return-from :block
4038 (f (mod a e))))
4039 s)))
4040 (g a)))
4041 :allow-style-warnings t))
4043 (with-test (:name :funcall-lambda-inlined)
4044 (assert (not
4045 (ctu:find-code-constants
4046 (checked-compile `(lambda (x y)
4047 (+ x (funcall (lambda (z) z) y))))
4048 :type 'function))))
4050 (with-test (:name :bug-720382)
4051 (multiple-value-bind (fun failurep warnings)
4052 (checked-compile `(lambda (b) ((lambda () b) 1)) :allow-warnings t)
4053 (assert failurep)
4054 (assert (= 1 (length warnings)))
4055 (assert-error (funcall fun 0))))
4057 (with-test (:name :multiple-args-to-function)
4058 (let ((form `(flet ((foo (&optional (x 13)) x))
4059 (funcall (function foo 42))))
4060 #+sb-eval (*evaluator-mode* :interpret))
4061 #+sb-eval
4062 (assert (eq :error
4063 (handler-case (eval form)
4064 (error () :error))))
4065 (multiple-value-bind (fun failure-p)
4066 (checked-compile `(lambda () ,form) :allow-failure t)
4067 (assert failure-p)
4068 (assert-error (funcall fun)))))
4070 ;;; This doesn't test LVAR-FUN-IS directly, but captures it
4071 ;;; pretty accurately anyways.
4072 (with-test (:name :lvar-fun-is :skipped-on :interpreter)
4073 (dolist (fun (list
4074 (lambda (x) (member x x :test #'eq))
4075 (lambda (x) (member x x :test 'eq))
4076 (lambda (x) (member x x :test #.#'eq))))
4077 (assert (equal (list #'sb-kernel:%member-eq)
4078 (ctu:find-named-callees fun))))
4079 (dolist (fun (list
4080 (lambda (x)
4081 (declare (notinline eq))
4082 (member x x :test #'eq))
4083 (lambda (x)
4084 (declare (notinline eq))
4085 (member x x :test 'eq))
4086 (lambda (x)
4087 (declare (notinline eq))
4088 (member x x :test #.#'eq))))
4089 (assert (member #'sb-kernel:%member-test
4090 (ctu:find-named-callees fun)))))
4092 (with-test (:name :delete-to-delq-opt :skipped-on :interpreter)
4093 (dolist (fun (list (lambda (x y)
4094 (declare (list y))
4095 (delete x y :test #'eq))
4096 (lambda (x y)
4097 (declare (fixnum x) (list y))
4098 (delete x y))
4099 (lambda (x y)
4100 (declare (symbol x) (list y))
4101 (delete x y :test #'eql))))
4102 (assert (equal (list #'sb-int:delq)
4103 (ctu:find-named-callees fun)))))
4105 (with-test (:name (compile :bug-767959))
4106 ;; This used to signal an error.
4107 (checked-compile `(lambda ()
4108 (declare (optimize sb-c:store-coverage-data))
4109 (assoc
4111 '((:ordinary . ordinary-lambda-list))))))
4113 ;; This test failed formerly because the source transform of TYPEP would be
4114 ;; disabled when storing coverage data, thus giving no semantics to
4115 ;; expressions such as (TYPEP x 'INTEGER). The compiler could therefore not
4116 ;; prove that the else clause of the IF is unreachable - which it must be
4117 ;; since X is asserted to be fixnum. The conflicting requirement on X
4118 ;; that it be acceptable to LENGTH signaled a full warning.
4119 ;; Nobody on sbcl-devel could remember why the source transform was disabled,
4120 ;; but nobody disagreed with undoing the disabling.
4121 (with-test (:name (compile :sb-cover-and-typep))
4122 (checked-compile
4123 '(lambda (x)
4124 (declare (fixnum x) (optimize sb-c:store-coverage-data))
4125 (if (typep x 'integer) x (length x)))))
4127 (with-test (:name (compile :member :on-long-constant-list))
4128 ;; This used to blow stack with a sufficiently long list.
4129 (let ((cycle (list t)))
4130 (nconc cycle cycle)
4131 (checked-compile `(lambda (x)
4132 (member x ',cycle)))))
4134 (with-test (:name (compile :bug-722734))
4135 (checked-compile-and-assert (:allow-warnings t :optimize :safe)
4136 '(lambda ()
4137 (eql (make-array 6)
4138 (list unbound-variable-1 unbound-variable-2)))
4139 (() (condition 'error))))
4141 (with-test (:name (compile :bug-771673))
4142 (assert (equal `(the foo bar) (macroexpand `(truly-the foo bar))))
4143 ;; Make sure the compiler doesn't use THE, and check that setf-expansions
4144 ;; work.
4145 (let ((f (checked-compile `(lambda (x y)
4146 (setf (truly-the fixnum (car x)) y)))))
4147 (let* ((cell (cons t t)))
4148 (funcall f cell :ok)
4149 (assert (equal '(:ok . t) cell)))))
4151 (with-test (:name (compile :bug-793771 +))
4152 (let ((f (checked-compile `(lambda (x y)
4153 (declare (type (single-float 2.0) x)
4154 (type (single-float (0.0)) y))
4155 (+ x y)))))
4156 (assert (equal `(function ((single-float 2.0) (single-float (0.0)))
4157 (values (single-float 2.0) &optional))
4158 (sb-kernel:%simple-fun-type f)))))
4160 (with-test (:name (compile :bug-793771 -))
4161 (let ((f (checked-compile `(lambda (x y)
4162 (declare (type (single-float * 2.0) x)
4163 (type (single-float (0.0)) y))
4164 (- x y)))))
4165 (assert (equal `(function ((single-float * 2.0) (single-float (0.0)))
4166 (values (single-float * 2.0) &optional))
4167 (sb-kernel:%simple-fun-type f)))))
4169 (with-test (:name (:bug-793771 *))
4170 (let ((f (checked-compile
4171 `(lambda (x)
4172 (declare (type (single-float (0.0)) x))
4173 (* x 0.1)))))
4174 (assert (equal `(function ((single-float (0.0)))
4175 (values (single-float 0.0) &optional))
4176 (sb-kernel:%simple-fun-type f)))))
4178 (with-test (:name (:bug-793771 /))
4179 (let ((f (checked-compile
4180 `(lambda (x)
4181 (declare (type (single-float (0.0)) x))
4182 (/ x 3.0)))))
4183 (assert (equal `(function ((single-float (0.0)))
4184 (values (single-float 0.0) &optional))
4185 (sb-kernel:%simple-fun-type f)))))
4187 (with-test (:name (compile :bug-486812 single-float))
4188 (checked-compile `(lambda ()
4189 (sb-kernel:make-single-float -1))))
4191 (with-test (:name (compile :bug-486812 double-float))
4192 (checked-compile `(lambda ()
4193 (sb-kernel:make-double-float -1 0))))
4195 (with-test (:name (compile :bug-729765))
4196 (checked-compile `(lambda (a b)
4197 (declare ((integer 1 1) a)
4198 ((integer 0 1) b)
4199 (optimize debug))
4200 (lambda () (< b a)))))
4202 ;; Actually tests the assembly of RIP-relative operands to comparison
4203 ;; functions (one of the few x86 instructions that have extra bytes
4204 ;; *after* the mem operand's effective address, resulting in a wrong
4205 ;; offset).
4206 (with-test (:name (compile :cmpps))
4207 (checked-compile-and-assert ()
4208 `(lambda (x)
4209 (= #C(2.0 3.0) (the (complex single-float) x)))
4210 ((#C(2.0 3.0)) t)
4211 ((#C(1.0 2.0)) nil)))
4213 (with-test (:name (compile :cmppd))
4214 (checked-compile-and-assert ()
4215 `(lambda (x)
4216 (= #C(2d0 3d0) (the (complex double-float) x)))
4217 ((#C(2d0 3d0)) t)
4218 ((#C(1d0 2d0)) nil)))
4220 (with-test (:name (compile :lvar-externally-checkable-type-nil))
4221 ;; Used to signal a BUG during compilation.
4222 (checked-compile-and-assert (:optimize :safe)
4223 `(lambda (a)
4224 (parse-integer "12321321" (the (member :start) a) 1))
4225 ((:start) (values 2321321 8))
4226 ((:end) (condition 'type-error))))
4228 (with-test (:name (compile simple-type-error :in-bound-propagation-a))
4229 (checked-compile `(lambda (i)
4230 (declare (unsigned-byte i))
4231 (expt 10 (expt 7 (- 2 i))))))
4233 (with-test (:name (compile simple-type-error :in-bound-propagation-b))
4234 (assert (equal `(FUNCTION (UNSIGNED-BYTE)
4235 (VALUES (SINGLE-FLOAT -1F0 1F0) &OPTIONAL))
4236 (sb-kernel:%simple-fun-type
4237 (checked-compile `(lambda (i)
4238 (declare (unsigned-byte i))
4239 (cos (expt 10 (+ 4096 i)))))))))
4241 (with-test (:name (compile :fixed-%more-arg-values))
4242 (checked-compile-and-assert ()
4243 `(lambda (&rest rest)
4244 (apply #'cons rest))
4245 (('car 'cdr) '(car . cdr))))
4247 (with-test (:name (compile :bug-826970))
4248 (checked-compile-and-assert ()
4249 `(lambda (a b c)
4250 (declare (type (member -2 1) b))
4251 (array-in-bounds-p a 4 b c))
4252 (((make-array '(5 2 2)) 1 1) t)))
4254 (with-test (:name (compile :bug-826971))
4255 (let ((foo "foo"))
4256 (checked-compile-and-assert ()
4257 `(lambda (p1 p2)
4258 (schar (the (eql ,foo) p1) p2))
4259 ((foo 0) #\f))))
4261 (with-test (:name (compile :bug-738464))
4262 (multiple-value-bind (fun failure-p warnings style-warnings)
4263 (checked-compile `(lambda ()
4264 (flet ((foo () 42))
4265 (declare (ftype non-function-type foo))
4266 (foo)))
4267 :allow-style-warnings t)
4268 (declare (ignore failure-p warnings))
4269 (assert style-warnings)
4270 (assert (eql 42 (funcall fun)))))
4272 (with-test (:name (compile :bug-832005))
4273 (checked-compile-and-assert ()
4274 `(lambda (x)
4275 (declare (type (complex single-float) x))
4276 (+ #C(0.0 1.0) x))
4277 ((#C(1.0 2.0)) #C(1.0 3.0))))
4279 ;; A refactoring 1.0.12.18 caused lossy computation of primitive
4280 ;; types for member types.
4281 (with-test (:name (compile member type :primitive-type))
4282 (checked-compile-and-assert ()
4283 `(lambda (p1 p2 p3)
4284 (if p1
4285 (the (member #c(1.2d0 1d0)) p2)
4286 (the (eql #c(1.0 1.0)) p3)))
4287 ((1 #c(1.2d0 1d0) #c(1.0 1.0)) #c(1.2d0 1.0d0))))
4289 ;; Fall-through jump elimination made control flow fall through to trampolines.
4290 ;; Reported by Eric Marsden on sbcl-devel@ 2011.10.26, with a test case
4291 ;; reproduced below (triggered a corruption warning and a memory fault).
4292 (with-test (:name (compile :bug-883500))
4293 (checked-compile-and-assert ()
4294 `(lambda (a)
4295 (declare (type (integer -50 50) a))
4296 (mod (mod a (min -5 a)) 5))
4297 ((1) 1)))
4299 ;; Test for literals too large for the ISA (e.g. (SIGNED-BYTE 13) on SPARC).
4300 #+sb-unicode
4301 (with-test (:name (compile :bug-883519))
4302 (checked-compile `(lambda (x)
4303 (declare (type character x))
4304 (eql x #\U0010FFFF))))
4306 ;; Wide fixnum platforms had buggy address computation in atomic-incf/aref
4307 (with-test (:name (compile :bug-887220))
4308 (checked-compile-and-assert ()
4309 `(lambda (vector index)
4310 (declare (type (simple-array sb-ext:word (4))
4311 vector)
4312 (type (mod 4) index))
4313 (sb-ext:atomic-incf (aref vector index) 1)
4314 vector)
4315 (((make-array 4 :element-type 'sb-ext:word
4316 :initial-element 0)
4318 #(0 1 0 0) :test #'equalp)))
4320 (with-test (:name (compile catch :interferes-with-debug-names))
4321 (let ((fun (funcall
4322 (checked-compile
4323 `(lambda ()
4324 (catch 'out
4325 (flet ((foo ()
4326 (throw 'out (lambda () t))))
4327 (foo))))))))
4328 (assert (equal '(lambda () :in foo) (sb-kernel:%fun-name fun)))))
4330 (with-test (:name (compile :interval-div-signed-zero))
4331 (checked-compile-and-assert ()
4332 `(Lambda (a)
4333 (declare (type (member 0 -272413371076) a))
4334 (ffloor (the number a) -63243.127451934015d0))
4335 ((0) (values -0d0 0d0))))
4337 (with-test (:name (compile :non-constant-keyword-typecheck))
4338 (checked-compile-and-assert ()
4339 `(lambda (p1 p3 p4)
4340 (declare (type keyword p3))
4341 (tree-equal p1 (cons 1 2) (the (member :test) p3) p4))
4342 (((cons 1.0 2.0) :test '=) t)))
4344 (with-test (:name (compile truncate :wild-values))
4345 (let ((sb-c::*check-consistency* t))
4346 (checked-compile-and-assert ()
4347 `(lambda (a)
4348 (declare (type (member 1d0 2d0) a))
4349 (block return-value-tag
4350 (funcall
4351 (the function
4352 (catch 'debug-catch-tag
4353 (return-from return-value-tag
4354 (progn (truncate a))))))))
4355 ((2d0) (values 2 0d0)))))
4357 (with-test (:name (compile :boxed-fp-constant-for-full-call))
4358 (let ((fun (checked-compile
4359 `(lambda (x)
4360 (declare (double-float x))
4361 (unknown-fun 4.0d0 (+ 4.0d0 x)))
4362 :allow-style-warnings t)))
4363 (assert (equal '(4.0d0) (ctu:find-code-constants fun :type 'double-float)))))
4365 (with-test (:name (compile :only-one-boxed-constant-for-multiple-uses))
4366 (let* ((big (1+ most-positive-fixnum))
4367 (fun (checked-compile
4368 `(lambda (x)
4369 (unknown-fun ,big (+ ,big x)))
4370 :allow-style-warnings t)))
4371 (assert (= 1 (length (ctu:find-code-constants fun :type `(eql ,big)))))))
4373 (with-test (:name (compile fixnum + float :coerces fixnum)
4374 :skipped-on :x86)
4375 (let ((fun (checked-compile
4376 `(lambda (x y)
4377 (declare (fixnum x)
4378 (single-float y))
4379 (+ x y)))))
4380 (assert (not (ctu:find-named-callees fun)))
4381 (assert (not (search "GENERIC"
4382 (with-output-to-string (s)
4383 (disassemble fun :stream s)))))))
4385 (with-test (:name (compile :bug-803508))
4386 (checked-compile `(lambda ()
4387 (print
4388 (lambda (bar)
4389 (declare (dynamic-extent bar))
4390 (foo bar))))
4391 :allow-style-warnings t))
4393 (with-test (:name (compile :bug-803508-b))
4394 (checked-compile `(lambda ()
4395 (list
4396 (lambda (bar)
4397 (declare (dynamic-extent bar))
4398 (foo bar))))
4399 :allow-style-warnings t))
4401 (with-test (:name (compile :bug-803508-c))
4402 (checked-compile `(lambda ()
4403 (list
4404 (lambda (bar &optional quux)
4405 (declare (dynamic-extent bar quux))
4406 (foo bar quux))))
4407 :allow-style-warnings t))
4409 (with-test (:name (compile :cprop-with-constant-but-assigned-to-closure-variable))
4410 (checked-compile `(lambda (b c d)
4411 (declare (type (integer -20545789 207590862) c))
4412 (declare (type (integer -1 -1) d))
4413 (let ((i (unwind-protect 32 (shiftf d -1))))
4414 (or (if (= d c) 2 (= 3 b)) 4)))
4415 :allow-style-warnings t))
4417 (with-test (:name (compile :bug-913232))
4418 (checked-compile `(lambda (x)
4419 (declare (optimize speed)
4420 (type (or (and (or (integer -100 -50)
4421 (integer 100 200))
4422 (satisfies foo))
4423 (and (or (integer 0 10) (integer 20 30)) a))
4426 :allow-style-warnings t)
4427 (checked-compile `(lambda (x)
4428 (declare (optimize speed)
4429 (type (and fixnum a) x))
4431 :allow-style-warnings t))
4433 (with-test (:name (compile :bug-959687))
4434 (flet ((test (form)
4435 (multiple-value-bind (fun failure-p warnings style-warnings)
4436 (checked-compile form :allow-failure t :allow-style-warnings t)
4437 (declare (ignore warnings))
4438 (assert (and failure-p style-warnings))
4439 (assert-error(funcall fun t)))))
4440 (test `(lambda (x)
4441 (case x
4443 :its-a-t)
4444 (otherwise
4445 :somethign-else))))
4446 (test `(lambda (x)
4447 (case x
4448 (otherwise
4449 :its-an-otherwise)
4451 :somethign-else))))))
4453 (with-test (:name (compile :bug-924276))
4454 (assert (nth-value
4455 3 (checked-compile `(lambda (a)
4456 (cons a (symbol-macrolet ((b 1))
4457 (declare (ignorable a))
4458 :c)))
4459 :allow-style-warnings t))))
4461 (with-test (:name (compile :bug-974406))
4462 (checked-compile-and-assert ()
4463 `(lambda (x)
4464 (declare (type (integer 53 86) x))
4465 (logand (+ x 1032791128) 11007078467))
4466 ((61) 268574721))
4467 (checked-compile-and-assert ()
4468 `(lambda (x)
4469 (declare (type (integer 53 86) x))
4470 (logand (+ x 1152921504606846975)
4471 38046409652025950207))
4472 ((61) 60))
4474 (let (result)
4475 (do ((width 5 (1+ width)))
4476 ((= width 130))
4477 (dotimes (extra 4)
4478 (let ((fun (checked-compile
4479 `(lambda (x)
4480 (declare (optimize speed (safety 0)))
4481 (declare (type (integer 1 16) x))
4482 (logand
4483 (+ x ,(1- (ash 1 width)))
4484 ,(logior (ash 1 (+ width 1 extra))
4485 (1- (ash 1 width))))))))
4486 (unless (= (funcall fun 16) (logand 15 (1- (ash 1 width))))
4487 (push (cons width extra) result)))))
4488 (assert (null result))))
4490 ;; On x86-64 MOVE-IMMEDIATE of fixnum values into memory either directly
4491 ;; uses a MOV into memory or goes through a temporary register if the
4492 ;; value is larger than a certain number of bits. Check that it respects
4493 ;; the limits of immediate arguments to the MOV instruction (if not, the
4494 ;; assembler will fail an assertion) and doesn't have sign-extension
4495 ;; problems. (The test passes fixnum constants through the MOVE VOP
4496 ;; which calls MOVE-IMMEDIATE.)
4497 (with-test (:name (compile :constant-fixnum-move))
4498 (let ((f (checked-compile `(lambda (g)
4499 (funcall g
4500 ;; The first three args are
4501 ;; uninteresting as they are
4502 ;; passed in registers.
4503 1 2 3
4504 ,@(loop for i from 27 to 32
4505 collect (expt 2 i)))))))
4506 (assert (every #'plusp (funcall f #'list)))))
4508 (with-test (:name (eval :malformed-ignore :lp-1000239)
4509 :skipped-on :interpreter)
4510 (assert-error
4511 (eval '(lambda () (declare (ignore (function . a)))))
4512 sb-int:simple-program-error)
4513 (assert-error
4514 (eval '(lambda () (declare (ignore (function a b)))))
4515 sb-int:simple-program-error)
4516 (assert-error
4517 (eval '(lambda () (declare (ignore (function)))))
4518 sb-int:simple-program-error)
4519 (assert-error
4520 (eval '(lambda () (declare (ignore (a)))))
4521 sb-int:simple-program-error)
4522 (assert-error
4523 (eval '(lambda () (declare (ignorable (a b)))))
4524 sb-int:simple-program-error))
4526 (with-test (:name (compile :malformed-type-declaraions))
4527 (assert (nth-value 1
4528 (checked-compile
4529 '(lambda (a) (declare (type (integer 1 2 . 3) a)) a)
4530 :allow-warnings t))))
4532 (with-test (:name :compiled-program-error-escaped-source)
4533 (assert
4534 (handler-case
4535 (funcall (checked-compile `(lambda () (lambda ("foo")))
4536 :allow-failure t))
4537 (sb-int:compiled-program-error (e)
4538 (let ((source (read-from-string (sb-kernel::program-error-source e))))
4539 (equal source '#'(lambda ("foo"))))))))
4541 (defun cell-note-p (condition)
4542 (search "Allocating a value-cell at runtime for"
4543 (princ-to-string condition)))
4544 (with-test (:name (compile :escape-analysis-for-nlxs)
4545 :skipped-on :interpreter)
4546 (flet ((test (check lambda &rest args)
4547 (multiple-value-bind (fun failure-p warnings style-warnings notes)
4548 (checked-compile lambda :allow-style-warnings t)
4549 (declare (ignore failure-p warnings style-warnings))
4550 (assert (eql check (when (some #'cell-note-p notes) t)))
4551 (if check
4552 (assert
4553 (eq :ok
4554 (handler-case
4555 (dolist (arg args nil)
4556 (setf fun (funcall fun arg)))
4557 (sb-int:simple-control-error (e)
4558 (when (equal
4559 (simple-condition-format-control e)
4560 "attempt to RETURN-FROM a block or GO to a tag that no longer exists")
4561 :ok)))))
4562 (ctu:assert-no-consing (apply fun args))))))
4563 (test nil `(lambda (x)
4564 (declare (optimize speed))
4565 (block out
4566 (flet ((ex () (return-from out 'out!)))
4567 (typecase x
4568 (cons (or (car x) (ex)))
4569 (t (ex)))))) :foo)
4570 (test t `(lambda (x)
4571 (declare (optimize speed))
4572 (funcall
4573 (block nasty
4574 (flet ((oops () (return-from nasty t)))
4575 #'oops)))) t)
4576 (test t `(lambda (r)
4577 (declare (optimize speed))
4578 (block out
4579 (flet ((ex () (return-from out r)))
4580 (lambda (x)
4581 (typecase x
4582 (cons (or (car x) (ex)))
4583 (t (ex))))))) t t)
4584 (test t `(lambda (x)
4585 (declare (optimize speed))
4586 (flet ((eh (x)
4587 (flet ((meh () (return-from eh 'meh)))
4588 (lambda ()
4589 (typecase x
4590 (cons (or (car x) (meh)))
4591 (t (meh)))))))
4592 (funcall (eh x)))) t t)))
4594 (with-test (:name (compile :bug-1050768 :symptom))
4595 ;; Used to signal an error.
4596 (checked-compile
4597 `(lambda (string position)
4598 (char string position)
4599 (array-in-bounds-p string (1+ position)))))
4601 (with-test (:name (:bug-1050768 :cause))
4602 (let ((types `((string string)
4603 ((or (simple-array character 24) (vector t 24))
4604 (or (simple-array character 24) (vector t))))))
4605 (dolist (pair types)
4606 (destructuring-bind (orig conservative) pair
4607 (assert sb-c::(type= (specifier-type cl-user::conservative)
4608 (conservative-type (specifier-type cl-user::orig))))))))
4610 (with-test (:name (compile :smodular64 :wrong-width))
4611 (checked-compile-and-assert ()
4612 '(lambda (x)
4613 (declare (type (signed-byte 64) x))
4614 (sb-c::mask-signed-field 64 (- x 7033717698976965573)))
4615 ((10038) -7033717698976955535)))
4617 (with-test (:name (compile :smodular32 :wrong-width))
4618 (checked-compile-and-assert ()
4619 '(lambda (x)
4620 (declare (type (signed-byte 31) x))
4621 (sb-c::mask-signed-field 31 (- x 1055131947)))
4622 ((10038) -1055121909)))
4624 (with-test (:name (compile :first-open-coded))
4625 (let ((fun (checked-compile `(lambda (x) (first x)))))
4626 (assert (not (ctu:find-named-callees fun)))))
4628 (with-test (:name (compile :second-open-coded))
4629 (let ((fun (checked-compile `(lambda (x) (second x)))))
4630 (assert (not (ctu:find-named-callees fun)))))
4632 (with-test (:name (compile svref :symbol-macro))
4633 (checked-compile `(lambda (x)
4634 (symbol-macrolet ((sv x))
4635 (values (svref sv 0) (setf (svref sv 0) 99))))))
4637 ;; The compiler used to update the receiving LVAR's type too
4638 ;; aggressively when converting a large constant to a smaller
4639 ;; (potentially signed) one, causing other branches to be
4640 ;; inferred as dead.
4641 (with-test (:name (compile :modular-cut-constant-to-width))
4642 (checked-compile-and-assert ()
4643 `(lambda (x)
4644 (logand 254
4645 (case x
4646 ((3) x)
4647 ((2 2 0 -2 -1 2) 9223372036854775803)
4648 (t 358458651))))
4649 ((-10470605025) 26)))
4651 (with-test (:name (compile append :derive-type))
4652 (let ((test-cases
4653 '((lambda () (append 10)) (integer 10 10)
4654 (lambda () (append nil 10)) (integer 10 10)
4655 (lambda (x) (append x 10)) (or (integer 10 10) cons)
4656 (lambda (x) (append x (cons 1 2))) cons
4657 (lambda (x y) (append x (cons 1 2) y)) cons
4658 (lambda (x y) (nconc x (the list y) x)) t
4659 (lambda (x y) (nconc (the atom x) y)) t
4660 (lambda (x y) (nconc (the (or null (eql 10)) x) y)) t
4661 (lambda (x y) (nconc (the (or cons vector) x) y)) cons
4662 (lambda (x y) (nconc (the sequence x) y)) t
4663 (lambda (x y) (print (length y)) (append x y)) sequence
4664 (lambda (x y) (print (length y)) (append x y)) sequence
4665 (lambda (x y) (append (the (member (a) (b)) x) y)) cons
4666 (lambda (x y) (append (the (member (a) (b) c) x) y)) cons
4667 (lambda (x y) (append (the (member (a) (b) nil) x) y)) t)))
4668 (loop for (function result-type) on test-cases by #'cddr
4669 do (assert (sb-kernel:type= (sb-kernel:specifier-type
4670 (car (cdaddr (sb-kernel:%simple-fun-type
4671 (checked-compile function)))))
4672 (sb-kernel:specifier-type result-type))))))
4674 (with-test (:name (compile :bug-504121))
4675 (checked-compile `(lambda (s)
4676 (let ((p1 #'upper-case-p))
4677 (funcall
4678 (lambda (g)
4679 (funcall p1 g))))
4680 (let ((p2 #'(lambda (char) (upper-case-p char))))
4681 (funcall p2 s)))
4682 :allow-warnings 'sb-int:local-argument-mismatch))
4684 (with-test (:name (compile :bug-504121 :optional-missing))
4685 (checked-compile `(lambda (s)
4686 (let ((p1 #'upper-case-p))
4687 (funcall
4688 (lambda (g &optional x)
4689 (funcall p1 g))))
4690 (let ((p2 #'(lambda (char) (upper-case-p char))))
4691 (funcall p2 s)))
4692 :allow-warnings 'sb-int:local-argument-mismatch))
4694 (with-test (:name (compile :bug-504121 :optional-superfluous))
4695 (checked-compile `(lambda (s)
4696 (let ((p1 #'upper-case-p))
4697 (funcall
4698 (lambda (g &optional x)
4699 (funcall p1 g))
4700 #\1 2 3))
4701 (let ((p2 #'(lambda (char) (upper-case-p char))))
4702 (funcall p2 s)))
4703 :allow-warnings 'sb-int:local-argument-mismatch))
4705 (with-test (:name (compile :bug-504121 :key-odd))
4706 (checked-compile `(lambda (s)
4707 (let ((p1 #'upper-case-p))
4708 (funcall
4709 (lambda (g &key x)
4710 (funcall p1 g))
4711 #\1 :x))
4712 (let ((p2 #'(lambda (char) (upper-case-p char))))
4713 (funcall p2 s)))
4714 :allow-warnings t))
4716 (with-test (:name (compile :bug-504121 :key-unknown))
4717 (checked-compile `(lambda (s)
4718 (let ((p1 #'upper-case-p))
4719 (funcall
4720 (lambda (g &key x)
4721 (funcall p1 g))
4722 #\1 :y 2))
4723 (let ((p2 #'(lambda (char) (upper-case-p char))))
4724 (funcall p2 s)))
4725 :allow-warnings t))
4727 (with-test (:name (compile :bug-1181684))
4728 (checked-compile `(lambda ()
4729 (let ((hash #xD13CCD13))
4730 (setf hash (logand most-positive-word
4731 (ash hash 5)))))))
4733 (with-test (:name (compile :local-&optional-recursive-inline :bug-1180992))
4734 (checked-compile `(lambda ()
4735 (labels ((called (&optional a))
4736 (recursed (&optional b)
4737 (called)
4738 (recursed)))
4739 (declare (inline recursed called))
4740 (recursed)))
4741 :allow-style-warnings t))
4743 (with-test (:name (compile :constant-fold-logtest))
4744 (assert (equal (sb-kernel:%simple-fun-type
4745 (checked-compile `(lambda (x)
4746 (declare (type (mod 1024) x)
4747 (optimize speed))
4748 (logtest x 2048))))
4749 '(function ((unsigned-byte 10)) (values null &optional)))))
4751 ;; type mismatches on LVARs with multiple potential sources used to
4752 ;; be reported as mismatches with the value NIL. Make sure we get
4753 ;; a warning, but that it doesn't complain about a constant NIL ...
4754 ;; of type FIXNUM.
4755 (with-test (:name (compile :multiple-use-lvar-interpreted-as-NIL :cast))
4756 (let ((warnings (nth-value
4757 2 (checked-compile `(lambda (x y z)
4758 (declare (type fixnum y z))
4759 (aref (if x y z) 0))
4760 :allow-warnings 'sb-int:type-warning))))
4761 (assert warnings)
4762 (assert (notany (lambda (condition)
4763 (search "Constant "
4764 (simple-condition-format-control
4765 condition)))
4766 warnings))))
4768 (with-test (:name (compile :multiple-use-lvar-interpreted-as-NIL catch))
4769 (let ((warnings (nth-value
4770 3 (checked-compile `(lambda (x y z f)
4771 (declare (type fixnum y z))
4772 (catch (if x y z) (funcall f)))
4773 :allow-style-warnings t))))
4774 (assert warnings)
4775 (assert (notany (lambda (condition)
4776 (position nil
4777 (simple-condition-format-arguments
4778 condition)))
4779 warnings))))
4781 ;; Smoke test for rightward shifts
4782 (with-test (:name (compile :ash/right-signed))
4783 (let* ((f (checked-compile `(lambda (x y)
4784 (declare (type (mod ,(* 2 sb-vm:n-word-bits)) y)
4785 (type sb-vm:signed-word x)
4786 (optimize speed))
4787 (ash x (- y)))))
4788 (max (ash most-positive-word -1))
4789 (min (- -1 max)))
4790 (flet ((test (x y)
4791 (assert (= (ash x (- y))
4792 (funcall f x y)))))
4793 (dotimes (x 32)
4794 (dotimes (y (* 2 sb-vm:n-word-bits))
4795 (test x y)
4796 (test (- x) y)
4797 (test (- max x) y)
4798 (test (+ min x) y))))))
4800 (with-test (:name (compile :ash/right-unsigned))
4801 (let ((f (checked-compile `(lambda (x y)
4802 (declare (type (mod ,(* 2 sb-vm:n-word-bits)) y)
4803 (type word x)
4804 (optimize speed))
4805 (ash x (- y)))))
4806 (max most-positive-word))
4807 (flet ((test (x y)
4808 (assert (= (ash x (- y))
4809 (funcall f x y)))))
4810 (dotimes (x 32)
4811 (dotimes (y (* 2 sb-vm:n-word-bits))
4812 (test x y)
4813 (test (- max x) y))))))
4815 (with-test (:name (compile :ash/right-fixnum))
4816 (let ((f (checked-compile `(lambda (x y)
4817 (declare (type (mod ,(* 2 sb-vm:n-word-bits)) y)
4818 (type fixnum x)
4819 (optimize speed))
4820 (ash x (- y))))))
4821 (flet ((test (x y)
4822 (assert (= (ash x (- y))
4823 (funcall f x y)))))
4824 (dotimes (x 32)
4825 (dotimes (y (* 2 sb-vm:n-word-bits))
4826 (test x y)
4827 (test (- x) y)
4828 (test (- most-positive-fixnum x) y)
4829 (test (+ most-negative-fixnum x) y))))))
4831 (with-test (:name (compile :fold-index-addressing-positive-offset))
4832 (checked-compile-and-assert ()
4833 `(lambda (i)
4834 (if (typep i '(integer -31 31))
4835 (aref #. (make-array 63) (+ i 31))
4836 (error "foo")))
4837 ((-31) 0)))
4839 ;; 5d3a728 broke something like this in CL-PPCRE
4840 (with-test (:name (compile :fold-index-addressing-potentially-negative-index))
4841 (checked-compile `(lambda (index vector)
4842 (declare (optimize speed (safety 0))
4843 ((simple-array character (*)) vector)
4844 ((unsigned-byte 24) index))
4845 (aref vector (1+ (mod index (1- (length vector))))))))
4847 (with-test (:name (compile :constant-fold-ash/right-fixnum))
4848 (checked-compile `(lambda (a b)
4849 (declare (type fixnum a)
4850 (type (integer * -84) b))
4851 (ash a b))))
4853 (with-test (:name (compile :constant-fold-ash/right-word))
4854 (checked-compile `(lambda (a b)
4855 (declare (type word a)
4856 (type (integer * -84) b))
4857 (ash a b))))
4859 (with-test (:name (compile :nconc-derive-type))
4860 (let ((function (checked-compile `(lambda (x y)
4861 (declare (type (or cons fixnum) x))
4862 (nconc x y)))))
4863 (assert (equal (sb-kernel:%simple-fun-type function)
4864 '(function ((or cons fixnum) t) (values cons &optional))))))
4866 ;; make sure that all data-vector-ref-with-offset VOPs are either
4867 ;; specialised on a 0 offset or accept signed indices
4868 (with-test (:name :data-vector-ref-with-offset-signed-index)
4869 (let ((dvr (find-symbol "DATA-VECTOR-REF-WITH-OFFSET" "SB-KERNEL")))
4870 (when dvr
4871 (assert
4872 (null
4873 (loop for info in (sb-c::fun-info-templates
4874 (sb-c::fun-info-or-lose dvr))
4875 for (nil second-arg third-arg) = (sb-c::vop-info-arg-types info)
4876 unless (or (typep second-arg '(cons (eql :constant)))
4877 (equal third-arg '(:constant . (integer 0 0)))
4878 (equal second-arg
4879 `(:or ,(sb-c::primitive-type-or-lose
4880 'sb-vm::positive-fixnum)
4881 ,(sb-c::primitive-type-or-lose
4882 'fixnum))))
4883 collect info))))))
4885 (with-test (:name :data-vector-set-with-offset-signed-index)
4886 (let ((dvr (find-symbol "DATA-VECTOR-SET-WITH-OFFSET" "SB-KERNEL")))
4887 (when dvr
4888 (assert
4889 (null
4890 (loop for info in (sb-c::fun-info-templates
4891 (sb-c::fun-info-or-lose dvr))
4892 for (nil second-arg third-arg) = (sb-c::vop-info-arg-types info)
4893 unless (or (typep second-arg '(cons (eql :constant)))
4894 (equal third-arg '(:constant . (integer 0 0)))
4895 (equal second-arg
4896 `(:or ,(sb-c::primitive-type-or-lose
4897 'sb-vm::positive-fixnum)
4898 ,(sb-c::primitive-type-or-lose
4899 'fixnum))))
4900 collect info))))))
4902 (with-test (:name (compile :maybe-inline-ref-to-dead-lambda))
4903 (checked-compile `(lambda (string)
4904 (declare (optimize speed (space 0)))
4905 (cond ((every #'digit-char-p string)
4906 nil)
4907 ((some (lambda (c)
4908 (digit-char-p c))
4909 string))))))
4911 ;; the x87 backend used to sometimes signal FP errors during boxing,
4912 ;; because converting between double and single float values was a
4913 ;; noop (fixed), and no doubt many remaining issues. We now store
4914 ;; the value outside pseudo-atomic, so any SIGFPE should be handled
4915 ;; correctly.
4917 ;; When it fails, this test lands into ldb.
4918 (with-test (:name :no-overflow-during-allocation)
4919 (handler-case (eval '(cosh 90))
4920 (floating-point-overflow ()
4921 t)))
4923 ;; unbounded integer types could break integer arithmetic.
4924 (with-test (:name (compile :bug-1199127))
4925 (checked-compile
4926 `(lambda (b)
4927 (declare (type (integer -1225923945345 -832450738898) b))
4928 (declare (optimize (speed 3) (space 3) (safety 2)
4929 (debug 0) (compilation-speed 1)))
4930 (loop for lv1 below 3
4931 sum (logorc2
4932 (if (>= 0 lv1)
4933 (ash b (min 25 lv1))
4935 -2)))))
4937 ;; non-trivial modular arithmetic operations would evaluate to wider results
4938 ;; than expected, and never be cut to the right final bitwidth.
4939 (with-test (:name (compile :bug-1199428-1))
4940 (checked-compile-and-assert (:optimize :quick/incomplete)
4941 `(lambda (a c)
4942 (declare (type (integer -2 1217810089) a))
4943 (declare (type (integer -6895591104928 -561736648588) c))
4944 (declare (optimize (space 0) (compilation-speed 3)))
4945 (logandc1 (gcd c)
4946 (+ (- a c)
4947 (loop for lv2 below 1 count t))))
4948 ((530436387 -4890629672277) 1338004008))
4949 (checked-compile-and-assert (:optimize :quick/incomplete)
4950 `(lambda (a c)
4951 (declare (notinline - + gcd logandc1))
4952 (declare (optimize (space 1) (compilation-speed 3)))
4953 (logandc1 (gcd c)
4954 (+ (- a c)
4955 (loop for lv2 below 1 count t))))
4956 ((530436387 -4890629672277) 1338004008)))
4958 (with-test (:name (compile :bug-1199428-2))
4959 (checked-compile-and-assert (:optimize :quick/incomplete)
4960 `(lambda (a b)
4961 (declare (type (integer -1869232508 -6939151) a))
4962 (declare (type (integer -11466348357 -2645644006) b))
4963 (declare (optimize (space 0) (compilation-speed 2)))
4964 (logand (lognand a -6) (* b -502823994)))
4965 ((-1491588365 -3745511761) 1084329992))
4966 (checked-compile-and-assert ()
4967 `(lambda (a b)
4968 (logand (lognand a -6) (* b -502823994)))
4969 ((-1491588365 -3745511761) 1084329992)))
4971 ;; win32 is very specific about the order in which catch blocks
4972 ;; must be allocated on the stack
4973 (with-test (:name (compile :bug-1072739))
4974 (checked-compile-and-assert (:optimize :safe)
4975 `(lambda ()
4976 (STRING=
4977 (LET ((% 23))
4978 (WITH-OUTPUT-TO-STRING (G13908)
4979 (PRINC
4980 (LET ()
4981 (DECLARE (OPTIMIZE (SB-EXT:INHIBIT-WARNINGS 3)))
4982 (HANDLER-CASE
4983 (WITH-OUTPUT-TO-STRING (G13909) (PRINC %A%B% G13909) G13909)
4984 (UNBOUND-VARIABLE NIL
4985 (HANDLER-CASE
4986 (WITH-OUTPUT-TO-STRING (G13914)
4987 (PRINC %A%B% G13914)
4988 (PRINC "" G13914)
4989 G13914)
4990 (UNBOUND-VARIABLE NIL
4991 (HANDLER-CASE
4992 (WITH-OUTPUT-TO-STRING (G13913)
4993 (PRINC %A%B G13913)
4994 (PRINC "%" G13913)
4995 G13913)
4996 (UNBOUND-VARIABLE NIL
4997 (HANDLER-CASE
4998 (WITH-OUTPUT-TO-STRING (G13912)
4999 (PRINC %A% G13912)
5000 (PRINC "b%" G13912)
5001 G13912)
5002 (UNBOUND-VARIABLE NIL
5003 (HANDLER-CASE
5004 (WITH-OUTPUT-TO-STRING (G13911)
5005 (PRINC %A G13911)
5006 (PRINC "%b%" G13911)
5007 G13911)
5008 (UNBOUND-VARIABLE NIL
5009 (HANDLER-CASE
5010 (WITH-OUTPUT-TO-STRING (G13910)
5011 (PRINC % G13910)
5012 (PRINC "a%b%" G13910)
5013 G13910)
5014 (UNBOUND-VARIABLE NIL
5015 (ERROR "Interpolation error in \"%a%b%\"
5016 "))))))))))))))
5017 G13908)))
5018 "23a%b%"))
5019 (() t)))
5021 (with-test (:name (compile equal equalp :transforms))
5022 (let* ((s "foo")
5023 (bit-vector #*11001100)
5024 (values `(nil 1 2 "test"
5025 ;; Floats duplicated here to ensure we get newly created instances
5026 (read-from-string "1.1") (read-from-string "1.2d0")
5027 (read-from-string "1.1") (read-from-string "1.2d0")
5028 1.1 1.2d0 '("foo" "bar" "test")
5029 #(1 2 3 4) #*101010 (make-broadcast-stream) #p"/tmp/file"
5030 ,s (copy-seq ,s) ,bit-vector (copy-seq ,bit-vector)
5031 ,(make-hash-table) #\a #\b #\A #\C
5032 ,(make-random-state) 1/2 2/3)))
5034 (dolist (predicate '(equal equalp))
5035 ;; Test all permutations of different types
5036 (loop for x in values
5037 do (loop for y in values
5038 do (checked-compile-and-assert (:optimize nil)
5039 `(lambda (x y)
5040 (,predicate (the ,(type-of x) x)
5041 (the ,(type-of y) y)))
5042 ((x y) (funcall predicate x y)))))
5043 (checked-compile-and-assert ()
5044 `(lambda (x y)
5045 (,predicate (the (cons (or simple-bit-vector simple-base-string))
5047 (the (cons (or (and bit-vector (not simple-array))
5048 (simple-array character (*))))
5049 y)))
5050 (((list (string 'list)) (list "LIST")) t)))))
5052 (with-test (:name (compile restart-case optimize speed compiler-note)
5053 ;; Cannot-DX note crashes test driver unless we have this:
5054 :skipped-on (not :stack-allocatable-fixed-objects))
5055 (checked-compile '(lambda ()
5056 (declare (optimize speed))
5057 (restart-case () (c ()))))
5058 (checked-compile '(lambda ()
5059 (declare (optimize speed))
5060 (let (x)
5061 (restart-case (setf x (car (compute-restarts)))
5062 (c ()))
5063 x))))
5065 (with-test (:name (compile :copy-more-arg)
5066 :fails-on (or :alpha :hppa :mips :sparc))
5067 ;; copy-more-arg might not copy in the right direction
5068 ;; when there are more fixed args than stack frame slots,
5069 ;; and thus end up splatting a single argument everywhere.
5070 ;; Failing platforms still start their stack frames at 8 slots, so
5071 ;; this is less likely to happen.
5072 (let ((limit 33))
5073 (labels ((iota (n)
5074 (loop for i below n collect i))
5075 (test-function (function skip)
5076 ;; function should just be (subseq x skip)
5077 (loop for i from skip below (+ skip limit) do
5078 (let* ((values (iota i))
5079 (f (apply function values))
5080 (subseq (subseq values skip)))
5081 (assert (equal f subseq)))))
5082 (make-function (n)
5083 (let ((gensyms (loop for i below n collect (gensym))))
5084 (checked-compile `(lambda (,@gensyms &rest rest)
5085 (declare (ignore ,@gensyms))
5086 rest)))))
5087 (dotimes (i limit)
5088 (test-function (make-function i) i)))))
5090 (with-test (:name (compile apply aref bit sbit))
5091 (checked-compile `(lambda (x y) (setf (apply #'aref x y) 21)))
5092 (checked-compile `(lambda (x y) (setf (apply #'bit x y) 1)))
5093 (checked-compile `(lambda (x y) (setf (apply #'sbit x y) 0))))
5095 (with-test (:name (compile :warn-on-the-values-constant))
5096 (multiple-value-bind (fun failure-p)
5097 (checked-compile
5098 ;; The compiler used to elide this test without
5099 ;; noting that the type demands multiple values.
5100 '(lambda () (the (values fixnum fixnum) 1))
5101 :allow-failure t :allow-warnings t)
5102 (assert (functionp fun))
5103 (assert failure-p)))
5105 ;; quantifiers shouldn't cons themselves.
5106 (with-test (:name :quantifiers-no-consing
5107 :skipped-on (or :interpreter
5108 (not :stack-allocatable-closures)))
5109 (let ((constantly-t (lambda (x) x t))
5110 (constantly-nil (lambda (x) x nil))
5111 (list (make-list 1000 :initial-element nil))
5112 (vector (make-array 1000 :initial-element nil)))
5113 (macrolet ((test (quantifier)
5114 (let ((function (make-symbol (format nil "TEST-~A" quantifier))))
5115 `(flet ((,function (function sequence)
5116 (,quantifier function sequence)))
5117 (ctu:assert-no-consing (,function constantly-t list))
5118 (ctu:assert-no-consing (,function constantly-nil vector))))))
5119 (test some)
5120 (test every)
5121 (test notany)
5122 (test notevery))))
5124 (with-test (:name :propagate-complex-type-tests)
5125 (flet ((test (type value)
5126 (let ((ftype (sb-kernel:%simple-fun-type
5127 (checked-compile `(lambda (x)
5128 (if (typep x ',type)
5130 ',value))))))
5131 (assert (typep ftype `(cons (eql function))))
5132 (assert (= 3 (length ftype)))
5133 (let* ((return (third ftype))
5134 (rtype (second return)))
5135 (assert (typep return `(cons (eql values)
5136 (cons t
5137 (cons (eql &optional)
5138 null)))))
5139 (assert (and (subtypep rtype type)
5140 (subtypep type rtype)))))))
5141 (mapc (lambda (params)
5142 (apply #'test params))
5143 `(((unsigned-byte 17) 0)
5144 ((member 1 3 5 7) 5)
5145 ((or symbol (eql 42)) t)))))
5147 (with-test (:name :constant-fold-complex-type-tests)
5148 (assert (equal (sb-kernel:%simple-fun-type
5149 (checked-compile `(lambda (x)
5150 (if (typep x '(member 1 3))
5151 (typep x '(member 1 3 15))
5152 t))))
5153 `(function (t) (values (member t) &optional))))
5154 (assert (equal (sb-kernel:%simple-fun-type
5155 (checked-compile `(lambda (x)
5156 (declare (type (member 1 3) x))
5157 (typep x '(member 1 3 15)))))
5158 `(function ((or (integer 1 1) (integer 3 3)))
5159 (values (member t) &optional)))))
5161 (with-test (:name :quietly-row-major-index-no-dimensions)
5162 (checked-compile `(lambda (x) (array-row-major-index x))))
5164 (with-test (:name :array-rank-transform)
5165 (checked-compile `(lambda (a) (array-rank (the an-imaginary-type a)))
5166 :allow-style-warnings t))
5168 (with-test (:name (:array-rank-fold :bug-1252108))
5169 (let ((notes (nth-value
5170 4 (checked-compile
5171 `(lambda (a)
5172 (typecase a
5173 ((array t 2)
5174 (when (= (array-rank a) 3)
5175 (array-dimension a 2)))))))))
5176 (assert (= 1 (length notes)))))
5178 (assert-error (upgraded-array-element-type 'an-undefined-type))
5180 (with-test (:name :xchg-misencoding)
5181 (checked-compile-and-assert ()
5182 `(lambda (a b)
5183 (declare (type single-float a))
5184 (unless (eql b 1/2)
5185 (min a -1f0)))
5186 ((0f0 1) -1f0)))
5188 (with-test (:name :malformed-declare)
5189 (assert (nth-value
5190 1 (checked-compile `(lambda (x)
5191 (declare (unsigned-byte (x)))
5193 :allow-failure t))))
5195 (with-test (:name :no-dubious-asterisk-warning)
5196 (checked-compile
5197 `(lambda (foo)
5198 (macrolet ((frob-some-stuff (&rest exprs)
5199 (let ((temps
5200 (mapcar
5201 (lambda (x)
5202 (if (symbolp x) (copy-symbol x) (gensym)))
5203 exprs)))
5204 `(let ,(mapcar #'list temps exprs)
5205 (if (and ,@temps)
5206 (format t "Got~@{ ~S~^ and~}~%" ,@temps))))))
5207 (frob-some-stuff *print-base* (car foo))))))
5209 (with-test (:name :interr-type-specifier-hashing)
5210 (let ((specifiers
5211 (remove
5212 'simple-vector
5213 (map 'list
5214 (lambda (saetp)
5215 (sb-c::type-specifier
5216 (sb-c::specifier-type
5217 `(simple-array ,(sb-vm:saetp-specifier saetp) (*)))))
5218 sb-vm:*specialized-array-element-type-properties*))))
5219 (assert (sb-c::%interr-symbol-for-type-spec `(or ,@specifiers)))
5220 (assert (sb-c::%interr-symbol-for-type-spec
5221 `(or ,@specifiers system-area-pointer)))))
5223 (with-test (:name :simple-rank-1-array-*-p-works)
5224 (checked-compile-and-assert ()
5225 `(lambda () (typep #() '(simple-array * (*))))
5226 (() t))
5227 (loop for saetp across sb-vm:*specialized-array-element-type-properties*
5229 (dotimes (n-dimensions 3) ; test ranks 0, 1, and 2.
5230 (let ((dims (make-list n-dimensions :initial-element 2)))
5231 (dolist (adjustable-p '(nil t))
5232 (let ((a (make-array dims :element-type (sb-vm:saetp-specifier saetp)
5233 :adjustable adjustable-p)))
5234 (assert (eq (and (= n-dimensions 1) (not adjustable-p))
5235 (typep a '(simple-array * (*)))))))))))
5237 (with-test (:name :array-subtype-tests
5238 :skipped-on (:not (:or :x86 :x86-64)))
5239 (checked-compile-and-assert ()
5240 `(lambda ()
5241 (typep #() '(or simple-vector simple-string)))
5242 (() t))
5243 (flet ((approx-lines-of-assembly-code (type-expr)
5244 (count #\Newline
5245 (with-output-to-string (s)
5246 (disassemble
5247 `(lambda (x)
5248 (declare (optimize (sb-c::verify-arg-count 0)))
5249 (typep x ',type-expr))
5250 :stream s)))))
5251 ;; These are fragile, but less bad than the possibility of messing up
5252 ;; any vops, especially since the generic code in 'vm-type' checks for
5253 ;; a vop by its name in a place that would otherwise be agnostic of the
5254 ;; backend were it not for my inability to test all platforms.
5255 (assert (< (approx-lines-of-assembly-code
5256 '(simple-array * (*))) 25))
5257 ;; this tested all possible widetags one at a time, e.g. in VECTOR-SAP
5258 (assert (< (approx-lines-of-assembly-code
5259 '(sb-kernel:simple-unboxed-array (*))) 25))
5260 ;; This is actually a strange type but it's what ANSI-STREAM-READ-N-BYTES
5261 ;; declares as its buffer, which would choke in %BYTE-BLT if you gave it
5262 ;; (simple-array t (*)). But that's a different problem.
5263 (assert (< (approx-lines-of-assembly-code
5264 '(or system-area-pointer (simple-array * (*)))) 29))
5265 ;; And this was used by %BYTE-BLT which tested widetags one-at-a-time.
5266 (assert (< (approx-lines-of-assembly-code
5267 '(or system-area-pointer (sb-kernel:simple-unboxed-array (*))))
5268 29))))
5270 (with-test (:name :local-argument-mismatch-error-string)
5271 (multiple-value-bind (fun failurep warnings)
5272 (checked-compile `(lambda (x)
5273 (flet ((foo ()))
5274 (foo x)))
5275 :allow-warnings t)
5276 (declare (ignore failurep))
5277 (assert (= 1 (length warnings)))
5278 (multiple-value-bind (ok err) (ignore-errors (funcall fun 42))
5279 (assert (not ok))
5280 (assert (search "FLET FOO" (princ-to-string err))))))
5282 (with-test (:name :bug-1310574-0)
5283 (checked-compile `(lambda (a)
5284 (typecase a
5285 ((or (array * (* * 3)) (array * (* * 4)))
5286 (case (array-rank a)
5287 (2 (aref a 1 2))))))))
5289 (with-test (:name :bug-1310574-1)
5290 (checked-compile `(lambda (a)
5291 (typecase a
5292 ((or (array * ()) (array * (1)) (array * (1 2)))
5293 (case (array-rank a)
5294 (3 (aref a 1 2 3))))))))
5296 (with-test (:name :bug-573747)
5297 (assert (nth-value
5298 1 (checked-compile `(lambda (x) (progn (declare (integer x)) (* x 6)))
5299 :allow-failure t))))
5301 ;; Something in this function used to confuse lifetime analysis into
5302 ;; recording multiple conflicts for a single TNs in the dolist block.
5303 (with-test (:name :bug-1327008)
5304 (checked-compile
5305 `(lambda (scheduler-spec
5306 schedule-generation-method
5307 utc-earliest-time utc-latest-time
5308 utc-other-earliest-time utc-other-latest-time
5309 &rest keys
5310 &key queue
5311 maximum-mileage
5312 maximum-extra-legs
5313 maximum-connection-time
5314 slice-number
5315 scheduler-hints
5316 permitted-route-locations prohibited-route-locations
5317 preferred-connection-locations disfavored-connection-locations
5318 origins destinations
5319 permitted-carriers prohibited-carriers
5320 permitted-operating-carriers prohibited-operating-carriers
5321 start-airports end-airports
5322 circuity-limit
5323 specified-circuity-limit-extra-miles
5324 (preferred-carriers :unspecified)
5325 &allow-other-keys)
5326 (declare (optimize speed))
5327 (let ((table1 (list nil))
5328 (table2 (list nil))
5329 (skip-flifo-checks (getf scheduler-spec :skip-flifo-checks))
5330 (construct-gaps-p (getf scheduler-spec :construct-gaps-p))
5331 (gap-locations (getf scheduler-spec :gap-locations))
5332 (result-array (make-array 100))
5333 (number-dequeued 0)
5334 (n-new 0)
5335 (n-calcs 0)
5336 (exit-reason 0)
5337 (prev-start-airports origins)
5338 (prev-end-airports destinations)
5339 (prev-permitted-carriers permitted-carriers))
5340 (flet ((run-with-hint (hint random-magic other-randomness
5341 maximum-extra-legs
5342 preferred-origins
5343 preferred-destinations
5344 same-pass-p)
5345 (let* ((hint-permitted-carriers (first hint))
5346 (preferred-end-airports
5347 (ecase schedule-generation-method
5348 (:DEPARTURE preferred-destinations)
5349 (:ARRIVAL preferred-origins)))
5350 (revised-permitted-carriers
5351 (cond ((and hint-permitted-carriers
5352 (not (eq permitted-carriers :ANY)))
5353 (intersection permitted-carriers
5354 hint-permitted-carriers))
5355 (hint-permitted-carriers)
5356 (permitted-carriers)))
5357 (revised-maximum-mileage
5358 (min (let ((maximum-mileage 0))
5359 (dolist (o start-airports)
5360 (dolist (d end-airports)
5361 (setf maximum-mileage
5362 (max maximum-mileage (mileage o d)))))
5363 (round (+ (* circuity-limit maximum-mileage)
5364 (or specified-circuity-limit-extra-miles
5365 (hairy-calculation slice-number)))))
5366 maximum-mileage)))
5367 (when (or (not (equal start-airports prev-start-airports))
5368 (not (equal end-airports prev-end-airports))
5369 (and (not (equal revised-permitted-carriers
5370 prev-permitted-carriers))))
5371 (incf n-calcs)
5372 (calculate-vectors
5373 prohibited-carriers
5374 permitted-operating-carriers
5375 prohibited-operating-carriers
5376 permitted-route-locations
5377 prohibited-route-locations
5378 construct-gaps-p
5379 gap-locations
5380 preferred-carriers)
5381 (setf prev-permitted-carriers revised-permitted-carriers))
5382 (multiple-value-bind (this-number-dequeued
5383 this-exit-reason
5384 this-n-new)
5385 (apply #'schedule-loop
5386 utc-earliest-time utc-other-earliest-time
5387 utc-latest-time utc-other-latest-time
5388 scheduler-spec schedule-generation-method
5389 queue
5390 :maximum-mileage revised-maximum-mileage
5391 :maximum-extra-legs maximum-extra-legs
5392 :maximum-connection-time maximum-connection-time
5393 :same-pass-p same-pass-p
5394 :preferred-end-airports preferred-end-airports
5395 :maximum-blah random-magic
5396 :skip-flifo-checks skip-flifo-checks
5397 :magic1 table1
5398 :magic2 table2
5399 :preferred-connection-locations preferred-connection-locations
5400 :disfavored-connection-locations disfavored-connection-locations
5401 keys)
5402 (when other-randomness
5403 (loop for i fixnum from n-new to (+ n-new (1- this-n-new))
5404 do (hairy-calculation i result-array)))
5405 (incf number-dequeued this-number-dequeued)
5406 (incf n-new this-n-new)
5407 (setq exit-reason (logior exit-reason this-exit-reason))))))
5408 (let ((n-hints-processed 0))
5409 (dolist (hint scheduler-hints)
5410 (run-with-hint hint n-hints-processed t 0
5411 nil nil nil)
5412 (incf n-hints-processed)))
5413 (run-with-hint nil 42 nil maximum-extra-legs
5414 '(yyy) '(xxx) t))
5415 exit-reason))
5416 :allow-style-warnings t))
5418 (with-test (:name :dead-code-in-optional-dispatch)
5419 ;; the translation of each optional entry is
5420 ;; (let ((#:g (error "nope"))) (funcall #<clambda> ...))
5421 ;; but the funcall is unreachable. Since this is an artifact of how the
5422 ;; lambda is converted, it should not generate a note as if in user code.
5423 (checked-compile
5424 `(lambda (a &optional (b (error "nope")) (c (error "nope")))
5425 (values c b a))))
5427 (with-test (:name :nth-value-of-non-constant-N :skipped-on :interpreter)
5428 (labels ((foo (n f) (nth-value n (funcall f)))
5429 (bar () (values 0 1 2 3 4 5 6 7 8 9)))
5430 (assert (= (foo 5 #'bar) 5)) ; basic correctness
5431 (assert (eq (foo 12 #'bar) nil))
5432 (ctu:assert-no-consing (eql (foo 953 #'bar) 953))))
5434 (with-test (:name :position-derive-type-optimizer)
5435 (assert-code-deletion-note
5436 '(lambda (x) ; the call to POSITION can't return 4
5437 (let ((i (position x #(a b c d) :test 'eq)))
5438 (case i (4 'nope) (t 'okeydokey))))))
5440 ;; lp# 310267
5441 (with-test (:name (optimize :quality-multiply-specified :bug-310267))
5442 (let ((sb-c::*policy* sb-c::*policy*)) ; to keep this test pure
5443 (assert-signal (proclaim '(optimize space debug (space 0)))
5444 style-warning)
5445 (flet ((test (form)
5446 (assert (= 1 (length (nth-value
5447 3 (checked-compile
5448 form :allow-style-warnings t)))))))
5449 (test `(lambda () (declare (optimize speed (speed 0))) 5))
5450 (test `(lambda () (declare (optimize speed) (optimize (speed 0))) 5))
5451 (test `(lambda ()
5452 (declare (optimize speed)) (declare (optimize (speed 0)))
5453 5)))
5455 ;; these are OK
5456 (assert-no-signal (proclaim '(optimize (space 3) space)))
5457 (checked-compile `(lambda () (declare (optimize speed (speed 3))) 5))
5458 (checked-compile `(lambda () (declare (optimize speed) (optimize (speed 3))) 5))
5459 (checked-compile `(lambda ()
5460 (declare (optimize speed)) (declare (optimize (speed 3)))
5461 5))))
5463 (with-test (:name (truncate :type-derivation))
5464 (checked-compile-and-assert ()
5465 `(lambda (a b)
5466 (truncate a (the (rational (1) (3)) b)))
5467 ((10 5/2) (values 4 0))))
5469 (with-test (:name :constantp-on-a-literal-function-works)
5470 (assert (constantp `(the (function (list) t) ,#'car))))
5472 (with-test (:name :arg-count-error)
5473 (assert (eq :win (handler-case (funcall (intern "CONS") 1 2 3)
5474 (sb-int:simple-program-error () :win)
5475 (condition () :lose)))))
5477 (with-test (:name :mv-conversion)
5478 (checked-compile `(lambda (a)
5479 (tagbody (go 0)
5480 (list (unwind-protect a))
5481 (multiple-value-call #'list
5482 (values (catch 'ct5 (go 0))))
5483 0))))
5485 (with-test (:name (:null-cleanups-1 :bug-1416704 :bug-404441))
5486 (let ((x (funcall
5487 (checked-compile
5488 `(lambda ()
5489 (lambda (x)
5490 (declare (optimize speed))
5491 (if x
5492 (funcall (flet ((bar () 10)) #'bar))
5493 (funcall (flet ((fez ()
5494 (funcall (flet ((foo () 20)) #'foo))))
5495 #'fez)))))))))
5496 (assert (= (funcall x t) 10))
5497 (assert (= (funcall x nil) 20))))
5499 (with-test (:name (:null-cleanups-2 :bug-1416704 :bug-404441))
5500 (let ((fun (funcall
5501 (checked-compile
5502 `(lambda ()
5503 (lambda (x)
5504 (declare (optimize speed))
5505 (let* ((a2 (lambda () 20))
5506 (a4 (lambda ()))
5507 (a0 (flet ((f () (funcall a2)))
5508 #'f))
5509 (a3 (lambda ()
5510 (if x
5511 (if x
5512 (throw 'x 10)
5513 (let ((a5 (lambda () (funcall a4))))
5514 (funcall a5)))
5515 (funcall a0)))))
5516 (funcall a3))))))))
5517 (assert (= (catch 'x (funcall fun t)) 10))
5518 (assert (= (catch 'x (funcall fun nil)) 20))))
5521 (with-test (:name :locall-already-let-converted)
5522 (assert (eq (funcall
5523 (funcall
5524 (checked-compile
5525 `(lambda ()
5526 (flet ((call (ff)
5527 (flet ((f () (return-from f ff)))
5528 (declare (inline f))
5530 (f))))
5531 (declare (inline call))
5532 (call 1)
5533 (call (lambda () 'result)))))))
5534 'result)))
5536 (with-test (:name :debug-dump-elsewhere)
5537 (assert (eql (catch 'x
5538 (funcall
5539 (checked-compile
5540 `(lambda ()
5541 (declare (optimize debug))
5542 (throw 'x *)))))
5543 *)))
5545 (with-test (:name (typep :quasiquoted-constant))
5546 (assert (null (ctu:find-named-callees
5547 (checked-compile
5548 `(lambda (x)
5549 (typep x `(signed-byte ,sb-vm:n-word-bits))))))))
5551 (with-test (:name (logior :transform))
5552 (multiple-value-bind (fun failurep warnings)
5553 (checked-compile `(lambda (c)
5554 (flet ((f (x)
5555 (the integer x)))
5556 (logior c (f nil))))
5557 :allow-warnings t)
5558 (assert failurep)
5559 (assert (= 1 (length warnings)))
5560 (assert-error (funcall fun 10) type-error)))
5562 (with-test (:name :eql/integer-folding)
5563 (checked-compile
5564 `(lambda (a)
5565 (fceiling (the (member 2.3 21672589639883401935) a)))))
5567 (with-test (:name (position :derive-type))
5568 (let ((f (checked-compile
5569 `(lambda (x)
5570 (declare (type (simple-string 90) x))
5571 (declare (muffle-conditions code-deletion-note))
5572 (let ((b (position #\i x)))
5573 (if (and (integerp b) (> b 100))
5574 'yikes 'okey-dokey))))))
5575 ;; The function can not return YIKES
5576 (assert (not (ctu:find-code-constants f :type '(eql yikes))))))
5578 (with-test (:name :compile-file-error-position-reporting)
5579 (dolist (input '("data/wonky1.lisp" "data/wonky2.lisp" "data/wonky3.lisp"))
5580 (let ((expect (with-open-file (f input) (read f))))
5581 (assert (stringp expect))
5582 (let ((err-string (with-output-to-string (*error-output*)
5583 (compile-file input :print nil))))
5584 (assert (search expect err-string))))))
5586 (with-test (:name (coerce :derive-type))
5587 (macrolet ((check (type ll form &rest values)
5588 `(assert (equal (funcall (checked-compile
5589 `(lambda ,',ll
5590 (ctu:compiler-derived-type ,',form)))
5591 ,@values)
5592 ',type))))
5593 (check list
5595 (coerce a 'list)
5596 nil)
5597 (check (unsigned-byte 32)
5599 (coerce a '(unsigned-byte 32))
5601 (check character
5602 (a x)
5603 (coerce a (array-element-type (the (array character) x)))
5605 "abc")
5606 (check (unsigned-byte 32)
5607 (a x)
5608 (coerce a (array-element-type (the (array (unsigned-byte 32)) x)))
5610 (make-array 10 :element-type '(unsigned-byte 32)))))
5612 (with-test (:name :associate-args)
5613 (flet ((test (form argument)
5614 (multiple-value-bind (fun failurep warnings)
5615 (checked-compile form :allow-warnings t)
5616 (assert failurep)
5617 (assert (= 1 (length warnings)))
5618 (assert-error (funcall fun argument)))))
5619 (test `(lambda (x) (+ 1 x nil)) 2)
5620 (test `(lambda (x) (/ 1 x nil)) 4)))
5622 (with-test (:name :eager-substitute-single-use-lvar)
5623 (checked-compile-and-assert ()
5624 `(lambda (a)
5625 (let ((a (the fixnum a))
5626 (x 1)
5628 (tagbody
5629 (flet ((jump () (go loop)))
5630 (jump))
5631 loop
5632 (setf z (the fixnum (if (= x 1) #xFFF a)))
5633 (unless (= x 0)
5634 (setf x 0)
5635 (go loop)))
5637 ((0) 0)
5638 ((2) 2)
5639 ((255) 255)))
5641 (with-test (:name :vop-on-eql-type)
5642 (assert (= (funcall
5643 (funcall (checked-compile
5644 `(lambda (b)
5645 (declare ((eql -7) b)
5646 (optimize debug))
5647 (lambda (x)
5648 (logior x b))))
5651 -5)))
5653 (with-test (:name :vop-on-eql-type.2)
5654 (assert (integerp
5655 (funcall
5656 (funcall (checked-compile
5657 `(lambda (b)
5658 (declare ((eql -7) b)
5659 (optimize debug))
5660 (lambda ()
5661 (+ (random 10) b))))
5662 -7)))))
5664 (with-test (:name :vop-on-eql-type.3)
5665 (assert (integerp
5666 (funcall
5667 (funcall (checked-compile
5668 `(lambda (b)
5669 (declare ((eql -7) b)
5670 (optimize (compilation-speed 0) debug))
5671 (lambda ()
5672 (+ (random 10) b))))
5673 -7)))))
5675 (flet ((test (form)
5676 (multiple-value-bind (fun failurep)
5677 (checked-compile `(lambda () ,form)
5678 :allow-failure t)
5679 (assert failurep)
5680 (assert-error (funcall fun) sb-int:compiled-program-error))))
5682 (with-test (:name (compile macrolet :malformed))
5683 (test '(macrolet (foo () 'bar)))
5684 (test '(macrolet x))
5685 (test '(symbol-macrolet x))
5686 (test '(symbol-macrolet (x))))
5688 (with-test (:name (compile flet :malformed))
5689 (test '(flet (foo () 'bar)))
5690 (test '(flet x))
5691 (test '(labels (foo () 'bar)))
5692 (test '(labels x))))
5694 (with-test (:name :compile-load-time-value-interpreted-mode)
5695 ;; This test exercises the same pattern as HANDLER-BIND (to a
5696 ;; degree). In particular a HANDLER-BIND that was compiled when the
5697 ;; *EVALUATOR-MODE* was :INTERPRET would not compile its class
5698 ;; predicates, because LOAD-TIME-VALUE just called EVAL, and you
5699 ;; would get back a list with an interpreted function in it.
5701 ;; In the code below, this function when called would generate a new
5702 ;; symbol each time. But if the compiler processes the guts as it
5703 ;; should, you get back a compiled lambda which returns a constant
5704 ;; symbol.
5705 (let ((f (let ((sb-ext:*evaluator-mode* :interpret))
5706 (checked-compile
5707 `(lambda ()
5708 (load-time-value
5709 (list (lambda ()
5710 (macrolet ((foo ()
5711 (sb-int:keywordicate (gensym))))
5712 (foo))))))))))
5713 (eq (funcall (car (funcall f)))
5714 (funcall (car (funcall f))))))
5716 (with-test (:name :constant-fold-%eql/integer)
5717 (checked-compile-and-assert ()
5718 `(lambda (x)
5719 (declare (type (complex single-float) x))
5720 (member (the (eql #c(0.0 0.0)) x)
5721 '(1 2 3 9912477572127105188)))
5722 ((#C(0.0 0.0)) nil)))
5724 (with-test (:name (compile svref :constant))
5725 (checked-compile-and-assert ()
5726 `(lambda () (svref #(1 2 3) 1))
5727 (() 2)))
5729 (with-test (:name (compile char-equal :type-intersection))
5730 (checked-compile-and-assert ()
5731 `(lambda (x y)
5732 (char-equal (the (member #\a #\B) x)
5733 (the (eql #\A) y)))
5734 ((#\a #\A) t)))
5736 (with-test (:name (oddp fixnum :no-consing)
5737 :skipped-on :interpreter)
5738 (let ((f (checked-compile '(lambda (x) (oddp x)))))
5739 (ctu:assert-no-consing (funcall f most-positive-fixnum))))
5740 (with-test (:name (oddp bignum :no-consing)
5741 :skipped-on :interpreter)
5742 (let ((f (checked-compile '(lambda (x) (oddp x))))
5743 (x (* most-positive-fixnum most-positive-fixnum 3)))
5744 (ctu:assert-no-consing (funcall f x))))
5745 (with-test (:name (logtest fixnum :no-consing :bug-1277690)
5746 :skipped-on :interpreter)
5747 (let ((f (checked-compile '(lambda (x) (logtest x most-positive-fixnum)))))
5748 (ctu:assert-no-consing (funcall f 1))))
5749 (with-test (:name (logtest bignum :no-consing)
5750 :skipped-on :interpreter)
5751 (let ((f (checked-compile '(lambda (x) (logtest x 1))))
5752 (x (* most-positive-fixnum most-positive-fixnum 3)))
5753 (ctu:assert-no-consing (funcall f x))))
5755 (with-test (:name (sb-c::mask-signed-field :randomized))
5756 (let (result)
5757 (dotimes (i 1000)
5758 (let* ((ool (checked-compile '(lambda (s i)
5759 (sb-c::mask-signed-field s i))))
5760 (size (random (* sb-vm:n-word-bits 2)))
5761 (constant (checked-compile `(lambda (i)
5762 (sb-c::mask-signed-field ,size i))))
5763 (arg (- (random (* most-positive-fixnum 8)) (* most-positive-fixnum 4)))
5764 (declared (checked-compile `(lambda (i)
5765 (declare (type (integer ,(- (abs arg)) ,(abs arg)) i))
5766 (sb-c::mask-signed-field ,size i))))
5767 (ool-answer (funcall ool size arg))
5768 (constant-answer (funcall constant arg))
5769 (declared-answer (funcall declared arg)))
5770 (unless (= ool-answer constant-answer declared-answer)
5771 (push (list size arg ool-answer constant-answer declared-answer) result))))
5772 (assert (null result))))
5774 (with-test (:name (array-dimension *))
5775 (checked-compile-and-assert ()
5776 `(lambda (array)
5777 (declare ((or (vector t) (array character)) array))
5778 (array-dimension array 0))
5779 ((#(1 2 3)) 3)))
5781 (with-test (:name :generate-type-checks-on-dead-blocks)
5782 (checked-compile-and-assert ()
5783 `(lambda (a b)
5784 (declare (type (member vector 42) a))
5785 (map a 'list (the vector b) #*))
5786 (('vector #()) #() :test #'equalp)))
5788 (with-test (:name (make-list :large 1))
5789 (checked-compile `(lambda ()
5790 (make-list (expt 2 28) :initial-element 0))))
5792 (with-test (:name (make-list :large 2)
5793 :skipped-on (not :64-bit))
5794 (checked-compile `(lambda ()
5795 (make-list (expt 2 30) :initial-element 0))))
5797 (with-test (:name :bad-cond)
5798 (assert-error
5799 (checked-compile
5800 '(lambda () (cond (t 10) 20)))))
5802 (with-test (:name :removed-dx-cast)
5803 (checked-compile-and-assert ()
5804 `(lambda ()
5805 (loop
5806 (let ((x (the integer (return 0))))
5807 (declare (dynamic-extent x))
5808 (unwind-protect x 1))))
5809 (() 0)))
5811 (with-test (:name (isqrt :derivation))
5812 (checked-compile-and-assert ()
5813 `(lambda (i)
5814 (isqrt (count (the bit i) #*11101)))
5815 ((1) 2)))
5817 (with-test (:name :vector-zero-initialization)
5818 (assert (equalp (funcall (funcall (checked-compile
5819 `(lambda (x b)
5820 (declare ((eql 0) x)
5821 (optimize (debug 2)))
5822 (lambda ()
5823 (vector x (isqrt b)))))
5824 0 4))
5825 #(0 2))))
5827 (with-test (:name :cons-zero-initialization)
5828 (assert (equalp (funcall (funcall (checked-compile
5829 `(lambda (x b)
5830 (declare ((eql 0) x)
5831 (optimize (debug 2)))
5832 (lambda ()
5833 (cons x (isqrt b)))))
5834 0 4))
5835 '(0 . 2))))
5837 (with-test (:name :check-important-result-warning)
5838 (multiple-value-bind (fun failure warnings style-warnings)
5839 (checked-compile '(lambda (x z)
5840 (declare (notinline nintersection))
5841 (nintersection x z) x)
5842 :allow-style-warnings t)
5843 (declare (ignore fun failure warnings))
5844 (loop for c in style-warnings
5846 (assert (search "NINTERSECTION"
5847 (princ-to-string c))))))
5849 (with-test (:name :destroyed-constant-warning)
5850 (multiple-value-bind (fun failure warnings)
5851 (checked-compile '(lambda ()
5852 (declare (notinline nunion))
5853 (nunion '(1 2 3) '(1 2 4)))
5854 :allow-warnings t)
5855 (declare (ignore fun failure))
5856 (loop for c in warnings
5858 (assert (search "NUNION"
5859 (princ-to-string c))))))
5861 (with-test (:name :%array-data-complex-type-derivation)
5862 (let ((type (funcall (checked-compile
5863 `(lambda (x)
5864 (ctu:compiler-derived-type (sb-kernel:%array-data (the array x)))))
5865 #2A())))
5866 (assert (eq type 'array))))
5868 (with-test (:name :equalp-transofrm)
5869 (assert
5870 (funcall (checked-compile
5871 `(lambda (x y)
5872 (equalp (the (simple-array single-float (*)) x)
5873 (the (simple-array double-float (*)) y))))
5874 (coerce '(1f0) '(simple-array single-float (*)))
5875 (coerce '(1d0) '(simple-array double-float (*))))))
5877 (with-test (:name :array-hairy-type-derivation)
5878 (assert
5879 (equal (funcall (checked-compile
5880 `(lambda (x)
5881 (subseq (the (and (satisfies sb-impl::vector-with-fill-pointer-p)
5882 (string 3)) x)
5883 1)))
5884 (make-array 3 :element-type 'character
5885 :fill-pointer t
5886 :initial-contents "abc"))
5887 "bc")))
5889 (with-test (:name :nreverse-derive-type)
5890 (assert
5891 (not (funcall (checked-compile
5892 '(lambda (x)
5893 (eql (car (nreverse (the (cons (eql 10)) x))) 10)))
5894 '(10 20)))))
5896 (with-test (:name :subseq-derive-type)
5897 (assert
5898 (equalp (funcall (checked-compile
5899 '(lambda (x)
5900 (subseq (the (simple-vector 3) x) 1)))
5901 #(1 2 3))
5902 #(2 3))))
5904 (with-test (:name :sequence-derive-type)
5905 (assert
5906 (equalp (funcall (checked-compile
5907 '(lambda (x)
5908 (copy-seq (the (and string (not (simple-array nil))) x))))
5909 (make-array 3 :element-type 'character
5910 :fill-pointer 2
5911 :initial-contents "123"))
5912 "12")))
5914 (with-test (:name :sequence-derive-type.2)
5915 (assert
5916 (funcall (checked-compile
5917 '(lambda (x y)
5918 (equal (the (and string (not (simple-array nil))) x) y)))
5919 (make-array 3 :element-type 'character
5920 :fill-pointer 2
5921 :initial-contents "123")
5922 "12")))
5924 (with-test (:name :sequence-derive-type.3)
5925 (assert
5926 (equalp (funcall (checked-compile
5927 '(lambda (x)
5928 (subseq (the (or (simple-array * (*)) string) x) 0 2)))
5929 #(1 2 3))
5930 #(1 2))))
5932 (with-test (:name :not-enough-values-cast)
5933 (assert
5934 (not (funcall (checked-compile
5935 `(lambda ()
5936 (car (describe 1 (make-broadcast-stream)))))))))
5938 ;; To check the :EXIT-DELETION tests below, enable the following form,
5939 ;; which allows the compiler to delete all vestigial exits, even if it
5940 ;; "shouldn't", which should case the :EXIT-DELETION tests to fail in
5941 ;; various ways.
5942 #+(or)
5943 (without-package-locks
5944 (defun sb-c::may-delete-vestigial-exit (cast)
5945 (declare (ignore cast))
5948 ;; Vestigial exit deletion was a bit too aggressive, causing stack
5949 ;; analysis to decide that the value of (BAR 10) in both cases below
5950 ;; needed to be nipped out from under the dynamic-extent allocation of
5951 ;; Y (or #'Y), which %NIP-VALUES refused to do (DX values must not be
5952 ;; moved once allocated).
5953 (with-test (:name (compile :exit-deletion :bug-1563127 :variable))
5954 (checked-compile '(lambda (x)
5955 (block test
5956 (multiple-value-prog1 (bar 10)
5957 (let ((y (list x)))
5958 (declare (dynamic-extent y))
5959 (bar y)
5960 (if x
5961 (return-from test))))))
5962 :allow-style-warnings t))
5964 (with-test (:name (compile :exit-deletion :bug-1563127 :function))
5965 (checked-compile '(lambda (x)
5966 (block test
5967 (multiple-value-prog1 (bar 10)
5968 (flet ((y () (list x)))
5969 (declare (dynamic-extent #'y))
5970 (bar #'y)
5971 (if x
5972 (return-from test))))))
5973 :allow-style-warnings t))
5975 (with-test (:name (compile :exit-deletion :bug-533930))
5976 (checked-compile '(lambda ()
5977 (block a
5978 (multiple-value-prog1 42
5979 (catch 'ct
5980 (let ((x (cons t t)))
5981 (declare (dynamic-extent x))
5982 (return-from a (catch 'ct (foo x))))))))
5983 :allow-style-warnings t))
5985 (with-test (:name (compile :exit-deletion :bug-518099))
5986 (checked-compile '(lambda (a)
5987 (block b1
5988 (multiple-value-prog1 42
5989 (catch 'ct
5990 (return-from b1
5991 (catch 'ct2
5992 (min 1 a)))))))))
5994 (with-test (:name (compile :exit-deletion :bug-1655011))
5995 (checked-compile '(lambda (x)
5996 (block nil
5997 (multiple-value-prog1 (catch 'ct)
5998 (let ((* (list 10)))
5999 (declare (dynamic-extent *))
6000 (if x
6001 (return))))))))
6003 (with-test (:name (compile :exit-deletion :2017-01-30))
6004 (checked-compile '(lambda (b c)
6005 (block b5
6006 (multiple-value-prog1 42
6007 (restart-bind nil
6008 (if b (return-from b5
6009 (catch 'foo c)))))))))
6011 (with-test (:name (compile :exit-deletion :2017-01-30 :even-more-subtle))
6012 (checked-compile '(lambda (b c)
6013 (block b5
6014 (multiple-value-prog1 42
6015 (restart-bind nil
6016 (if b (return-from b5
6017 (catch 'foo
6018 (error "even more subtle"))))))))
6019 :allow-style-warnings t))
6021 (with-test (:name (compile :exit-deletion :2017-01-31 :tagbody))
6022 (let ((test-closure
6023 (checked-compile '(lambda (b c)
6024 (declare (notinline funcall))
6025 (block b5
6026 (multiple-value-prog1 42
6027 (if b (tagbody
6028 (return-from b5
6029 (funcall c (lambda () (go away))))
6030 away))))))))
6031 ;; Be careful here: The return value can be garbage. Our saving
6032 ;; grace is that it's stack garbage, thus by definition GC-safe to
6033 ;; hold in a register long enough to take its address, but we
6034 ;; really don't want to try and externalize it in any way.
6035 (assert (= (sb-kernel:get-lisp-obj-address
6036 (funcall test-closure t #'funcall))
6037 (sb-kernel:get-lisp-obj-address
6038 42)))))
6040 (with-test (:name (compile :exit-deletion :2017-03-29 :tagbody))
6041 (checked-compile '(lambda ()
6042 (block foo
6043 (multiple-value-prog1 42
6044 (tagbody
6045 (return-from foo
6046 (catch 'ct (go tag6)))
6047 tag6))))))
6049 (with-test (:name (compile :exit-deletion :bug-1723993 :ignoring-block-value))
6050 (checked-compile '(lambda (x)
6051 (block b1
6052 (multiple-value-prog1 0
6053 (block b2
6054 (return-from b1
6055 (catch 'c
6056 (return-from b2
6057 x)))))))))
6059 (with-test (:name :mv-call-no-let-conversion)
6060 (assert (equal
6061 (funcall
6062 (checked-compile
6063 '(lambda ()
6064 (locally (declare (optimize (sb-c::let-conversion 0)))
6065 (multiple-value-call #'lisp-implementation-version (values))))))
6066 (lisp-implementation-version)))
6067 (assert (equal
6068 (funcall
6069 (checked-compile
6070 '(lambda ()
6071 (locally (declare (optimize (sb-c::let-conversion 0)))
6072 (multiple-value-call #'lisp-implementation-type (values))))))
6073 (lisp-implementation-type)))
6074 (assert (equal
6075 (funcall
6076 (checked-compile
6077 '(lambda ()
6078 (locally (declare (optimize (sb-c::let-conversion 0)))
6079 (multiple-value-call #'princ-to-string 1)))))
6080 "1")))
6082 (with-test (:name :mv-call-argument-mismatch)
6083 (assert
6084 (nth-value 2
6085 (checked-compile
6086 '(lambda () (multiple-value-call #'cons 1 2 3))
6087 :allow-warnings t))))
6089 (with-test (:name :valid-callable-argument-cast)
6090 (assert (equal (funcall (checked-compile '(lambda (x)
6091 (find-if (the function #'oddp)
6092 x)))
6093 '(2 4 3))
6094 3)))
6096 (with-test (:name :usigned-word-float-conversion)
6097 (assert (= (rational (funcall (checked-compile `(lambda (x)
6098 (float (the sb-ext:word x) 1d0)))
6099 sb-ext:most-positive-word))
6100 #+32-bit 4294967295
6101 #+64-bit 18446744073709551616)))
6103 (with-test (:name :callable-argument-mismatch-on-xep)
6104 (checked-compile-and-assert ()
6105 `(lambda (s x)
6106 (locally (declare (notinline reduce))
6107 (reduce (lambda (a b)
6108 (+ a b x))
6109 s)))
6110 (('(1 2) 3) 6))
6111 (checked-compile-and-assert ()
6112 `(lambda (s x)
6113 (locally (declare (notinline reduce))
6114 (reduce (lambda (&optional a b z)
6115 (declare (ignore z))
6116 (+ a b x))
6117 s)))
6118 (('(1 2) 3) 6)))
6120 (with-test (:name (multiple-value-call :type-checking-rest))
6121 (checked-compile-and-assert (:allow-warnings t
6122 :optimize :safe)
6123 `(lambda (list)
6124 (multiple-value-call
6125 (lambda (&optional a &rest r)
6126 (declare ((satisfies eval) r)
6127 (ignore r))
6128 (list a))
6129 (values-list list)))
6130 (('(1 list 2)) '(1))
6131 (('(1)) (condition 'type-error))))
6133 (with-test (:name (multiple-value-call :type-checking-rest.2))
6134 (checked-compile-and-assert (:allow-warnings t
6135 :optimize :safe)
6136 `(lambda (list)
6137 (multiple-value-call
6138 (lambda (&optional a &rest r)
6139 (declare (null r)
6140 (ignore r))
6141 (list a))
6142 (values-list list)))
6143 (('(1 list 2)) (condition 'type-error))
6144 (('(1)) '(1))))
6146 (with-test (:name (multiple-value-call :type-checking-rest :type-derivation))
6147 (checked-compile-and-assert (:allow-warnings t
6148 :optimize :safe)
6149 `(lambda (list)
6150 (multiple-value-call
6151 (lambda (&optional a &rest r)
6152 (declare (cons r)
6153 (ignore r))
6154 (list a))
6155 (values-list list)))
6156 (('(1 2)) '(1))
6157 (('(1)) (condition 'type-error))))
6159 (with-test (:name :delete-optional-dispatch-xep)
6160 (let ((name (gensym)))
6161 (checked-compile-and-assert ()
6162 `(sb-int:named-lambda ,name (&optional x)
6163 (if (= x 0)
6165 (multiple-value-call #',name (1- x))))
6166 ((3) 10))))
6168 (with-test (:name (yes-or-no-p type))
6169 (checked-compile `(lambda ()
6170 (yes-or-no-p nil)))
6171 (checked-compile `(lambda ()
6172 (y-or-n-p nil)))
6173 (checked-compile `(lambda ()
6174 (yes-or-no-p #'list)))
6175 (checked-compile `(lambda ()
6176 (y-or-n-p #'list))))
6178 (with-test (:name :callable-delayed-mismatch)
6179 (multiple-value-bind (fun failure-p warnings)
6180 (checked-compile '(lambda () (let ((f 'cons)) (find-if f '(10))))
6181 :allow-warnings 'simple-warning)
6182 (declare (ignore fun))
6183 (assert failure-p)
6184 (assert (= (length warnings) 1))
6185 (search "The function CONS is called by"
6186 (princ-to-string (first warnings)))))
6188 (with-test (:name :set-type-conflict)
6189 (assert (nth-value 1
6190 (checked-compile
6191 '(lambda () (set '// 10))
6192 :allow-warnings t))))
6194 (with-test (:name :two-arg-funs-check)
6195 (loop for (nil x) in sb-c::*two-arg-functions*
6197 (assert (fboundp x))
6198 (assert (sb-int:info :function :info x))))
6200 (with-test (:name :two-arg-with-two-arguments-only)
6201 (checked-compile-and-assert ()
6202 `(lambda (x y) (string-lessp x y :start1 0))
6203 (("a" "b") 0)))
6205 (with-test (:name :optimize-functional-arguments-casts)
6206 (checked-compile-and-assert (:optimize :safe)
6207 '(lambda (list key)
6208 (declare (type atom key))
6209 (find 1 list :key (the (member car) key)))
6210 (('((a b) (1 a)) 'car) '(1 a))
6211 (('((a b) (1 a)) 'cdr) (condition 'type-error))))
6213 (with-test (:name (:two-arg-rewriting find-if))
6214 (checked-compile-and-assert ()
6215 `(lambda (x)
6216 (declare (type vector x))
6217 (find-if #'oddp x :key '-))
6218 ((#(1)) 1)))
6220 (with-test (:name :transforms-check-policy-first)
6221 (checked-compile-and-assert (:optimize '(:safety t :debug t :speed 3 :space 3)
6222 :allow-notes nil)
6223 `(lambda (x)
6224 (find x "a b c" :test #'char-equal))
6225 ((#\B) #\b)))
6228 (with-test (:name (:valid-callable-argument :toplevel-xep))
6229 (assert (nth-value 2 (checked-compile `(lambda (l) (find-if (lambda ()) l))
6230 :allow-warnings t))))
6232 (with-test (:name (:valid-callable-argument :handler-bind))
6233 (assert (nth-value 2 (checked-compile
6234 `(lambda (l) (handler-bind ((error (lambda ()))) (funcall l)))
6235 :allow-warnings t))))
6237 (with-test (:name (ignorable macrolet))
6238 (checked-compile-and-assert ()
6239 `(lambda ()
6240 (macrolet ((f () 10))
6241 (declare (ignorable #'f))
6242 (f)))
6243 (() 10))
6244 (assert
6245 (eql (assert-no-signal
6246 (eval `(macrolet ((f () 10))
6247 (declare (ignorable #'f))
6248 (f))))
6249 10)))
6251 (with-test (:name (:cast values &rest))
6252 (checked-compile-and-assert ()
6253 `(lambda ()
6254 (values (the (values &rest integer) (eval '(values)))))
6255 (() nil)))
6258 (with-test (:name (:cast values &optional))
6259 (checked-compile-and-assert ()
6260 `(lambda ()
6261 (let ((x (the (values &optional integer) (eval '(values)))))
6262 (when x
6263 (setf x 10))))
6264 (() nil)))
6266 #+sb-unicode
6267 (with-test (:name (setf schar :type-mismatch))
6268 (let ((fun (checked-compile
6269 `(lambda (a) (setf (schar a 0) #\HIRAGANA_LETTER_SMALL_TU)))))
6270 (let ((string (string #\a))
6271 (base-string (coerce "a" 'simple-base-string)))
6272 (assert (eq (funcall fun string) #\HIRAGANA_LETTER_SMALL_TU))
6273 (assert (equal string (string #\HIRAGANA_LETTER_SMALL_TU)))
6274 (assert-error (funcall fun base-string) type-error)
6275 (assert (equal base-string "a")))))
6277 (with-test (:name :can-escape-functionals-escape)
6278 (checked-compile
6279 `(lambda ()
6280 (declare (optimize (speed 3)))
6281 (lambda () (unwind-protect :x :z)))
6282 :allow-notes nil)
6283 (checked-compile
6284 `(lambda ()
6285 (declare (optimize (speed 3)))
6286 (lambda () (catch :x)))
6287 :allow-notes nil))
6289 (with-test (:name (:combination-implementation-style :constants))
6290 (checked-compile-and-assert ()
6291 `(lambda (p1 p2)
6292 (logbitp (the (eql 1) p1) (the fixnum p2)))
6293 ((1 2) t)))
6295 (with-test (:name :reducing-constants
6296 ;; x86 delays FPE signalling
6297 :fails-on :x86)
6298 (checked-compile-and-assert ()
6299 `(lambda (x) (* 4.457268f31 4 x -46253801283659))
6300 ((5.0f-9) -4.123312f37))
6301 (checked-compile-and-assert ()
6302 `(lambda (x) (* #C(4.457268f31 0.0) 4 x -46253801283659))
6303 ((5.0f-9) #C(-4.123312f37 -0.0))))
6305 (with-test (:name :reducing-constants.2
6306 ;; x86 delays FPE signalling
6307 :fails-on :x86)
6308 (checked-compile-and-assert (:allow-style-warnings t)
6309 `(lambda () (* 1.0 2 (expt 2 127)))
6310 (() (condition 'floating-point-overflow))))
6312 (with-test (:name (logbitp :past fixnum))
6313 (checked-compile-and-assert ()
6314 `(lambda (x) (logbitp sb-vm:n-fixnum-bits (the fixnum x)))
6315 ((1) nil)
6316 ((-1) t)))
6318 (with-test (:name (dpb :implementation-style 1))
6319 (checked-compile-and-assert ()
6320 `(lambda ()
6321 (let ((res 126))
6322 (declare (type sb-vm:signed-word res))
6323 (setf res (dpb res (byte 1 2) res))
6324 res))
6325 (() 122)))
6327 (with-test (:name (dpb :implementation-style 2))
6328 (checked-compile-and-assert ()
6329 `(lambda (x i)
6330 (declare (fixnum x i))
6331 (dpb x (byte 0 0) i))
6332 (( 0 1) 1)
6333 ((-1 1) 1)))
6335 (with-test (:name (fixnum :mod-p :immediate))
6336 (checked-compile-and-assert ()
6337 `(lambda (x)
6338 (declare (type fixnum x))
6339 (typep x '(integer 0 2049)))
6340 ((2050) nil)
6341 ((-1) nil)
6342 ((1) t)
6343 ((0) t)))
6345 (with-test (:name (make-array :initial-contents :element-type :mismatch))
6346 (checked-compile-and-assert ()
6347 `(lambda (x)
6348 (make-array '(1 2) :element-type 'list :initial-contents x))
6349 (('(((1 2) (3 4)))) #2A(((1 2) (3 4))) :test #'equalp)))
6351 (with-test (:name :unknown-values-receiver-register-clobber)
6352 (checked-compile-and-assert ()
6353 `(lambda ()
6354 (let ((x (list 1)))
6355 (declare (sb-int:truly-dynamic-extent x))
6356 (progv '(*) x
6357 (catch 'ct (the integer (eval (dotimes (i 1 42) 42)))))))
6358 (() 42)))
6361 (with-test (:name :single-float-bits-to-signed-stack)
6362 (checked-compile-and-assert ()
6363 `(lambda (p1)
6364 (declare (type single-float p1))
6365 (scale-float p1 27))
6366 ((1.0) 1.3421773e8)))
6368 (with-test (:name (compile :call :dotted-list))
6369 (flet ((test (form)
6370 (multiple-value-bind (fun failure-p warnings style-warnings notes
6371 compiler-errors)
6372 (checked-compile `(lambda () ,form)
6373 :allow-failure t :allow-warnings t)
6374 (declare (ignore fun warnings style-warnings notes))
6375 (assert failure-p)
6376 (assert (= 1 (length compiler-errors)))
6377 (assert (search "is not a proper list."
6378 (princ-to-string (first compiler-errors)))))))
6379 (test '(cons 1 . 2))
6380 (test '((lambda (x) x) . 1))
6381 (test '(let () . 1))))
6383 (with-test (:name (ldb :rlwinm))
6384 (checked-compile-and-assert ()
6385 `(lambda (x)
6386 (declare (fixnum x))
6387 (ldb (byte 13 19) x))
6388 ((-3560597) 8185)))
6390 (with-test (:name (logand :transform))
6391 (checked-compile-and-assert ()
6392 `(lambda (b)
6393 (catch 'ct1
6394 (flet ((%f (&key (y (throw 'ct1 1)))
6395 (return-from %f y)))
6396 (logand (%f) b))))
6397 ((1) 1)))
6399 (with-test (:name (:left ash :cut-amount))
6400 (checked-compile-and-assert ()
6401 `(lambda (b z)
6402 (declare (type fixnum b)
6403 (type (and fixnum unsigned-byte) z))
6404 (ldb (byte 64 0) (ash b z)))
6405 ((-1 70) 0)))
6407 (with-test (:name :stp-load-fp-tn)
6408 (checked-compile-and-assert ()
6409 `(sb-int:named-lambda ,(gensym) (a)
6410 (max
6411 (handler-case
6412 (locally (declare (notinline values))
6413 (values a a a a a a a a a a a)))
6415 ((1) 1)))
6417 #+sb-unicode
6418 (with-test (:name :immediate-char-=)
6419 (checked-compile-and-assert ()
6420 `(lambda (x)
6421 (declare (type (member #\U9925 #\UBC19E) x))
6422 (the (member #\UBC19E) x))
6423 ((#\UBC19E) #\UBC19E)))
6425 (with-test (:name (compile * :constant-behind-cast :lp-1717971]))
6426 (checked-compile-and-assert (:optimize :quick/incomplete)
6427 `(lambda (x)
6428 (declare (type integer x))
6429 (declare (optimize (space 3) (compilation-speed 0)))
6430 (catch 'ct5
6431 (* (flet ((%f (&key (x (throw 'ct5 123)))
6432 (the integer x)))
6433 (%f))
6434 x)))
6435 ((45) 123)))
6437 (with-test (:name (if :refs-to-the-same-var-but-different-types))
6438 (checked-compile-and-assert ()
6439 `(lambda (a b)
6440 (declare (type fixnum b a))
6441 (setf a -1)
6442 (plusp (if (<= a b)
6444 (if nil
6446 b))))
6447 ((1 2) t))
6448 (checked-compile-and-assert ()
6449 `(lambda (a b)
6450 (declare (type integer b a))
6451 (setf a -1)
6452 (plusp (if (<= a b)
6454 (+ b 0))))
6455 ((1 2) t)))
6457 (with-test (:name :unequal-n-values-type-intersection)
6458 (checked-compile-and-assert ()
6459 `(lambda ()
6460 (let ((b 0))
6461 (unwind-protect
6462 (if (and
6463 (random (setf b 2))
6464 (eql b 0))
6465 (case (dpb b (byte 0 0) -25)
6466 ((3) (values 1 2 3)))
6467 (values 0 0)))))
6468 (() (values 0 0))))
6470 #+sb-unicode
6471 (with-test (:name :base-char-weakinging)
6472 (checked-compile-and-assert (:optimize :safe)
6473 `(lambda (x) (the base-char x))
6474 (((code-char 252)) (condition 'type-error))))