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