Unbreak non-x86 builds
[sbcl.git] / tests / compiler.pure.lisp
blob1fb8acaedf2a9da9e605061324a63800779a53d3
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 :allow-style-warnings t))))
517 (assert style-warnings))))
519 ;; Uh, this test is semi-bogus - it's trying to test that you can't
520 ;; repeat, but it's now actually testing that &WHOLE has to appear
521 ;; first, per the formal spec.
522 (with-test (:name (macrolet :lambda-list &whole :must-be-first))
523 (assert-error (checked-compile
524 `(lambda ()
525 (macrolet ((foo (&environment x &whole x) nil)
526 (bar (&environment env)
527 `',(macro-function 'foo env)))
528 (bar))))))
530 (assert (typep (eval `(the arithmetic-error
531 ',(make-condition 'arithmetic-error)))
532 'arithmetic-error))
534 (with-test (:name (compile make-array :dimensions nil))
535 (checked-compile `(lambda ()
536 (make-array nil :initial-element 11))))
538 (assert-error (funcall (eval #'open) "assertoid.lisp"
539 :external-format '#:nonsense))
540 (assert-error (funcall (eval #'load) "assertoid.lisp"
541 :external-format '#:nonsense))
543 (assert (= (the (values integer symbol) (values 1 'foo 13)) 1))
545 (let ((f (compile nil
546 '(lambda (v)
547 (declare (optimize (safety 3)))
548 (list (the fixnum (the (real 0) (eval v))))))))
549 (assert-error (funcall f 0.1) type-error)
550 (assert-error (funcall f -1) type-error))
552 ;;; the implicit block does not enclose lambda list
553 (with-test (:name (compile :implicit block :does-not-enclose :lambda-list))
554 (let ((forms '((defmacro #1=#:foo (&optional (x (return-from #1#)))
555 (declare (ignore x)))
556 #+nil(macrolet ((#2=#:foo (&optional (x (return-from #2#))))))
557 (define-compiler-macro #3=#:foo (&optional (x (return-from #3#)))
558 (declare (ignore x)))
559 (deftype #4=#:foo (&optional (x (return-from #4#)))
560 (declare (ignore x)))
561 (define-setf-expander #5=#:foo (&optional (x (return-from #5#)))
562 (declare (ignore x)))
563 (defsetf #6=#:foo (&optional (x (return-from #6#))) ()
564 (declare (ignore x))))))
565 (dolist (form forms)
566 (assert (nth-value
567 1 (checked-compile `(lambda () ,form) :allow-failure t))))))
569 (with-test (:name (compile make-array svref :derive-type))
570 (multiple-value-bind (fun failurep warnings)
571 (checked-compile `(lambda ()
572 (svref (make-array '(8 9) :adjustable t) 1))
573 :allow-warnings t)
574 (declare (ignore fun))
575 (assert failurep)
576 (assert (= 1 (length warnings)))))
578 ;;; CHAR= did not check types of its arguments (reported by Adam Warner)
579 (macrolet ((define-char=-test (function form)
580 `(with-test (:name (compile ,function :argument-type-check))
581 (assert-error (funcall (checked-compile ,form) #\a #\b nil)
582 type-error))))
583 (define-char=-test char= `(lambda (x y z) (char= x y z)))
584 (define-char=-test char/= `(lambda (x y z)
585 (declare (optimize (speed 3) (safety 3)))
586 (char/= x y z))))
588 ;;; Compiler lost return type of MAPCAR and friends
589 (with-test (:name (compile mapcar mapc maplist mapl
590 :return-type :type-derivation))
591 (dolist (fun '(mapcar mapc maplist mapl))
592 (assert (= 1 (length (nth-value
593 2 (checked-compile
594 `(lambda (x)
595 (1+ (,fun #'print x)))
596 :allow-warnings t))))))
598 (assert (= 1 (length (nth-value
599 2 (checked-compile
600 `(lambda ()
601 (declare (notinline mapcar))
602 (1+ (mapcar #'print '(1 2 3))))
603 :allow-warnings t))))))
605 ;;; bug found by Paul Dietz: (SETF AREF) for bit vectors with constant
606 ;;; index was effectless
607 (with-test (:name (compile setf aref bit-vector))
608 (let ((f (checked-compile `(lambda (a v)
609 (declare (type simple-bit-vector a) (type bit v))
610 (declare (optimize (speed 3) (safety 0)))
611 (setf (aref a 0) v)
612 a))))
613 (let ((y (make-array 2 :element-type 'bit :initial-element 0)))
614 (assert (equal y #*00))
615 (funcall f y 1)
616 (assert (equal y #*10)))))
618 ;;; use of declared array types
619 (with-test (:name (compile declare array type :no sb-ext:compiler-note))
620 (dolist (form `((lambda (x)
621 (declare (type (simple-array (simple-string 3) (5)) x)
622 (optimize speed))
623 (aref (aref x 0) 0))
624 (lambda (x)
625 (declare (type (simple-array (simple-array bit (10)) (10)) x)
626 (optimize speed))
627 (1+ (aref (aref x 0) 0)))))
628 (checked-compile form :allow-notes nil)))
630 ;;; compiler failure
631 (with-test (:name (compile typep not member))
632 (let ((f (checked-compile `(lambda (x) (typep x '(not (member 0d0)))))))
633 (assert (funcall f 1d0))))
635 (with-test (:name (compile double-float atan))
636 (checked-compile `(lambda (x)
637 (declare (double-float x))
638 (let ((y (* x pi)))
639 (atan y y)))))
641 ;;; bogus optimization of BIT-NOT
642 (multiple-value-bind (result x)
643 (eval '(let ((x (eval #*1001)))
644 (declare (optimize (speed 2) (space 3))
645 (type (bit-vector) x))
646 (values (bit-not x nil) x)))
647 (assert (equal x #*1001))
648 (assert (equal result #*0110)))
650 ;;; the VECTOR type in CONCATENATE/MERGE/MAKE-SEQUENCE means (VECTOR T).
651 (with-test (:name (compile vector make-sequence sb-ext:compiler-note))
652 (let ((fun (checked-compile
653 `(lambda ()
654 (let ((x (make-sequence 'vector 10 :initial-element 'a)))
655 (setf (aref x 4) 'b)
657 :allow-notes t)))
658 (assert (equalp (funcall fun) #(a a a a b a a a a a)))))
660 ;;; this is not a check for a bug, but rather a test of compiler
661 ;;; quality
662 (with-test (:name (compile integer :type-derivation))
663 (dolist (type '((integer 0 *) ; upper bound
664 (real (-1) *)
665 float ; class
666 (real * (-10)) ; lower bound
668 (assert (= 1 (length (nth-value
669 2 (checked-compile
670 `(lambda (n)
671 (declare (optimize (speed 3) (compilation-speed 0)))
672 (loop for i from 1 to (the (integer -17 10) n) by 2
673 collect (when (> (random 10) 5)
674 (the ,type (- i 11)))))
675 :allow-warnings t)))))))
677 ;;; bug 278b
679 ;;; We suppose that INTEGER arithmetic cannot be efficient, and the
680 ;;; compiler has an optimized VOP for +; so this code should cause an
681 ;;; efficiency note.
682 (with-test (:name (compile integer + sb-ext:compiler-note :bug-278b))
683 (assert (= 1 (length (nth-value
684 4 (checked-compile
685 `(lambda (i)
686 (declare (optimize speed))
687 (declare (type integer i))
688 (+ i 2))))))))
690 ;;; bug 277: IGNORE/IGNORABLE declarations should be acceptable for
691 ;;; symbol macros
692 (with-test (:name (compile symbol-macrolet ignore ignorable :bug-277))
693 (checked-compile `(lambda (u v)
694 (symbol-macrolet ((x u)
695 (y v))
696 (declare (ignore x)
697 (ignorable y))
698 (list u v)))))
700 ;;; bug reported by Paul Dietz: wrong optimizer for (EXPT ... 0)
701 (loop for (x type) in
702 '((14 integer)
703 (14 rational)
704 (-14/3 (rational -8 11))
705 (3s0 short-float)
706 (4f0 single-float)
707 (5d0 double-float)
708 (6l0 long-float)
709 (14 real)
710 (13/2 real)
711 (2s0 real)
712 (2d0 real)
713 (#c(-3 4) (complex fixnum))
714 (#c(-3 4) (complex rational))
715 (#c(-3/7 4) (complex rational))
716 (#c(2s0 3s0) (complex short-float))
717 (#c(2f0 3f0) (complex single-float))
718 (#c(2d0 3d0) (complex double-float))
719 (#c(2l0 3l0) (complex long-float))
720 (#c(2d0 3s0) (complex float))
721 (#c(2 3f0) (complex real))
722 (#c(2 3d0) (complex real))
723 (#c(-3/7 4) (complex real))
724 (#c(-3/7 4) complex)
725 (#c(2 3l0) complex))
726 do (dolist (zero '(0 0s0 0f0 0d0 0l0))
727 (dolist (real-zero (list zero (- zero)))
728 (let* ((src `(lambda (x) (expt (the ,type x) ,real-zero)))
729 (fun (compile nil src))
730 (result (1+ (funcall (eval #'*) x real-zero))))
731 (assert (eql result (funcall fun x)))))))
733 ;;; (SIGNED-BYTE 1) [ returned from the logxor derive-type optimizer ]
734 ;;; wasn't recognized as a good type specifier.
735 (let ((fun (lambda (x y)
736 (declare (type (integer -1 0) x y) (optimize speed))
737 (logxor x y))))
738 (assert (= (funcall fun 0 0) 0))
739 (assert (= (funcall fun 0 -1) -1))
740 (assert (= (funcall fun -1 -1) 0)))
742 ;;; from PFD's torture test, triggering a bug in our effective address
743 ;;; treatment.
744 (with-test (:name (compile declare type logandc1 logandc2))
745 (checked-compile `(lambda (a b)
746 (declare (type (integer 8 22337) b))
747 (logandc2
748 (logandc2
749 (* (logandc1 (max -29303 b) 4) b)
750 (abs (logorc1 (+ (logandc1 -11 b) 2607688420) -31153924)))
751 (logeqv (max a 0) b)))))
753 ;;; Alpha floating point modes weren't being reset after an exception,
754 ;;; leading to an exception on the second compile, below.
755 (with-test (:name (compile :floating-point-mode))
756 (let ((form `(lambda (x y) (declare (type (double-float 0.0d0) x y)) (/ x y))))
757 (checked-compile form)
758 (handler-case (/ 1.0 0.0)
759 ;; provoke an exception
760 (arithmetic-error ()))
761 (checked-compile form)))
763 ;;; bug reported by Paul Dietz: component last block does not have
764 ;;; start ctran
765 (with-test (:name (compile block return-from))
766 (checked-compile `(lambda ()
767 (declare (notinline + logand)
768 (optimize (speed 0)))
769 (logand
770 (block b5
771 (flet ((%f1 ()
772 (return-from b5 -220)))
773 (let ((v7 (%f1)))
774 (+ 359749 35728422))))
775 -24076))))
777 (with-test (:name :ansi-misc.293a)
778 (assert (= (funcall
779 (compile
781 '(lambda (a b c)
782 (declare (optimize (speed 2) (space 3) (safety 1)
783 (debug 2) (compilation-speed 2)))
784 (block b6
785 (multiple-value-prog1
786 0 b 0
787 (catch 'ct7
788 (return-from b6
789 (catch 'ct2
790 (complex (cl::handler-bind nil -254932942) 0))))))))
791 1 2 3)
792 -254932942)))
794 (with-test (:name :ansi-misc.293d)
795 (assert (= (funcall
796 (checked-compile
797 `(lambda ()
798 (declare (optimize (debug 3) (safety 0) (space 2)
799 (compilation-speed 2) (speed 2)))
800 (block b4
801 (multiple-value-prog1
803 (catch 'ct8
804 (return-from b4 (catch 'ct2 (progn (tagbody) 0)))))))))
805 0)))
807 (with-test (:name :ansi-misc.618)
808 (assert (= (funcall
809 (checked-compile
810 `(lambda (c)
811 (declare (optimize (space 0) (compilation-speed 2) (debug 0)
812 (speed 3) (safety 0)))
813 (block b1
814 (ignore-errors
815 (multiple-value-prog1 0
816 (apply (constantly 0)
818 (catch 'ct2 (return-from b1 0))
819 nil))))))
820 -4951)
821 0)))
823 ;;; bug 294 reported by Paul Dietz: miscompilation of REM and MOD
824 (with-test (:name (compile rem :bug-294))
825 (assert (= (funcall (checked-compile
826 `(lambda (b)
827 (declare (optimize (speed 3))
828 (type (integer 2 152044363) b))
829 (rem b (min -16 0))))
830 108251912)
831 8)))
833 (with-test (:name (compile mod :bug-294))
834 (assert (= (funcall (checked-compile
835 `(lambda (c)
836 (declare (optimize (speed 3))
837 (type (integer 23062188 149459656) c))
838 (mod c (min -2 0))))
839 95019853)
840 -1)))
842 ;;; bug reported by Paul Dietz: block splitting inside FLUSH-DEAD-CODE
843 (with-test (:name (compile logeqv rem :dead-code :block-splitting))
844 (checked-compile `(lambda (a b c)
845 (block b6
846 (logeqv (rem c -6758)
847 (rem b (max 44 (return-from b6 a))))))))
849 (with-test (:name (compile block flet :dead-code :block-splitting))
850 (checked-compile `(lambda ()
851 (block nil
852 (flet ((foo (x y) (if (> x y) (print x) (print y))))
853 (foo 1 2)
854 (bar)
855 (foo (return 14) 2))))
856 :allow-style-warnings t))
858 ;;; bug in Alpha backend: not enough sanity checking of arguments to
859 ;;; instructions
860 (assert (= (funcall (compile nil
861 '(lambda (x)
862 (declare (fixnum x))
863 (ash x -257)))
864 1024)
867 ;;; bug found by WHN and pfdietz: compiler failure while referencing
868 ;;; an entry point inside a deleted lambda
869 (with-test (:name (compile :reference-entry-point-in-deleted lambda))
870 (checked-compile
871 `(lambda ()
872 (let (r3533)
873 (flet ((bbfn ()
874 (setf r3533
875 (progn
876 (flet ((truly (fn bbd)
877 (let (r3534)
878 (let ((p3537 nil))
879 (unwind-protect
880 (multiple-value-prog1
881 (progn
882 (setf r3534
883 (progn
884 (bubf bbd t)
885 (flet ((c-3536 ()
886 (funcall fn)))
887 (cdec #'c-3536
888 (vector bbd))))))
889 (setf p3537 t))
890 (unless p3537
891 (error "j"))))
892 r3534))
893 (c (pd) (pdc pd)))
894 (let ((a (smock a))
895 (b (smock b))
896 (b (smock c)))))))))
897 (wum #'bbfn "hc3" (list)))
898 r3533))
899 :allow-failure t :allow-style-warnings t))
901 (with-test (:name (compile flet unwind-protect :dead-code))
902 (checked-compile `(lambda () (flet ((%f () (unwind-protect nil))) nil))))
904 ;;; the strength reduction of constant multiplication used (before
905 ;;; sbcl-0.8.4.x) to lie to the compiler. This meant that, under
906 ;;; certain circumstances, the compiler would derive that a perfectly
907 ;;; reasonable multiplication never returned, causing chaos. Fixed by
908 ;;; explicitly doing modular arithmetic, and relying on the backends
909 ;;; being smart.
910 (assert (= (funcall
911 (compile nil
912 '(lambda (x)
913 (declare (type (integer 178956970 178956970) x)
914 (optimize speed))
915 (* x 24)))
916 178956970)
917 4294967280))
919 ;;; bug in modular arithmetic and type specifiers
920 (assert (= (funcall (compile nil '(lambda (x) (logand x x 0)))
924 ;;; MISC.99 from Paul Dietz' random tester: FAST-ASH-MOD32-C VOP
925 ;;; produced wrong result for shift >=32 on X86
926 (assert (= 0 (funcall
927 (compile nil
928 '(lambda (a)
929 (declare (type (integer 4303063 101130078) a))
930 (mask-field (byte 18 2) (ash a 77))))
931 57132532)))
932 ;;; rewrite the test case to get the unsigned-byte 32/64
933 ;;; implementation even after implementing some modular arithmetic
934 ;;; with signed-byte 30:
935 (assert (= 0 (funcall
936 (compile nil
937 '(lambda (a)
938 (declare (type (integer 4303063 101130078) a))
939 (mask-field (byte 30 2) (ash a 77))))
940 57132532)))
941 (assert (= 0 (funcall
942 (compile nil
943 '(lambda (a)
944 (declare (type (integer 4303063 101130078) a))
945 (mask-field (byte 64 2) (ash a 77))))
946 57132532)))
947 ;;; and a similar test case for the signed masking extension (not the
948 ;;; final interface, so change the call when necessary):
949 (assert (= 0 (funcall
950 (compile nil
951 '(lambda (a)
952 (declare (type (integer 4303063 101130078) a))
953 (sb-c::mask-signed-field 30 (ash a 77))))
954 57132532)))
955 (assert (= 0 (funcall
956 (compile nil
957 '(lambda (a)
958 (declare (type (integer 4303063 101130078) a))
959 (sb-c::mask-signed-field 61 (ash a 77))))
960 57132532)))
962 ;;; MISC.101 and MISC.103: FLUSH-DEST did not mark the USE's block for
963 ;;; type check regeneration
964 (assert (eql (funcall
965 (compile nil '(lambda (a c)
966 (declare (type (integer 185501219873 303014665162) a))
967 (declare (type (integer -160758 255724) c))
968 (declare (optimize (speed 3)))
969 (let ((v8
970 (- -554046873252388011622614991634432
971 (ignore-errors c)
972 (unwind-protect 2791485))))
973 (max (ignore-errors a)
974 (let ((v6 (- v8 (restart-case 980))))
975 (min v8 v6))))))
976 259448422916 173715)
977 259448422916))
978 (assert (eql (funcall
979 (compile nil '(lambda (a b)
980 (min -80
981 (abs
982 (ignore-errors
984 (logeqv b
985 (block b6
986 (return-from b6
987 (load-time-value -6876935))))
988 (if (logbitp 1 a) b (setq a -1522022182249))))))))
989 -1802767029877 -12374959963)
990 -80))
992 ;;; various MISC.*, related to NODEs/LVARs with derived type NIL
993 (assert (eql (funcall (compile nil '(lambda (c)
994 (declare (type (integer -3924 1001809828) c))
995 (declare (optimize (speed 3)))
996 (min 47 (if (ldb-test (byte 2 14) c)
997 -570344431
998 (ignore-errors -732893970)))))
999 705347625)
1000 -570344431))
1001 (assert (eql (funcall
1002 (compile nil '(lambda (b)
1003 (declare (type (integer -1598566306 2941) b))
1004 (declare (optimize (speed 3)))
1005 (max -148949 (ignore-errors b))))
1008 (assert (eql (funcall
1009 (compile nil '(lambda (b c)
1010 (declare (type (integer -4 -3) c))
1011 (block b7
1012 (flet ((%f1 (f1-1 f1-2 f1-3)
1013 (if (logbitp 0 (return-from b7
1014 (- -815145138 f1-2)))
1015 (return-from b7 -2611670)
1016 99345)))
1017 (let ((v2 (%f1 -2464 (%f1 -1146 c c) -2)))
1018 b)))))
1019 2950453607 -4)
1020 -815145134))
1021 (assert (eql (funcall
1022 (compile nil
1023 '(lambda (b c)
1024 (declare (type (integer -29742055786 23602182204) b))
1025 (declare (type (integer -7409 -2075) c))
1026 (declare (optimize (speed 3)))
1027 (floor
1028 (labels ((%f2 ()
1029 (block b6
1030 (ignore-errors (return-from b6
1031 (if (= c 8) b 82674))))))
1032 (%f2)))))
1033 22992834060 -5833)
1034 82674))
1035 (assert (equal (multiple-value-list
1036 (funcall
1037 (compile nil '(lambda (a)
1038 (declare (type (integer -944 -472) a))
1039 (declare (optimize (speed 3)))
1040 (round
1041 (block b3
1042 (return-from b3
1043 (if (= 55957 a) -117 (ignore-errors
1044 (return-from b3 a))))))))
1045 -589))
1046 '(-589 0)))
1048 ;;; MISC.158
1049 (assert (zerop (funcall
1050 (compile nil
1051 '(lambda (a b c)
1052 (declare (type (integer 79828 2625480458) a))
1053 (declare (type (integer -4363283 8171697) b))
1054 (declare (type (integer -301 0) c))
1055 (if (equal 6392154 (logxor a b))
1056 1706
1057 (let ((v5 (abs c)))
1058 (logand v5
1059 (logior (logandc2 c v5)
1060 (common-lisp:handler-case
1061 (ash a (min 36 22477)))))))))
1062 100000 0 0)))
1064 ;;; MISC.152, 153: deleted code and iteration var type inference
1065 (assert (eql (funcall
1066 (compile nil
1067 '(lambda (a)
1068 (block b5
1069 (let ((v1 (let ((v8 (unwind-protect 9365)))
1070 8862008)))
1072 (return-from b5
1073 (labels ((%f11 (f11-1) f11-1))
1074 (%f11 87246015)))
1075 (return-from b5
1076 (setq v1
1077 (labels ((%f6 (f6-1 f6-2 f6-3) v1))
1078 (dpb (unwind-protect a)
1079 (byte 18 13)
1080 (labels ((%f4 () 27322826))
1081 (%f6 -2 -108626545 (%f4))))))))))))
1083 87246015))
1085 (assert (eql (funcall
1086 (compile nil
1087 '(lambda (a)
1088 (if (logbitp 3
1089 (case -2
1090 ((-96879 -1035 -57680 -106404 -94516 -125088)
1091 (unwind-protect 90309179))
1092 ((-20811 -86901 -9368 -98520 -71594)
1093 (let ((v9 (unwind-protect 136707)))
1094 (block b3
1095 (setq v9
1096 (let ((v4 (return-from b3 v9)))
1097 (- (ignore-errors (return-from b3 v4))))))))
1098 (t -50)))
1099 -20343
1100 a)))
1102 -20343))
1104 ;;; MISC.165
1105 (assert (eql (funcall
1106 (compile
1108 '(lambda (a b c)
1109 (block b3
1110 (flet ((%f15
1111 (f15-1 f15-2 f15-3
1112 &optional
1113 (f15-4
1114 (flet ((%f17
1115 (f17-1 f17-2 f17-3
1116 &optional (f17-4 185155520) (f17-5 c)
1117 (f17-6 37))
1119 (%f17 -1046 a 1115306 (%f17 b -146330 422) -337817)))
1120 (f15-5 a) (f15-6 -40))
1121 (return-from b3 -16)))
1122 (multiple-value-call #'%f15 (values -519354 a 121 c -1905))))))
1123 0 0 -5)
1124 -16))
1126 ;;; MISC.172
1127 (assert (eql (funcall
1128 (compile
1130 '(lambda (a b c)
1131 (declare (notinline list apply))
1132 (declare (optimize (safety 3)))
1133 (declare (optimize (speed 0)))
1134 (declare (optimize (debug 0)))
1135 (labels ((%f12 (f12-1 f12-2)
1136 (labels ((%f2 (f2-1 f2-2)
1137 (flet ((%f6 ()
1138 (flet ((%f18
1139 (f18-1
1140 &optional (f18-2 a)
1141 (f18-3 -207465075)
1142 (f18-4 a))
1143 (return-from %f12 b)))
1144 (%f18 -3489553
1146 (%f18 (%f18 150 -64 f12-1)
1147 (%f18 (%f18 -8531)
1148 11410)
1150 56362666))))
1151 (labels ((%f7
1152 (f7-1 f7-2
1153 &optional (f7-3 (%f6)))
1154 7767415))
1155 f12-1))))
1156 (%f2 b -36582571))))
1157 (apply #'%f12 (list 774 -4413)))))
1158 0 1 2)
1159 774))
1161 ;;; MISC.173
1162 (assert (eql (funcall
1163 (compile
1165 '(lambda (a b c)
1166 (declare (notinline values))
1167 (declare (optimize (safety 3)))
1168 (declare (optimize (speed 0)))
1169 (declare (optimize (debug 0)))
1170 (flet ((%f11
1171 (f11-1 f11-2
1172 &optional (f11-3 c) (f11-4 7947114)
1173 (f11-5
1174 (flet ((%f3 (f3-1 &optional (f3-2 b) (f3-3 5529))
1175 8134))
1176 (multiple-value-call #'%f3
1177 (values (%f3 -30637724 b) c)))))
1178 (setq c 555910)))
1179 (if (and nil (%f11 a a))
1180 (if (%f11 a 421778 4030 1)
1181 (labels ((%f7
1182 (f7-1 f7-2
1183 &optional
1184 (f7-3
1185 (%f11 -79192293
1186 (%f11 c a c -4 214720)
1189 (%f11 b 985)))
1190 (f7-4 a))
1192 (%f11 c b -25644))
1194 -32326608))))
1195 1 2 3)
1196 -32326608))
1198 ;;; MISC.177, 182: IR2 copy propagation missed a hidden write to a
1199 ;;; local lambda argument
1200 (assert
1201 (equal
1202 (funcall
1203 (compile nil
1204 '(lambda (a b c)
1205 (declare (type (integer 804561 7640697) a))
1206 (declare (type (integer -1 10441401) b))
1207 (declare (type (integer -864634669 55189745) c))
1208 (declare (ignorable a b c))
1209 (declare (optimize (speed 3)))
1210 (declare (optimize (safety 1)))
1211 (declare (optimize (debug 1)))
1212 (flet ((%f11
1213 (f11-1 f11-2)
1214 (labels ((%f4 () (round 200048 (max 99 c))))
1215 (logand
1216 f11-1
1217 (labels ((%f3 (f3-1) -162967612))
1218 (%f3 (let* ((v8 (%f4)))
1219 (setq f11-1 (%f4)))))))))
1220 (%f11 -120429363 (%f11 62362 b)))))
1221 6714367 9645616 -637681868)
1222 -264223548))
1224 ;;; Bug reported by Paul F. Dietz caused by derive type loss in VALUE
1225 ;;; transform
1226 (assert (equal (multiple-value-list
1227 (funcall
1228 (compile nil '(lambda ()
1229 (declare (optimize (speed 1) (space 0) (safety 3) (debug 3) (compilation-speed 1)))
1230 (ceiling
1231 (ceiling
1232 (flet ((%f16 () 0)) (%f16))))))))
1233 '(0 0)))
1235 ;;; MISC.184
1236 (assert (zerop
1237 (funcall
1238 (compile
1240 '(lambda (a b c)
1241 (declare (type (integer 867934833 3293695878) a))
1242 (declare (type (integer -82111 1776797) b))
1243 (declare (type (integer -1432413516 54121964) c))
1244 (declare (optimize (speed 3)))
1245 (declare (optimize (safety 1)))
1246 (declare (optimize (debug 1)))
1247 (if nil
1248 (flet ((%f15 (f15-1 &optional (f15-2 c))
1249 (labels ((%f1 (f1-1 f1-2) 0))
1250 (%f1 a 0))))
1251 (flet ((%f4 ()
1252 (multiple-value-call #'%f15
1253 (values (%f15 c 0) (%f15 0)))))
1254 (if nil (%f4)
1255 (flet ((%f8 (f8-1 &optional (f8-2 (%f4)) (f8-3 0))
1256 f8-3))
1257 0))))
1258 0)))
1259 3040851270 1664281 -1340106197)))
1261 ;;; MISC.249
1262 (assert (zerop
1263 (funcall
1264 (compile
1266 '(lambda (a b)
1267 (declare (notinline <=))
1268 (declare (optimize (speed 2) (space 3) (safety 0)
1269 (debug 1) (compilation-speed 3)))
1270 (if (if (<= 0) nil nil)
1271 (labels ((%f9 (f9-1 f9-2 f9-3)
1272 (ignore-errors 0)))
1273 (dotimes (iv4 5 a) (%f9 0 0 b)))
1274 0)))
1275 1 2)))
1277 ;;; MISC.259-264 (aka "CSR screwed up implementing *-MOD32")
1278 (assert
1279 (= (funcall
1280 (compile
1282 '(lambda (a)
1283 (declare (type (integer 177547470 226026978) a))
1284 (declare (optimize (speed 3) (space 0) (safety 0) (debug 0)
1285 (compilation-speed 1)))
1286 (logand a (* a 438810))))
1287 215067723)
1288 13739018))
1291 ;;;; Bugs in stack analysis
1292 ;;; bug 299 (reported by PFD)
1293 (assert
1294 (equal (funcall
1295 (compile
1297 '(lambda ()
1298 (declare (optimize (debug 1)))
1299 (multiple-value-call #'list
1300 (if (eval t) (eval '(values :a :b :c)) nil)
1301 (catch 'foo (throw 'foo (values :x :y)))))))
1302 '(:a :b :c :x :y)))
1303 ;;; bug 298 (= MISC.183)
1304 (assert (zerop (funcall
1305 (compile
1307 '(lambda (a b c)
1308 (declare (type (integer -368154 377964) a))
1309 (declare (type (integer 5044 14959) b))
1310 (declare (type (integer -184859815 -8066427) c))
1311 (declare (ignorable a b c))
1312 (declare (optimize (speed 3)))
1313 (declare (optimize (safety 1)))
1314 (declare (optimize (debug 1)))
1315 (block b7
1316 (flet ((%f3 (f3-1 f3-2 f3-3) 0))
1317 (apply #'%f3 0 (catch 'foo (return-from b7 (%f3 0 b c))) c nil)))))
1318 0 6000 -9000000)))
1319 (assert (equal (eval '(let () (apply #'list 1 (list (catch 'a (throw 'a (block b 2)))))))
1320 '(1 2)))
1321 (let ((f (compile
1323 '(lambda (x)
1324 (block foo
1325 (multiple-value-call #'list
1327 (block bar
1328 (return-from foo
1329 (multiple-value-call #'list
1331 (block quux
1332 (return-from bar
1333 (catch 'baz
1334 (if x
1335 (return-from quux 1)
1336 (throw 'baz 2))))))))))))))
1337 (assert (equal (funcall f t) '(:b 1)))
1338 (assert (equal (funcall f nil) '(:a 2))))
1340 ;;; MISC.185
1341 (assert (equal
1342 (funcall
1343 (compile
1345 '(lambda (a b c)
1346 (declare (type (integer 5 155656586618) a))
1347 (declare (type (integer -15492 196529) b))
1348 (declare (type (integer 7 10) c))
1349 (declare (optimize (speed 3)))
1350 (declare (optimize (safety 1)))
1351 (declare (optimize (debug 1)))
1352 (flet ((%f3
1353 (f3-1 f3-2 f3-3
1354 &optional (f3-4 a) (f3-5 0)
1355 (f3-6
1356 (labels ((%f10 (f10-1 f10-2 f10-3)
1358 (apply #'%f10
1361 (- (if (equal a b) b (%f10 c a 0))
1362 (catch 'ct2 (throw 'ct2 c)))
1363 nil))))
1365 (%f3 (%f3 (%f3 b 0 0 0) a 0) a b b b c)))) 5 0 7)
1367 ;;; MISC.186
1368 (assert (eq
1369 (eval
1370 '(let* ((form '(labels ((%f3 (f3-1 f3-2) f3-1))
1371 (apply #'%f3 b (catch 'ct8 (throw 'ct8 (logeqv (%f3 c 0)))) nil)))
1372 (vars '(b c))
1373 (fn1 `(lambda ,vars
1374 (declare (type (integer -2 19) b)
1375 (type (integer -1520 218978) c)
1376 (optimize (speed 3) (safety 1) (debug 1)))
1377 ,form))
1378 (fn2 `(lambda ,vars
1379 (declare (notinline logeqv apply)
1380 (optimize (safety 3) (speed 0) (debug 0)))
1381 ,form))
1382 (cf1 (compile nil fn1))
1383 (cf2 (compile nil fn2))
1384 (result1 (multiple-value-list (funcall cf1 2 18886)))
1385 (result2 (multiple-value-list (funcall cf2 2 18886))))
1386 (if (equal result1 result2)
1387 :good
1388 (values result1 result2))))
1389 :good))
1391 ;;; MISC.290
1392 (assert (zerop
1393 (funcall
1394 (compile
1396 '(lambda ()
1397 (declare
1398 (optimize (speed 3) (space 3) (safety 1)
1399 (debug 2) (compilation-speed 0)))
1400 (apply (constantly 0) (catch 'ct2 0) 0 (catch 'ct2 0) nil))))))
1402 ;;; MISC.292
1403 (assert (zerop (funcall
1404 (compile
1406 '(lambda (a b)
1407 (declare (optimize (speed 2) (space 0) (safety 3) (debug 1)
1408 (compilation-speed 2)))
1409 (apply (constantly 0)
1412 (catch 'ct6
1413 (apply (constantly 0)
1416 (let* ((v1
1417 (let ((*s7* 0))
1418 b)))
1421 nil))
1423 nil)))
1424 1 2)))
1426 ;;; misc.295
1427 (assert (eql
1428 (funcall
1429 (compile
1431 '(lambda ()
1432 (declare (optimize (speed 1) (space 0) (safety 0) (debug 0)))
1433 (multiple-value-prog1
1434 (the integer (catch 'ct8 (catch 'ct7 15867134)))
1435 (catch 'ct1 (throw 'ct1 0))))))
1436 15867134))
1438 ;;; misc.361: replacing CAST with (m-v-call #'%compile-time-type-error)
1439 ;;; could transform known-values LVAR to UVL
1440 (assert (zerop (funcall
1441 (compile
1443 '(lambda (a b c)
1444 (declare (notinline boole values denominator list))
1445 (declare
1446 (optimize (speed 2)
1447 (space 0)
1448 (safety 1)
1449 (debug 0)
1450 (compilation-speed 2)))
1451 (catch 'ct6
1452 (progv
1453 '(*s8*)
1454 (list 0)
1455 (let ((v9 (ignore-errors (throw 'ct6 0))))
1456 (denominator
1457 (progv nil nil (values (boole boole-and 0 v9)))))))))
1458 1 2 3)))
1460 ;;; non-continuous dead UVL blocks
1461 (defun non-continuous-stack-test (x)
1462 (multiple-value-call #'list
1463 (eval '(values 11 12))
1464 (eval '(values 13 14))
1465 (block ext
1466 (return-from non-continuous-stack-test
1467 (multiple-value-call #'list
1468 (eval '(values :b1 :b2))
1469 (eval '(values :b3 :b4))
1470 (block int
1471 (return-from ext
1472 (multiple-value-call (eval #'values)
1473 (eval '(values 1 2))
1474 (eval '(values 3 4))
1475 (block ext
1476 (return-from int
1477 (multiple-value-call (eval #'values)
1478 (eval '(values :a1 :a2))
1479 (eval '(values :a3 :a4))
1480 (block int
1481 (return-from ext
1482 (multiple-value-call (eval #'values)
1483 (eval '(values 5 6))
1484 (eval '(values 7 8))
1485 (if x
1486 :ext
1487 (return-from int :int))))))))))))))))
1488 (assert (equal (non-continuous-stack-test t) '(11 12 13 14 1 2 3 4 5 6 7 8 :ext)))
1489 (assert (equal (non-continuous-stack-test nil) '(:b1 :b2 :b3 :b4 :a1 :a2 :a3 :a4 :int)))
1491 ;;; MISC.362: environment of UNWIND-PROTECTor is different from that
1492 ;;; if ENTRY.
1493 (assert (equal (multiple-value-list (funcall
1494 (compile
1496 '(lambda (b g h)
1497 (declare (optimize (speed 3) (space 3) (safety 2)
1498 (debug 2) (compilation-speed 3)))
1499 (catch 'ct5
1500 (unwind-protect
1501 (labels ((%f15 (f15-1 f15-2 f15-3)
1502 (rational (throw 'ct5 0))))
1503 (%f15 0
1504 (apply #'%f15
1507 (progn
1508 (progv '(*s2* *s5*) (list 0 (%f15 0 g 0)) b)
1510 nil)
1512 (common-lisp:handler-case 0)))))
1513 1 2 3))
1514 '(0)))
1517 ;;; MISC.275
1518 (assert
1519 (zerop
1520 (funcall
1521 (compile
1523 '(lambda (b)
1524 (declare (notinline funcall min coerce))
1525 (declare
1526 (optimize (speed 1)
1527 (space 2)
1528 (safety 2)
1529 (debug 1)
1530 (compilation-speed 1)))
1531 (flet ((%f12 (f12-1)
1532 (coerce
1533 (min
1534 (if f12-1 (multiple-value-prog1
1535 b (return-from %f12 0))
1537 'integer)))
1538 (funcall #'%f12 0))))
1539 -33)))
1541 ;;; Discussion of a CMUCL PCL bug on Sparc with Raymond Toy revealed a
1542 ;;; potential problem: optimizers and type derivers for MAX and MIN
1543 ;;; were not consistent in treating EQUALP, but not EQL, arguments.
1544 (dolist (f '(min max))
1545 (loop for complex-arg-args in '((1d0 2d0) (0d0 1d0))
1546 for complex-arg = `(if x ,@complex-arg-args)
1548 (loop for args in `((1 ,complex-arg)
1549 (,complex-arg 1))
1550 for form = `(,f ,@args)
1551 for f1 = (compile nil `(lambda (x) ,form))
1552 and f2 = (compile nil `(lambda (x) (declare (notinline min max))
1553 ,form))
1555 (dolist (x '(nil t))
1556 (assert (eql (funcall f1 x) (funcall f2 x)))))))
1559 (handler-case (compile nil '(lambda (x)
1560 (declare (optimize (speed 3) (safety 0)))
1561 (the double-float (sqrt (the double-float x)))))
1562 (sb-ext:compiler-note (c)
1563 ;; Ignore the note for the float -> pointer conversion of the
1564 ;; return value.
1565 (unless (string= (car (last (sb-c::simple-condition-format-arguments c)))
1566 "<return value>")
1567 (error "Compiler does not trust result type assertion."))))
1569 (let ((f (compile nil '(lambda (x)
1570 (declare (optimize speed (safety 0)))
1571 (block nil
1572 (the double-float
1573 (multiple-value-prog1
1574 (sqrt (the double-float x))
1575 (when (< x 0)
1576 (return :minus)))))))))
1577 (assert (eql (funcall f -1d0) :minus))
1578 (assert (eql (funcall f 4d0) 2d0)))
1580 ;;; bug 304: SBCL produced something similar to (/ (ASH x 4) 8)
1581 (handler-case
1582 (compile nil '(lambda (a i)
1583 (locally
1584 (declare (optimize (speed 3) (safety 0) (space 0) (debug 0)
1585 (inhibit-warnings 0)))
1586 (declare (type (alien (* (unsigned 8))) a)
1587 (type (unsigned-byte 32) i))
1588 (deref a i))))
1589 (compiler-note (c)
1590 (unless (search "%ASH/RIGHT" (first (simple-condition-format-arguments c)))
1591 (error "The code is not optimized."))))
1593 (handler-case
1594 (compile nil '(lambda (x)
1595 (declare (type (integer -100 100) x))
1596 (declare (optimize speed))
1597 (declare (notinline identity))
1598 (1+ (identity x))))
1599 (compiler-note () (error "IDENTITY derive-type not applied.")))
1601 (assert (null (funcall (compile nil '(lambda (x) (funcall #'cddr x))) nil)))
1603 ;;; MISC.293 = easy variant of bug 303: repeated write to the same
1604 ;;; LVAR; here the first write may be cleared before the second is
1605 ;;; made.
1606 (assert
1607 (zerop
1608 (funcall
1609 (compile
1611 '(lambda ()
1612 (declare (notinline complex))
1613 (declare (optimize (speed 1) (space 0) (safety 1)
1614 (debug 3) (compilation-speed 3)))
1615 (flet ((%f () (multiple-value-prog1 0 (return-from %f 0))))
1616 (complex (%f) 0)))))))
1618 ;;; MISC.110A: CAST optimizer forgot to flush LVAR derived type
1619 (assert (zerop (funcall
1620 (compile
1622 '(lambda (a c)
1623 (declare (type (integer -1294746569 1640996137) a))
1624 (declare (type (integer -807801310 3) c))
1625 (declare (optimize (speed 3) (space 3) (safety 0) (debug 0) (compilation-speed 3)))
1626 (catch 'ct7
1628 (logbitp 0
1629 (if (/= 0 a)
1631 (ignore-errors
1632 (progn (if (ldb-test (byte 0 0) (rational (throw 'ct7 0))) 0 0) 0))))
1633 0 0))))
1634 391833530 -32785211)))
1636 ;;; efficiency notes for ordinary code
1637 (macrolet ((frob (arglist &body body)
1638 `(progn
1639 (handler-case
1640 (compile nil '(lambda ,arglist ,@body))
1641 (sb-ext:compiler-note (e)
1642 (error "bad compiler note for ~S:~% ~A" ',body e)))
1643 (let ((gotit nil))
1644 (handler-bind ((compiler-note
1645 (lambda (c)
1646 (setq gotit t) (muffle-warning c))))
1647 (compile nil '(lambda ,arglist (declare (optimize speed))
1648 ,@body)))
1649 (unless gotit
1650 (error "missing compiler note for ~S" ',body))))))
1651 (frob (x) (funcall x))
1652 (frob (x y) (find x y))
1653 (frob (x y) (find-if x y))
1654 (frob (x y) (find-if-not x y))
1655 (frob (x y) (position x y))
1656 (frob (x y) (position-if x y))
1657 (frob (x y) (position-if-not x y))
1658 (frob (x) (aref x 0)))
1660 (macrolet ((frob (style-warn-p form)
1661 (unless (eq (car form) 'lambda)
1662 (setq form `(lambda () ,form)))
1663 (if style-warn-p
1664 `(let ((gotit nil))
1665 (handler-bind ((style-warning
1666 (lambda (c)
1667 (setq gotit t) (muffle-warning c))))
1668 (compile nil ',form))
1669 (unless gotit
1670 (error "missing style-warning for ~S" ',form)))
1671 `(handler-case
1672 (compile nil ',form)
1673 (style-warning (e)
1674 (error "bad style-warning for ~S: ~A" ',form e))))))
1675 (frob t (lambda (x &optional y &key z) (list x y z)))
1676 (frob nil (lambda (x &optional y z) (list x y z)))
1677 (frob nil (lambda (x &key y z) (list x y z)))
1678 (frob t (defgeneric #:foo (x &optional y &key z)))
1679 (frob nil (defgeneric #:foo (x &optional y z)))
1680 (frob nil (defgeneric #:foo (x &key y z)))
1681 (frob t (defun #:foo (x) (flet ((foo (x &optional y &key z) (list x y z))) (foo x x :z x)))))
1683 ;;; this was a bug in the LOGXOR type deriver. The top form gave a
1684 ;;; note, because the system failed to derive the fact that the return
1685 ;;; from LOGXOR was small and negative, though the bottom one worked.
1686 (handler-bind ((sb-ext:compiler-note #'error))
1687 (compile nil '(lambda ()
1688 (declare (optimize speed (safety 0)))
1689 (lambda (x y)
1690 (declare (type (integer 3 6) x)
1691 (type (integer -6 -3) y))
1692 (+ (logxor x y) most-positive-fixnum)))))
1693 (handler-bind ((sb-ext:compiler-note #'error))
1694 (compile nil '(lambda ()
1695 (declare (optimize speed (safety 0)))
1696 (lambda (x y)
1697 (declare (type (integer 3 6) y)
1698 (type (integer -6 -3) x))
1699 (+ (logxor x y) most-positive-fixnum)))))
1701 ;;; check that modular ash gives the right answer, to protect against
1702 ;;; possible misunderstandings about the hardware shift instruction.
1703 (assert (zerop (funcall
1704 (compile nil '(lambda (x y)
1705 (declare (optimize speed)
1706 (type (unsigned-byte 32) x y))
1707 (logand #xffffffff (ash x y))))
1708 1 257)))
1710 ;;; code instrumenting problems
1711 (compile nil
1712 '(lambda ()
1713 (declare (optimize (debug 3)))
1714 (list (the integer (if nil 14 t)))))
1716 (compile nil
1717 '(LAMBDA (A B C D)
1718 (DECLARE (NOTINLINE LOGORC1 BYTE MASK-FIELD))
1719 (DECLARE
1720 (OPTIMIZE (SPEED 1)
1721 (SPACE 1)
1722 (SAFETY 1)
1723 (DEBUG 3)
1724 (COMPILATION-SPEED 0)))
1725 (MASK-FIELD (BYTE 7 26)
1726 (PROGN
1727 (TAGBODY (THE INTEGER (CATCH 'CT4 (LOGORC1 C -15950))) 1)
1728 B))))
1730 (compile nil
1731 '(lambda (buffer i end)
1732 (declare (optimize (debug 3)))
1733 (loop (when (not (eql 0 end)) (return)))
1734 (let ((s (make-string end)))
1735 (setf (schar s i) (schar buffer i))
1736 s)))
1738 ;;; check that constant string prefix and suffix don't cause the
1739 ;;; compiler to emit code deletion notes.
1740 (handler-bind ((sb-ext:code-deletion-note #'error))
1741 (compile nil '(lambda (s x)
1742 (pprint-logical-block (s x :prefix "(")
1743 (print x s))))
1744 (compile nil '(lambda (s x)
1745 (pprint-logical-block (s x :per-line-prefix ";")
1746 (print x s))))
1747 (compile nil '(lambda (s x)
1748 (pprint-logical-block (s x :suffix ">")
1749 (print x s)))))
1751 ;;; MISC.427: loop analysis requires complete DFO structure
1752 (assert (eql 17 (funcall
1753 (compile
1755 '(lambda (a)
1756 (declare (notinline list reduce logior))
1757 (declare (optimize (safety 2) (compilation-speed 1)
1758 (speed 3) (space 2) (debug 2)))
1759 (logior
1760 (let* ((v5 (reduce #'+ (list 0 a))))
1761 (declare (dynamic-extent v5))
1762 v5))))
1763 17)))
1765 ;;; MISC.434
1766 (assert (zerop (funcall
1767 (compile
1769 '(lambda (a b)
1770 (declare (type (integer -8431780939320 1571817471932) a))
1771 (declare (type (integer -4085 0) b))
1772 (declare (ignorable a b))
1773 (declare
1774 (optimize (space 2)
1775 (compilation-speed 0)
1776 #+sbcl (sb-c:insert-step-conditions 0)
1777 (debug 2)
1778 (safety 0)
1779 (speed 3)))
1780 (let ((*s5* 0))
1781 (dotimes (iv1 2 0)
1782 (let ((*s5*
1783 (elt '(1954479092053)
1784 (min 0
1785 (max 0
1786 (if (< iv1 iv1)
1787 (lognand iv1 (ash iv1 (min 53 iv1)))
1788 iv1))))))
1789 0)))))
1790 -7639589303599 -1368)))
1792 (compile
1794 '(lambda (a b)
1795 (declare (type (integer) a))
1796 (declare (type (integer) b))
1797 (declare (ignorable a b))
1798 (declare (optimize (space 2) (compilation-speed 0)
1799 (debug 0) (safety 0) (speed 3)))
1800 (dotimes (iv1 2 0)
1801 (when (< iv1 2) (print 'x)) ;; request for second constraint propagation pass
1802 (print (if (< iv1 iv1)
1803 (logand (ash iv1 iv1) 1)
1804 iv1)))))
1806 ;;; MISC.435: lambda var substitution in a deleted code.
1807 (assert (zerop (funcall
1808 (compile
1810 '(lambda (a b c d)
1811 (declare (notinline aref logandc2 gcd make-array))
1812 (declare
1813 (optimize (space 0) (safety 0) (compilation-speed 3)
1814 (speed 3) (debug 1)))
1815 (progn
1816 (tagbody
1817 (let* ((v2 (make-array nil :initial-element (catch 'ct1 (go tag2)))))
1818 (declare (dynamic-extent v2))
1819 (gcd (go tag2) (logandc2 (catch 'ct2 c) (aref v2))))
1820 tag2)
1821 0)))
1822 3021871717588 -866608 -2 -17194)))
1824 ;;; MISC.436, 438: lost reoptimization
1825 (assert (zerop (funcall
1826 (compile
1828 '(lambda (a b)
1829 (declare (type (integer -2917822 2783884) a))
1830 (declare (type (integer 0 160159) b))
1831 (declare (ignorable a b))
1832 (declare
1833 (optimize (compilation-speed 1)
1834 (speed 3)
1835 (safety 3)
1836 (space 0)
1837 ; #+sbcl (sb-c:insert-step-conditions 0)
1838 (debug 0)))
1840 (oddp
1841 (loop for
1843 below
1845 count
1846 (logbitp 0
1848 (ash b
1849 (min 8
1850 (count 0
1851 '(-10197561 486 430631291
1852 9674068))))))))
1854 0)))
1855 1265797 110757)))
1857 (assert (zerop (funcall
1858 (compile
1860 ' (lambda (a)
1861 (declare (type (integer 0 1696) a))
1862 ; (declare (ignorable a))
1863 (declare (optimize (space 2) (debug 0) (safety 1)
1864 (compilation-speed 0) (speed 1)))
1865 (if (logbitp 0 (ash (1- a) (min 11 a))) 0 0)))
1866 805)))
1868 ;;; bug #302
1869 (assert (compile
1871 '(lambda (s ei x y)
1872 (declare (type (simple-array function (2)) s) (type ei ei))
1873 (funcall (aref s ei) x y))))
1875 ;;; MISC.320: ir1-transform can create an intercomponent reference to
1876 ;;; a DEFINED-FUN.
1877 (assert (eql 102 (funcall
1878 (compile
1880 '(lambda ()
1881 (declare (optimize (speed 3) (space 0) (safety 2)
1882 (debug 2) (compilation-speed 0)))
1883 (catch 'ct2
1884 (elt '(102)
1885 (flet ((%f12 () (rem 0 -43)))
1886 (multiple-value-call #'%f12 (values))))))))))
1888 ;;; MISC.437: lost reoptimization after FLUSH-DEST
1889 (assert (zerop (funcall
1890 (compile
1892 '(lambda (a b c d e)
1893 (declare (notinline values complex eql))
1894 (declare
1895 (optimize (compilation-speed 3)
1896 (speed 3)
1897 (debug 1)
1898 (safety 1)
1899 (space 0)))
1900 (flet ((%f10
1901 (f10-1 f10-2 f10-3
1902 &optional (f10-4 (ignore-errors 0)) (f10-5 0)
1903 &key &allow-other-keys)
1904 (if (or (eql 0 0) t) 0 (if f10-1 0 0))))
1905 (complex (multiple-value-call #'%f10 (values a c b 0 0)) 0))))
1906 80043 74953652306 33658947 -63099937105 -27842393)))
1908 ;;; bug #351 -- program-error for malformed LET and LET*, including those
1909 ;;; resulting from SETF of LET.
1910 (with-test (:name :bug-351)
1911 (dolist (fun (list (compile nil '(lambda (x) (let :bogus-let :oops)))
1912 (compile nil '(lambda (x) (let* :bogus-let* :oops)))
1913 (compile nil '(lambda (x) (push x (let ((y 0)) y))))))
1914 (assert (functionp fun))
1915 (multiple-value-bind (res err) (ignore-errors (funcall fun t))
1916 (princ err) (terpri)
1917 (assert (not res))
1918 (assert (typep err 'program-error)))))
1920 (let ((fun (compile nil '(lambda (x) (random (if x 10 20))))))
1921 (dotimes (i 100 (error "bad RANDOM distribution"))
1922 (when (> (funcall fun nil) 9)
1923 (return t)))
1924 (dotimes (i 100)
1925 (when (> (funcall fun t) 9)
1926 (error "bad RANDOM event"))))
1928 ;;; 0.8.17.28-sma.1 lost derived type information.
1929 (with-test (:name :0.8.17.28-sma.1 :fails-on :sparc)
1930 (handler-bind ((sb-ext:compiler-note (lambda (c) (error "~A" c))))
1931 (compile nil
1932 '(lambda (x y v)
1933 (declare (optimize (speed 3) (safety 0)))
1934 (declare (type (integer 0 80) x)
1935 (type (integer 0 11) y)
1936 (type (simple-array (unsigned-byte 32) (*)) v))
1937 (setf (aref v 0) (* (* x #.(floor (ash 1 32) (* 11 80))) y))
1938 nil))))
1940 ;;; Bug reported by Robert J. Macomber: instrumenting of more-entry
1941 ;;; prevented open coding of %LISTIFY-REST-ARGS.
1942 (let ((f (compile nil '(lambda ()
1943 (declare (optimize (debug 3)))
1944 (with-simple-restart (blah "blah") (error "blah"))))))
1945 (handler-bind ((error (lambda (c) (invoke-restart 'blah))))
1946 (assert (equal (multiple-value-list (funcall f)) '(nil t)))))
1948 ;;; Bug reported by Timmy Douglas: overflow in bit vector setter with
1949 ;;; constant index and value.
1950 (loop for n-bits = 1 then (* n-bits 2)
1951 for type = `(unsigned-byte ,n-bits)
1952 and v-max = (1- (ash 1 n-bits))
1953 while (<= n-bits sb-vm:n-word-bits)
1955 (let* ((n (* 2 (1+ (- sb-vm::n-word-bits n-bits))))
1956 (array1 (make-array n :element-type type))
1957 (array2 (make-array n :element-type type)))
1958 (dotimes (i n)
1959 (dolist (v (list 0 v-max))
1960 (let ((f (compile nil `(lambda (a)
1961 (declare (type (simple-array ,type (,n)) a))
1962 (setf (aref a ,i) ,v)))))
1963 (fill array1 (- v-max v))
1964 (fill array2 (- v-max v))
1965 (funcall f array1)
1966 (setf (aref array2 i) v)
1967 (assert (every #'= array1 array2)))))))
1969 (let ((fn (compile nil '(lambda (x)
1970 (declare (type bit x))
1971 (declare (optimize speed))
1972 (let ((b (make-array 64 :element-type 'bit
1973 :initial-element 0)))
1974 (count x b))))))
1975 (assert (= (funcall fn 0) 64))
1976 (assert (= (funcall fn 1) 0)))
1978 (let ((fn (compile nil '(lambda (x y)
1979 (declare (type simple-bit-vector x y))
1980 (declare (optimize speed))
1981 (equal x y)))))
1982 (assert (funcall
1984 (make-array 64 :element-type 'bit :initial-element 0)
1985 (make-array 64 :element-type 'bit :initial-element 0)))
1986 (assert (not
1987 (funcall
1989 (make-array 64 :element-type 'bit :initial-element 0)
1990 (let ((b (make-array 64 :element-type 'bit :initial-element 0)))
1991 (setf (sbit b 63) 1)
1992 b)))))
1994 ;;; MISC.535: compiler failure
1995 (let ((c0 #c(4196.088977268509d0 -15943.3603515625d0)))
1996 (assert (not (funcall
1997 (compile
1999 `(lambda (p1 p2)
2000 (declare (optimize speed (safety 1))
2001 (type (eql ,c0) p1)
2002 (type number p2))
2003 (eql (the (complex double-float) p1) p2)))
2004 c0 #c(12 612/979)))))
2006 ;;; reported by Lutz Euler: we shouldn't signal a compiler note for
2007 ;;; simple-bit-vector functions.
2008 (with-test (:name (:simple-bit-vector :count :should-not-compiler-note))
2009 (handler-bind ((sb-ext:compiler-note (lambda (c) (error "~A" c))))
2010 (compile nil '(lambda (x)
2011 (declare (type simple-bit-vector x))
2012 (count 1 x)))))
2013 (with-test (:name (:simple-bit-vector :equal :should-not-compiler-note))
2014 (handler-bind ((sb-ext:compiler-note (lambda (c) (error "~A" c))))
2015 (compile nil '(lambda (x y)
2016 (declare (type simple-bit-vector x y))
2017 (equal x y)))))
2019 ;;; MISC.550: CAST merging in IR1 finalization caused unexpected
2020 ;;; code transformations.
2021 (assert (eql (funcall
2022 (compile
2024 '(lambda (p1 p2)
2025 (declare (optimize (speed 3) (safety 2) (debug 3) (space 3))
2026 (type atom p1)
2027 (type symbol p2))
2028 (or p1 (the (eql t) p2))))
2029 nil t)
2032 ;;; MISC.548: type check weakening converts required type into
2033 ;;; optional
2034 (assert (eql t
2035 (funcall
2036 (compile
2038 '(lambda (p1)
2039 (declare (optimize (speed 2) (safety 1) (debug 3) (space 2)))
2040 (atom (the (member f assoc-if write-line t w) p1))))
2041 t)))
2043 ;;; Free special bindings only apply to the body of the binding form, not
2044 ;;; the initialization forms.
2045 (assert (eq :good
2046 (funcall (compile 'nil
2047 '(lambda ()
2048 (let ((x :bad))
2049 (declare (special x))
2050 (let ((x :good))
2051 ((lambda (&optional (y x))
2052 (declare (special x)) y)))))))))
2054 ;;; Bug from pfdietz's random tester: the compiler knew that IMAGPART of
2055 ;;; a rational was zero, but didn't do the substitution, leading to a
2056 ;;; crash in the ASH vop (since a shift of 57 wouldn't fit in the
2057 ;;; machine's ASH instruction's immediate field) that the compiler
2058 ;;; thought was legitimate.
2059 (with-test (:name :overlarge-immediate-in-ash-vop)
2060 (checked-compile `(lambda (b)
2061 (declare (type (integer -2 14) b))
2062 (declare (ignorable b))
2063 (ash (imagpart b) 57))))
2065 ;;; bug reported by Eduardo Mu\~noz
2066 (with-test (:name (compile vector loop))
2067 (checked-compile
2068 `(lambda (struct first)
2069 (declare (optimize speed))
2070 (let* ((nodes (nodes struct))
2071 (bars (bars struct))
2072 (length (length nodes))
2073 (new (make-array length :fill-pointer 0)))
2074 (vector-push first new)
2075 (loop with i fixnum = 0
2076 for newl fixnum = (length new)
2077 while (< newl length) do
2078 (let ((oldl (length new)))
2079 (loop for j fixnum from i below newl do
2080 (dolist (n (node-neighbours (aref new j) bars))
2081 (unless (find n new)
2082 (vector-push n new))))
2083 (setq i oldl)))
2084 new))
2085 :allow-style-warnings t))
2087 ;;; bug #389: "0.0 can't be converted to type NIL." (Brian Rowe
2088 ;;; sbcl-devel)
2089 (with-test (:name (compile float :bug-389))
2090 (checked-compile `(lambda (x y a b c)
2091 (- y (* (signum x) (sqrt (abs (- (* b x) c))))))
2092 :allow-style-warnings t))
2094 ;;; Type inference from CHECK-TYPE
2095 (let ((count0 0) (count1 0))
2096 (handler-bind ((sb-ext:compiler-note (lambda (c) (incf count0))))
2097 (compile nil '(lambda (x)
2098 (declare (optimize (speed 3)))
2099 (1+ x))))
2100 ;; forced-to-do GENERIC-+, etc, possible word -> bignum conversion note
2101 (assert (> count0 1))
2102 (handler-bind ((sb-ext:compiler-note (lambda (c) (incf count1))))
2103 (compile nil '(lambda (x)
2104 (declare (optimize (speed 3)))
2105 (check-type x fixnum)
2106 (1+ x))))
2107 ;; Only the posssible word -> bignum conversion note
2108 (assert (= count1 1)))
2110 ;;; Up to 0.9.8.22 x86-64 had broken return value handling in the
2111 ;;; %SET-SAP-REF-DOUBLE/SINGLE VOPs.
2112 (with-test (:name :sap-ref-float)
2113 (compile nil '(lambda (sap)
2114 (let ((x (setf (sb-vm::sap-ref-double sap 0) 1d0)))
2115 (1+ x))))
2116 (compile nil '(lambda (sap)
2117 (let ((x (setf (sb-vm::sap-ref-single sap 0) 1d0)))
2118 (1+ x)))))
2120 ;;; bug #399
2121 (with-test (:name :string-union-types)
2122 (compile nil '(lambda (x)
2123 (declare (type (or (simple-array character (6))
2124 (simple-array character (5))) x))
2125 (aref x 0))))
2127 ;;; MISC.623: missing functions for constant-folding
2128 (assert (eql 0
2129 (funcall
2130 (compile
2132 '(lambda ()
2133 (declare (optimize (space 2) (speed 0) (debug 2)
2134 (compilation-speed 3) (safety 0)))
2135 (loop for lv3 below 1
2136 count (minusp
2137 (loop for lv2 below 2
2138 count (logbitp 0
2139 (bit #*1001101001001
2140 (min 12 (max 0 lv3))))))))))))
2142 ;;; MISC.624: erroneous AVER in x86's %LOGBITP VOPs
2143 (assert (eql 0
2144 (funcall
2145 (compile
2147 '(lambda (a)
2148 (declare (type (integer 21 28) a))
2149 (declare (optimize (compilation-speed 1) (safety 2)
2150 (speed 0) (debug 0) (space 1)))
2151 (let* ((v7 (flet ((%f3 (f3-1 f3-2)
2152 (loop for lv2 below 1
2153 count
2154 (logbitp 29
2155 (sbit #*10101111
2156 (min 7 (max 0 (eval '0))))))))
2157 (%f3 0 a))))
2158 0)))
2159 22)))
2161 ;;; MISC.626: bandaged AVER was still wrong
2162 (assert (eql -829253
2163 (funcall
2164 (compile
2166 '(lambda (a)
2167 (declare (type (integer -902970 2) a))
2168 (declare (optimize (space 2) (debug 0) (compilation-speed 1)
2169 (speed 0) (safety 3)))
2170 (prog2 (if (logbitp 30 a) 0 (block b3 0)) a)))
2171 -829253)))
2173 ;; MISC.628: constant-folding %LOGBITP was buggy
2174 (with-test (:name (compile logbitp :constant-folding))
2175 (assert (eql t
2176 (funcall
2177 (checked-compile
2178 `(lambda ()
2179 (declare (optimize (safety 3) (space 3) (compilation-speed 3)
2180 (speed 0) (debug 1)))
2181 (not (not (logbitp 0 (floor 2147483651 (min -23 0)))))))))))
2183 ;; mistyping found by random-tester
2184 (with-test (:name (compile :type-derivation))
2185 (assert (zerop
2186 (funcall
2187 (checked-compile
2188 `(lambda ()
2189 (declare (optimize (speed 1) (debug 0)
2190 (space 2) (safety 0) (compilation-speed 0)))
2191 (unwind-protect 0
2192 (* (/ (multiple-value-prog1 -29457482 -5602513511) 1)))))))))
2194 ;; aggressive constant folding (bug #400)
2195 (with-test (:name (compile :aggressive-constant-folding :bug-400))
2196 (assert
2197 (eq t (funcall (checked-compile `(lambda () (or t (the integer (/ 1 0)))))))))
2199 (with-test (:name (:compiler :constraint-propagation :var-eql-to-non-var-1))
2200 (checked-compile `(lambda (x y)
2201 (when (eql x (length y))
2202 (locally
2203 (declare (optimize (speed 3)))
2204 (1+ x))))
2205 :allow-notes '(not compiler-note)))
2207 (with-test (:name (:compiler :constraint-propagation :var-eql-to-non-var-2))
2208 (checked-compile `(lambda (x y)
2209 (when (eql (length y) x)
2210 (locally
2211 (declare (optimize (speed 3)))
2212 (1+ x))))
2213 :allow-notes '(not compiler-note)))
2215 (with-test (:name (:compiler :constraint-propagation :float-bounds-1))
2216 (checked-compile `(lambda (x)
2217 (declare (type (single-float * (3.0)) x))
2218 (when (<= x 2.0)
2219 (when (<= 2.0 x)
2220 x)))
2221 :allow-notes '(not compiler-note)))
2223 (defun assert-code-deletion-note (lambda &optional (howmany 1))
2224 (let ((notes (nth-value
2225 4 (checked-compile lambda :allow-notes 'code-deletion-note))))
2226 (assert (= howmany (length notes)))))
2228 (with-test (:name (:compiler :constraint-propagation :float-bounds-2))
2229 (assert-code-deletion-note
2230 `(lambda (x)
2231 (declare (type single-float x))
2232 (when (< 1.0 x)
2233 (when (<= x 1.0)
2234 (error "This is unreachable."))))))
2236 (with-test (:name (:compiler :constraint-propagation :float-bounds-3
2237 :LP-894498))
2238 (assert-code-deletion-note
2239 `(lambda (x)
2240 (declare (type (single-float 0.0) x))
2241 (when (> x 0.0)
2242 (when (zerop x)
2243 (error "This is unreachable."))))))
2245 (with-test (:name (:compiler :constraint-propagation :float-bounds-4
2246 :LP-894498))
2247 (assert-code-deletion-note
2248 `(lambda (x y)
2249 (declare (type (single-float 0.0) x)
2250 (type (single-float (0.0)) y))
2251 (when (> x y)
2252 (when (zerop x)
2253 (error "This is unreachable."))))))
2255 (with-test (:name (:compiler :constraint-propagation :var-eql-to-var-1))
2256 (assert-code-deletion-note
2257 `(lambda (x y)
2258 (when (typep y 'fixnum)
2259 (when (eql x y)
2260 (unless (typep x 'fixnum)
2261 (error "This is unreachable"))
2262 (setq y nil))))))
2264 (with-test (:name (:compiler :constraint-propagation :var-eql-to-var-2))
2265 (assert-code-deletion-note
2266 `(lambda (x y)
2267 (when (typep y 'fixnum)
2268 (when (eql y x)
2269 (unless (typep x 'fixnum)
2270 (error "This is unreachable"))
2271 (setq y nil))))))
2273 ;; Reported by John Wiseman, sbcl-devel
2274 ;; Subject: [Sbcl-devel] float type derivation bug?
2275 ;; Date: Tue, 4 Apr 2006 15:28:15 -0700
2276 (with-test (:name (compile :type-derivation :float-bounds))
2277 (checked-compile
2278 `(lambda (bits)
2279 (let* ((s (if (= (ash bits -31) 0) 1 -1))
2280 (e (logand (ash bits -23) #xff))
2281 (m (if (= e 0)
2282 (ash (logand bits #x7fffff) 1)
2283 (logior (logand bits #x7fffff) #x800000))))
2284 (float (* s m (expt 2 (- e 150))))))))
2286 ;; Reported by James Knight
2287 ;; Subject: [Sbcl-devel] AVER: "(EQ (SB-NAME (SC-SB (TN-SC TN))) 'REGISTERS)"
2288 ;; Date: Fri, 24 Mar 2006 19:30:00 -0500
2289 (with-test (:name (compile logbitp :vop))
2290 (checked-compile
2291 `(lambda (days shift)
2292 (declare (type fixnum shift days))
2293 (let* ((result 0)
2294 (canonicalized-shift (+ shift 1))
2295 (first-wrapping-day (- 1 canonicalized-shift)))
2296 (declare (type fixnum result))
2297 (dotimes (source-day 7)
2298 (declare (type (integer 0 6) source-day))
2299 (when (logbitp source-day days)
2300 (setf result
2301 (logior result
2302 (the fixnum
2303 (if (< source-day first-wrapping-day)
2304 (+ source-day canonicalized-shift)
2305 (- (+ source-day
2306 canonicalized-shift)
2307 7)))))))
2308 result))))
2310 ;;; MISC.637: incorrect delaying of conversion of optional entries
2311 ;;; with hairy constant defaults
2312 (with-test (:name (compile :optional-entry :hairy-defaults :misc.637))
2313 (let ((fun (checked-compile
2314 `(lambda ()
2315 (labels ((%f11 (f11-2 &key key1)
2316 (labels ((%f8 (f8-2 &optional (f8-5 (if nil (return-from %f11 0) 0)))
2317 :bad1))
2318 (%f8 (%f8 0)))
2319 :bad2))
2320 :good)))))
2321 (assert (eq (funcall fun) :good))))
2323 ;;; MISC.555: new reference to an already-optimized local function
2324 (with-test (:name (compile :already-optimized :local-function :misc.555))
2325 (let ((fun (checked-compile
2326 `(lambda (p1)
2327 (declare (optimize (speed 1) (safety 2) (debug 2) (space 0))
2328 (type keyword p1))
2329 (keywordp p1)))))
2330 (assert (funcall fun :good))
2331 (assert-error (funcall fun 42) type-error)))
2333 ;;; Check that the compiler doesn't munge *RANDOM-STATE*.
2334 (let* ((state (make-random-state))
2335 (*random-state* (make-random-state state))
2336 (a (random most-positive-fixnum)))
2337 (setf *random-state* state)
2338 (compile nil `(lambda (x a)
2339 (declare (single-float x)
2340 (type (simple-array double-float) a))
2341 (+ (loop for i across a
2342 summing i)
2343 x)))
2344 (assert (= a (random most-positive-fixnum))))
2346 ;;; MISC.641: LET-conversion after physical environment analysis lost NLX-INFOs
2347 (with-test (:name (compile let :conversion :lost :nlx-infos :misc.641))
2348 (let ((fun (checked-compile
2349 `(lambda ()
2350 (declare (optimize (speed 1) (space 0) (debug 2)
2351 (compilation-speed 0) (safety 1)))
2352 (flet ((%f3 (f3-1 &key (key1 (count (floor 0 (min -74 0)) #())))
2354 (apply #'%f3 0 nil)))
2355 :allow-style-warnings t)))
2356 (assert (zerop (funcall fun)))))
2358 ;;; 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
2359 (with-test (:name (compile make-array aref :size-mismatch))
2360 (checked-compile `(lambda ()
2361 (let ((x (make-array '(1) :element-type '(signed-byte 32))))
2362 (setf (aref x 0) 1)))))
2364 ;;; step instrumentation confusing the compiler, reported by Faré
2365 (with-test (:name (compile step))
2366 (checked-compile `(lambda ()
2367 (declare (optimize (debug 2))) ; not debug 3!
2368 (let ((val "foobar"))
2369 (map-into (make-array (list (length val))
2370 :element-type '(unsigned-byte 8))
2371 #'char-code val)))))
2373 ;;; overconfident primitive type computation leading to bogus type
2374 ;;; checking.
2375 (let* ((form1 '(lambda (x)
2376 (declare (type (and condition function) x))
2378 (fun1 (compile nil form1))
2379 (form2 '(lambda (x)
2380 (declare (type (and standard-object function) x))
2382 (fun2 (compile nil form2)))
2383 (assert-error (funcall fun1 (make-condition 'error)))
2384 (assert-error (funcall fun1 fun1))
2385 (assert-error (funcall fun2 fun2))
2386 (assert (eq (funcall fun2 #'print-object) #'print-object)))
2388 ;;; LET* + VALUES declaration: while the declaration is a non-standard
2389 ;;; and possibly a non-conforming extension, as long as we do support
2390 ;;; it, we might as well get it right.
2392 ;;; Bug reported by Kaersten Poeck on sbcl-devel 20061023.
2393 (compile nil '(lambda () (let* () (declare (values list)))))
2396 ;;; test for some problems with too large immediates in x86-64 modular
2397 ;;; arithmetic vops
2398 (compile nil '(lambda (x) (declare (fixnum x))
2399 (logand most-positive-fixnum (logxor x most-positive-fixnum))))
2401 (compile nil '(lambda (x) (declare (fixnum x))
2402 (logand most-positive-fixnum (+ x most-positive-fixnum))))
2404 (compile nil '(lambda (x) (declare (fixnum x))
2405 (logand most-positive-fixnum (* x most-positive-fixnum))))
2407 ;;; bug 256.b
2408 (with-test (:name :propagate-type-through-error-and-binding)
2409 (assert (let (warned-p)
2410 (handler-bind ((warning (lambda (w) (setf warned-p t))))
2411 (compile nil
2412 '(lambda (x)
2413 (list (let ((y (the real x)))
2414 (unless (floatp y) (error ""))
2416 (integer-length x)))))
2417 warned-p)))
2419 ;; Dead / in safe code
2420 (with-test (:name :safe-dead-/)
2421 (assert (eq :error
2422 (handler-case
2423 (funcall (compile nil
2424 '(lambda (x y)
2425 (declare (optimize (safety 3)))
2426 (/ x y)
2427 (+ x y)))
2430 (division-by-zero ()
2431 :error)))))
2433 ;;; Dead unbound variable (bug 412)
2434 (with-test (:name :dead-unbound)
2435 (assert (eq :error
2436 (handler-case
2437 (funcall (compile nil
2438 '(lambda ()
2439 #:unbound
2440 42)))
2441 (unbound-variable ()
2442 :error)))))
2444 ;;; No compiler notes from compiling SUBSEQ SIMPLE-VECTOR.
2445 (handler-bind ((sb-ext:compiler-note 'error))
2446 (assert
2447 (equalp #(2 3)
2448 (funcall (compile nil `(lambda (s p e)
2449 (declare (optimize speed)
2450 (simple-vector s))
2451 (subseq s p e)))
2452 (vector 1 2 3 4)
2454 3))))
2456 ;;; No compiler notes from compiling COPY-SEQ SIMPLE-VECTOR.
2457 (handler-bind ((sb-ext:compiler-note 'error))
2458 (assert
2459 (equalp #(1 2 3 4)
2460 (funcall (compile nil `(lambda (s)
2461 (declare (optimize speed)
2462 (simple-vector s))
2463 (copy-seq s)))
2464 (vector 1 2 3 4)))))
2466 ;;; bug in adding DATA-VECTOR-REF-WITH-OFFSET to x86-64
2467 (assert (not (mismatch #(1.0f0 2.0f0) (make-array 2 :element-type 'single-float :initial-contents (list 1.0f0 2.0f0)))))
2469 ;;; bug in interval-arithmetic used by the compiler: needless attempt to coerce too
2470 ;;; large bignums to floats
2471 (dolist (op '(* / + -))
2472 (let ((fun (compile
2474 `(lambda (x)
2475 (declare (type (integer 0 #.(* 2 (truncate most-positive-double-float))) x))
2476 (,op 0.0d0 x)))))
2477 (loop repeat 10
2478 do (let ((arg (random (truncate most-positive-double-float))))
2479 (assert (eql (funcall fun arg)
2480 (funcall op 0.0d0 arg)))))))
2482 (with-test (:name :high-debug-known-function-inlining)
2483 (let ((fun (compile nil
2484 '(lambda ()
2485 (declare (optimize (debug 3)) (inline append))
2486 (let ((fun (lambda (body)
2487 (append
2488 (first body)
2489 nil))))
2490 (funcall fun
2491 '((foo (bar)))))))))
2492 (funcall fun)))
2494 (with-test (:name :high-debug-known-function-transform-with-optional-arguments)
2495 (compile nil '(lambda (x y)
2496 (declare (optimize sb-c::preserve-single-use-debug-variables))
2497 (if (block nil
2498 (some-unknown-function
2499 (lambda ()
2500 (return (member x y))))
2503 (error "~a" y)))))
2505 ;;; Compiling W-P-O when the pinned objects are known to be fixnums
2506 ;;; or characters.
2507 (compile nil '(lambda (x y)
2508 (declare (fixnum y) (character x))
2509 (sb-sys:with-pinned-objects (x y)
2510 (some-random-function))))
2512 ;;; *CHECK-CONSISTENCY* and TRULY-THE
2514 (with-test (:name :bug-423)
2515 (let ((sb-c::*check-consistency* t))
2516 (handler-bind ((warning #'error))
2517 (flet ((make-lambda (type)
2518 `(lambda (x)
2519 ((lambda (z)
2520 (if (listp z)
2521 (let ((q (truly-the list z)))
2522 (length q))
2523 (if (arrayp z)
2524 (let ((q (truly-the vector z)))
2525 (length q))
2526 (error "oops"))))
2527 (the ,type x)))))
2528 (compile nil (make-lambda 'list))
2529 (compile nil (make-lambda 'vector))))))
2531 ;;; this caused a momentary regression when an ill-adviced fix to
2532 ;;; bug 427 made ANY-REG suitable for primitive-type T:
2534 ;;; 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)
2535 ;;; [Condition of type SIMPLE-ERROR]
2536 (compile nil
2537 '(lambda (frob)
2538 (labels
2539 ((%zig (frob)
2540 (typecase frob
2541 (double-float
2542 (setf (sb-alien:deref (sb-alien:cast (sb-alien:sap-alien (unknown1) (* unsigned-char))
2543 (* double-float))) frob))
2544 (hash-table
2545 (%zig (the (values (single-float (0.0) 1.0) &optional) (unknown2)))
2546 nil))))
2547 (%zig))))
2549 ;;; non-required arguments in HANDLER-BIND
2550 (assert (eq :oops (car (funcall (compile nil
2551 '(lambda (x)
2552 (block nil
2553 (handler-bind ((error (lambda (&rest args) (return (cons :oops args)))))
2554 (/ 2 x)))))
2555 0))))
2557 ;;; NIL is a legal function name
2558 (assert (eq 'a (flet ((nil () 'a)) (nil))))
2560 ;;; misc.528
2561 (assert (null (let* ((x 296.3066f0)
2562 (y 22717067)
2563 (form `(lambda (r p2)
2564 (declare (optimize speed (safety 1))
2565 (type (simple-array single-float nil) r)
2566 (type (integer -9369756340 22717335) p2))
2567 (setf (aref r) (* ,x (the (eql 22717067) p2)))
2568 (values)))
2569 (r (make-array nil :element-type 'single-float))
2570 (expected (* x y)))
2571 (funcall (compile nil form) r y)
2572 (let ((actual (aref r)))
2573 (unless (eql expected actual)
2574 (list expected actual))))))
2575 ;;; misc.529
2576 (assert (null (let* ((x -2367.3296f0)
2577 (y 46790178)
2578 (form `(lambda (r p2)
2579 (declare (optimize speed (safety 1))
2580 (type (simple-array single-float nil) r)
2581 (type (eql 46790178) p2))
2582 (setf (aref r) (+ ,x (the (integer 45893897) p2)))
2583 (values)))
2584 (r (make-array nil :element-type 'single-float))
2585 (expected (+ x y)))
2586 (funcall (compile nil form) r y)
2587 (let ((actual (aref r)))
2588 (unless (eql expected actual)
2589 (list expected actual))))))
2591 ;;; misc.556
2592 (assert (eql -1
2593 (funcall
2594 (compile nil '(lambda (p1 p2)
2595 (declare
2596 (optimize (speed 1) (safety 0)
2597 (debug 0) (space 0))
2598 (type (member 8174.8604) p1)
2599 (type (member -95195347) p2))
2600 (floor p1 p2)))
2601 8174.8604 -95195347)))
2603 ;;; misc.557
2604 (assert (eql -1
2605 (funcall
2606 (compile
2608 '(lambda (p1)
2609 (declare (optimize (speed 3) (safety 0) (debug 3) (space 1))
2610 (type (member -94430.086f0) p1))
2611 (floor (the single-float p1) 19311235)))
2612 -94430.086f0)))
2614 ;;; misc.558
2615 (assert (eql -1.0f0
2616 (funcall
2617 (compile
2619 '(lambda (p1)
2620 (declare (optimize (speed 1) (safety 2)
2621 (debug 2) (space 3))
2622 (type (eql -39466.56f0) p1))
2623 (ffloor p1 305598613)))
2624 -39466.56f0)))
2626 ;;; misc.559
2627 (assert (eql 1
2628 (funcall
2629 (compile
2631 '(lambda (p1)
2632 (declare (optimize (speed 1) (safety 1) (debug 1) (space 2))
2633 (type (eql -83232.09f0) p1))
2634 (ceiling p1 -83381228)))
2635 -83232.09f0)))
2637 ;;; misc.560
2638 (assert (eql 1
2639 (funcall
2640 (compile
2642 '(lambda (p1)
2643 (declare (optimize (speed 1) (safety 1)
2644 (debug 1) (space 0))
2645 (type (member -66414.414f0) p1))
2646 (ceiling p1 -63019173f0)))
2647 -66414.414f0)))
2649 ;;; misc.561
2650 (assert (eql 1.0f0
2651 (funcall
2652 (compile
2654 '(lambda (p1)
2655 (declare (optimize (speed 0) (safety 1)
2656 (debug 0) (space 1))
2657 (type (eql 20851.398f0) p1))
2658 (fceiling p1 80839863)))
2659 20851.398f0)))
2661 ;;; misc.581
2662 (assert (floatp
2663 (funcall
2664 (compile nil '(lambda (x)
2665 (declare (type (eql -5067.2056) x))
2666 (+ 213734822 x)))
2667 -5067.2056)))
2669 ;;; misc.581a
2670 (assert (typep
2671 (funcall
2672 (compile nil '(lambda (x) (declare (type (eql -1.0) x))
2673 (+ #x1000001 x)))
2674 -1.0f0)
2675 'single-float))
2677 ;;; misc.582
2678 (assert (plusp (funcall
2679 (compile
2681 ' (lambda (p1)
2682 (declare (optimize (speed 0) (safety 1) (debug 1) (space 1))
2683 (type (eql -39887.645) p1))
2684 (mod p1 382352925)))
2685 -39887.645)))
2687 ;;; misc.587
2688 (assert (let ((result (funcall
2689 (compile
2691 '(lambda (p2)
2692 (declare (optimize (speed 0) (safety 3) (debug 1) (space 0))
2693 (type (eql 33558541) p2))
2694 (- 92215.266 p2)))
2695 33558541)))
2696 (typep result 'single-float)))
2698 ;;; misc.635
2699 (assert (eql 1
2700 (let* ((form '(lambda (p2)
2701 (declare (optimize (speed 0) (safety 1)
2702 (debug 2) (space 2))
2703 (type (member -19261719) p2))
2704 (ceiling -46022.094 p2))))
2705 (values (funcall (compile nil form) -19261719)))))
2707 ;;; misc.636
2708 (assert (let* ((x 26899.875)
2709 (form `(lambda (p2)
2710 (declare (optimize (speed 3) (safety 1) (debug 3) (space 1))
2711 (type (member ,x #:g5437 char-code #:g5438) p2))
2712 (* 104102267 p2))))
2713 (floatp (funcall (compile nil form) x))))
2715 ;;; misc.622
2716 (assert (eql
2717 (funcall
2718 (compile
2720 '(lambda (p2)
2721 (declare (optimize (speed 3) (safety 2) (debug 3) (space 0))
2722 (type real p2))
2723 (+ 81535869 (the (member 17549.955 #:g35917) p2))))
2724 17549.955)
2725 (+ 81535869 17549.955)))
2727 ;;; misc.654
2728 (assert (eql 2
2729 (let ((form '(lambda (p2)
2730 (declare (optimize (speed 0) (safety 2) (debug 0) (space 2))
2731 (type (member integer eql) p2))
2732 (coerce 2 p2))))
2733 (funcall (compile nil form) 'integer))))
2735 ;;; misc.656
2736 (assert (eql 2
2737 (let ((form '(lambda (p2)
2738 (declare (optimize (speed 0) (safety 2) (debug 0) (space 2))
2739 (type (member integer mod) p2))
2740 (coerce 2 p2))))
2741 (funcall (compile nil form) 'integer))))
2743 ;;; misc.657
2744 (assert (eql 2
2745 (let ((form '(lambda (p2)
2746 (declare (optimize (speed 0) (safety 2) (debug 0) (space 2))
2747 (type (member integer values) p2))
2748 (coerce 2 p2))))
2749 (funcall (compile nil form) 'integer))))
2751 (with-test (:name :string-aref-type)
2752 (assert (eq 'character
2753 (funcall (compile nil
2754 '(lambda (s)
2755 (ctu:compiler-derived-type (aref (the string s) 0))))
2756 "foo"))))
2758 (with-test (:name :base-string-aref-type)
2759 (assert (eq #+sb-unicode 'base-char
2760 #-sb-unicode 'character
2761 (funcall (compile nil
2762 '(lambda (s)
2763 (ctu:compiler-derived-type (aref (the base-string s) 0))))
2764 (coerce "foo" 'base-string)))))
2766 (with-test (:name :dolist-constant-type-derivation)
2767 (assert (equal '(integer 1 3)
2768 (funcall (compile nil
2769 '(lambda (x)
2770 (dolist (y '(1 2 3))
2771 (when x
2772 (return (ctu:compiler-derived-type y))))))
2773 t))))
2775 (with-test (:name :dolist-simple-list-type-derivation)
2776 (assert (equal '(integer 1 3)
2777 (funcall (compile nil
2778 '(lambda (x)
2779 (dolist (y (list 1 2 3))
2780 (when x
2781 (return (ctu:compiler-derived-type y))))))
2782 t))))
2784 (with-test (:name :dolist-dotted-constant-list-type-derivation)
2785 (let* ((warned nil)
2786 (fun (handler-bind ((style-warning (lambda (c) (push c warned))))
2787 (compile nil
2788 '(lambda (x)
2789 (dolist (y '(1 2 3 . 4) :foo)
2790 (when x
2791 (return (ctu:compiler-derived-type y)))))))))
2792 (assert (equal '(integer 1 3) (funcall fun t)))
2793 (assert (= 1 (length warned)))
2794 (multiple-value-bind (res err) (ignore-errors (funcall fun nil))
2795 (assert (not res))
2796 (assert (typep err 'type-error)))))
2798 (with-test (:name :constant-list-destructuring)
2799 (handler-bind ((sb-ext:compiler-note #'error))
2800 (progn
2801 (assert (= 10
2802 (funcall
2803 (compile nil
2804 '(lambda ()
2805 (destructuring-bind (a (b c) d) '(1 (2 3) 4)
2806 (+ a b c d)))))))
2807 (assert (eq :feh
2808 (funcall
2809 (compile nil
2810 '(lambda (x)
2811 (or x
2812 (destructuring-bind (a (b c) d) '(1 "foo" 4)
2813 (+ a b c d)))))
2814 :feh))))))
2816 ;;; Functions with non-required arguments used to end up with
2817 ;;; (&OPTIONAL-DISPATCH ...) as their names.
2818 (with-test (:name :hairy-function-name)
2819 (assert (eq 'read-line (nth-value 2 (function-lambda-expression #'read-line))))
2820 (assert (equal "#<FUNCTION READ-LINE>" (princ-to-string #'read-line))))
2822 ;;; PROGV + RESTRICT-COMPILER-POLICY
2823 ;; META: there's a test in compiler.impure.lisp that also tests
2824 ;; interaction of PROGV with (debug 3). These tests should be together.
2825 (with-test (:name :progv-and-restrict-compiler-policy)
2826 (let ((sb-c::*policy-restrictions* sb-c::*policy-restrictions*))
2827 (restrict-compiler-policy 'debug 3)
2828 (let ((fun (compile nil '(lambda (x)
2829 (let ((i x))
2830 (declare (special i))
2831 (list i
2832 (progv '(i) (list (+ i 1))
2834 i))))))
2835 (assert (equal '(1 2 1) (funcall fun 1))))))
2837 ;;; It used to be possible to confuse the compiler into
2838 ;;; IR2-converting such a call to CONS
2839 (with-test (:name :late-bound-primitive)
2840 (compile nil `(lambda ()
2841 (funcall 'cons 1))))
2843 (with-test (:name :hairy-array-element-type-derivation)
2844 (compile nil '(lambda (x)
2845 (declare (type (and simple-string (satisfies array-has-fill-pointer-p)) x))
2846 (array-element-type x))))
2848 (with-test (:name :rest-list-type-derivation)
2849 (multiple-value-bind (type derivedp)
2850 (funcall (compile nil `(lambda (&rest args)
2851 (ctu:compiler-derived-type args)))
2852 nil)
2853 (assert (eq 'list type))
2854 (assert derivedp)))
2856 (with-test (:name :rest-list-type-derivation2)
2857 (multiple-value-bind (type derivedp)
2858 (funcall (funcall (compile nil `(lambda ()
2859 (lambda (&rest args)
2860 (ctu:compiler-derived-type args))))))
2861 (assert (eq 'list type))
2862 (assert derivedp)))
2864 (with-test (:name :rest-list-type-derivation3)
2865 (multiple-value-bind (type derivedp)
2866 (funcall (funcall (compile nil `(lambda ()
2867 (lambda (&optional x &rest args)
2868 (unless x (error "oops"))
2869 (ctu:compiler-derived-type args)))))
2871 (assert (eq 'list type))
2872 (assert derivedp)))
2874 (with-test (:name :rest-list-type-derivation4)
2875 (multiple-value-bind (type derivedp)
2876 (funcall (funcall (compile nil `(lambda ()
2877 (lambda (&optional x &rest args)
2878 (declare (type (or null integer) x))
2879 (when x (setf args x))
2880 (ctu:compiler-derived-type args)))))
2882 (assert (equal '(or cons null integer) type))
2883 (assert derivedp)))
2885 (with-test (:name :base-char-typep-elimination)
2886 (assert (eq (funcall (compile nil
2887 `(lambda (ch)
2888 (declare (type base-char ch) (optimize (speed 3) (safety 0)))
2889 (typep ch 'base-char)))
2891 t)))
2893 (with-test (:name :regression-1.0.24.37)
2894 (checked-compile `(lambda (&key (test (constantly t)))
2895 (when (funcall test)
2896 :quux))))
2898 ;;; Attempt to test a decent cross section of conditions
2899 ;;; and values types to move conditionally.
2900 (macrolet
2901 ((test-comparison (comparator type x y)
2902 `(progn
2903 ,@(loop for (result-type a b)
2904 in '((nil t nil)
2905 (nil 0 1)
2906 (nil 0.0 1.0)
2907 (nil 0d0 0d0)
2908 (nil 0.0 0d0)
2909 (nil #c(1.0 1.0) #c(2.0 2.0))
2911 (t t nil)
2912 (fixnum 0 1)
2913 ((unsigned-byte #.sb-vm:n-word-bits)
2914 (1+ most-positive-fixnum)
2915 (+ 2 most-positive-fixnum))
2916 ((signed-byte #.sb-vm:n-word-bits)
2917 -1 (* 2 most-negative-fixnum))
2918 (single-float 0.0 1.0)
2919 (double-float 0d0 1d0))
2920 for lambda = (if result-type
2921 `(lambda (x y a b)
2922 (declare (,type x y)
2923 (,result-type a b))
2924 (if (,comparator x y)
2925 a b))
2926 `(lambda (x y)
2927 (declare (,type x y))
2928 (if (,comparator x y)
2929 ,a ,b)))
2930 for args = `(,x ,y ,@(and result-type
2931 `(,a ,b)))
2932 collect
2933 `(progn
2934 (eql (funcall (checked-compile ',lambda)
2935 ,@args)
2936 (eval '(,lambda ,@args))))))))
2937 (sb-vm::with-float-traps-masked
2938 (:divide-by-zero :overflow :inexact :invalid)
2939 (let (#+sb-eval (sb-ext:*evaluator-mode* :interpret))
2940 (declare (sb-ext:muffle-conditions style-warning))
2941 (test-comparison eql t t nil)
2942 (test-comparison eql t t t)
2944 (test-comparison = t 1 0)
2945 (test-comparison = t 1 1)
2946 (test-comparison = t (1+ most-positive-fixnum) (+ 2 most-positive-fixnum))
2947 (test-comparison = fixnum 1 0)
2948 (test-comparison = fixnum 0 0)
2949 (test-comparison = (unsigned-byte #.sb-vm:n-word-bits) 1 0)
2950 (test-comparison = (unsigned-byte #.sb-vm:n-word-bits) 0 0)
2951 (test-comparison = (signed-byte #.sb-vm:n-word-bits) 1 0)
2952 (test-comparison = (signed-byte #.sb-vm:n-word-bits) 1 1)
2954 (test-comparison = single-float 0.0 1.0)
2955 (test-comparison = single-float 1.0 1.0)
2956 (test-comparison = single-float (/ 1.0 0.0) (/ 1.0 0.0))
2957 (test-comparison = single-float (/ 1.0 0.0) 1.0)
2958 (test-comparison = single-float (/ 0.0 0.0) (/ 0.0 0.0))
2959 (test-comparison = single-float (/ 0.0 0.0) 0.0)
2961 (test-comparison = double-float 0d0 1d0)
2962 (test-comparison = double-float 1d0 1d0)
2963 (test-comparison = double-float (/ 1d0 0d0) (/ 1d0 0d0))
2964 (test-comparison = double-float (/ 1d0 0d0) 1d0)
2965 (test-comparison = double-float (/ 0d0 0d0) (/ 0d0 0d0))
2966 (test-comparison = double-float (/ 0d0 0d0) 0d0)
2968 (test-comparison < t 1 0)
2969 (test-comparison < t 0 1)
2970 (test-comparison < t 1 1)
2971 (test-comparison < t (1+ most-positive-fixnum) (+ 2 most-positive-fixnum))
2972 (test-comparison < t (+ 2 most-positive-fixnum) (1+ most-positive-fixnum))
2973 (test-comparison < fixnum 1 0)
2974 (test-comparison < fixnum 0 1)
2975 (test-comparison < fixnum 0 0)
2976 (test-comparison < (unsigned-byte #.sb-vm:n-word-bits) 1 0)
2977 (test-comparison < (unsigned-byte #.sb-vm:n-word-bits) 0 1)
2978 (test-comparison < (unsigned-byte #.sb-vm:n-word-bits) 0 0)
2979 (test-comparison < (signed-byte #.sb-vm:n-word-bits) 1 0)
2980 (test-comparison < (signed-byte #.sb-vm:n-word-bits) 0 1)
2981 (test-comparison < (signed-byte #.sb-vm:n-word-bits) 1 1)
2983 (test-comparison < single-float 0.0 1.0)
2984 (test-comparison < single-float 1.0 0.0)
2985 (test-comparison < single-float 1.0 1.0)
2986 (test-comparison < single-float (/ 1.0 0.0) (/ 1.0 0.0))
2987 (test-comparison < single-float (/ 1.0 0.0) 1.0)
2988 (test-comparison < single-float 1.0 (/ 1.0 0.0))
2989 (test-comparison < single-float (/ 0.0 0.0) (/ 0.0 0.0))
2990 (test-comparison < single-float (/ 0.0 0.0) 0.0)
2992 (test-comparison < double-float 0d0 1d0)
2993 (test-comparison < double-float 1d0 0d0)
2994 (test-comparison < double-float 1d0 1d0)
2995 (test-comparison < double-float (/ 1d0 0d0) (/ 1d0 0d0))
2996 (test-comparison < double-float (/ 1d0 0d0) 1d0)
2997 (test-comparison < double-float 1d0 (/ 1d0 0d0))
2998 (test-comparison < double-float (/ 0d0 0d0) (/ 0d0 0d0))
2999 (test-comparison < double-float (/ 0d0 0d0) 0d0)
3000 (test-comparison < double-float 0d0 (/ 0d0 0d0))
3002 (test-comparison > t 1 0)
3003 (test-comparison > t 0 1)
3004 (test-comparison > t 1 1)
3005 (test-comparison > t (1+ most-positive-fixnum) (+ 2 most-positive-fixnum))
3006 (test-comparison > t (+ 2 most-positive-fixnum) (1+ most-positive-fixnum))
3007 (test-comparison > fixnum 1 0)
3008 (test-comparison > fixnum 0 1)
3009 (test-comparison > fixnum 0 0)
3010 (test-comparison > (unsigned-byte #.sb-vm:n-word-bits) 1 0)
3011 (test-comparison > (unsigned-byte #.sb-vm:n-word-bits) 0 1)
3012 (test-comparison > (unsigned-byte #.sb-vm:n-word-bits) 0 0)
3013 (test-comparison > (signed-byte #.sb-vm:n-word-bits) 1 0)
3014 (test-comparison > (signed-byte #.sb-vm:n-word-bits) 0 1)
3015 (test-comparison > (signed-byte #.sb-vm:n-word-bits) 1 1)
3017 (test-comparison > single-float 0.0 1.0)
3018 (test-comparison > single-float 1.0 0.0)
3019 (test-comparison > single-float 1.0 1.0)
3020 (test-comparison > single-float (/ 1.0 0.0) (/ 1.0 0.0))
3021 (test-comparison > single-float (/ 1.0 0.0) 1.0)
3022 (test-comparison > single-float 1.0 (/ 1.0 0.0))
3023 (test-comparison > single-float (/ 0.0 0.0) (/ 0.0 0.0))
3024 (test-comparison > single-float (/ 0.0 0.0) 0.0)
3026 (test-comparison > double-float 0d0 1d0)
3027 (test-comparison > double-float 1d0 0d0)
3028 (test-comparison > double-float 1d0 1d0)
3029 (test-comparison > double-float (/ 1d0 0d0) (/ 1d0 0d0))
3030 (test-comparison > double-float (/ 1d0 0d0) 1d0)
3031 (test-comparison > double-float 1d0 (/ 1d0 0d0))
3032 (test-comparison > double-float (/ 0d0 0d0) (/ 0d0 0d0))
3033 (test-comparison > double-float (/ 0d0 0d0) 0d0)
3034 (test-comparison > double-float 0d0 (/ 0d0 0d0)))))
3036 (with-test (:name :car-and-cdr-type-derivation-conservative)
3037 (let ((f1 (checked-compile
3038 `(lambda (y)
3039 (declare (optimize speed))
3040 (let ((x (the (cons fixnum fixnum) (cons 1 2))))
3041 (declare (type (cons t fixnum) x))
3042 (rplaca x y)
3043 (+ (car x) (cdr x))))))
3044 (f2 (checked-compile
3045 `(lambda (y)
3046 (declare (optimize speed))
3047 (let ((x (the (cons fixnum fixnum) (cons 1 2))))
3048 (setf (cdr x) y)
3049 (+ (car x) (cdr x)))))))
3050 (flet ((test-error (e value)
3051 (assert (typep e 'type-error))
3052 (assert (eq 'number (type-error-expected-type e)))
3053 (assert (eq value (type-error-datum e)))))
3054 (let ((v1 "foo")
3055 (v2 "bar"))
3056 (multiple-value-bind (res err) (ignore-errors (funcall f1 v1))
3057 (assert (not res))
3058 (test-error err v1))
3059 (multiple-value-bind (res err) (ignore-errors (funcall f2 v2))
3060 (assert (not res))
3061 (test-error err v2))))))
3063 (with-test (:name :array-dimension-derivation-conservative)
3064 (let ((f (checked-compile `(lambda (x)
3065 (declare (optimize speed))
3066 (declare (type (array * (4 4)) x))
3067 (let ((y x))
3068 (setq x (make-array '(4 4)))
3069 (adjust-array y '(3 5))
3070 (array-dimension y 0))))))
3071 (assert (= 3 (funcall f (make-array '(4 4) :adjustable t))))))
3073 (with-test (:name :with-timeout-code-deletion-note)
3074 (checked-compile `(lambda ()
3075 (sb-ext:with-timeout 0
3076 (sleep 1)))
3077 :allow-notes nil))
3079 (with-test (:name :full-warning-for-undefined-type-in-cl)
3080 (multiple-value-bind (fun failure-p warnings)
3081 (checked-compile `(lambda (x) (the replace x)) :allow-warnings t)
3082 (declare (ignore fun failure-p))
3083 (assert (= 1 (length warnings)))))
3085 (with-test (:name :single-warning-for-single-undefined-type)
3086 ;; STYLE-WARNING for symbol not in cl package.
3087 (multiple-value-bind (fun failure-p warnings style-warnings)
3088 (checked-compile `(lambda (x) (the #:no-type x))
3089 :allow-style-warnings t)
3090 (declare (ignore fun failure-p warnings))
3091 (assert (= 1 (length style-warnings))))
3093 ;; Full WARNING for invalid type specifier starting with QUOTE.
3094 (multiple-value-bind (fun failure-p warnings)
3095 (checked-compile `(lambda (x) (the 'fixnum x)) :allow-warnings t)
3096 (declare (ignore fun failure-p))
3097 (assert (= 1 (length warnings)))))
3099 (with-test (:name :complex-subtype-dumping-in-xc)
3100 (assert
3101 (= sb-vm:complex-single-float-widetag
3102 (sb-kernel:widetag-of
3103 (sb-vm:saetp-initial-element-default (sb-c::find-saetp '(complex single-float))))))
3104 (assert
3105 (= sb-vm:complex-double-float-widetag
3106 (sb-kernel:widetag-of
3107 (sb-vm:saetp-initial-element-default (sb-c::find-saetp '(complex double-float)))))))
3109 (with-test (:name :complex-single-float-fill)
3110 (assert (every (lambda (x) (= #c(1.0 2.0) x))
3111 (funcall
3112 (compile nil
3113 `(lambda (n x)
3114 (make-array (list n)
3115 :element-type '(complex single-float)
3116 :initial-element x)))
3118 #c(1.0 2.0)))))
3120 (with-test (:name :regression-1.0.28.21)
3121 (let ((fun (compile nil `(lambda (x) (typep x '(simple-array * 1))))))
3122 (assert (funcall fun (vector 1 2 3)))
3123 (assert (funcall fun "abc"))
3124 (assert (not (funcall fun (make-array '(2 2)))))))
3126 (with-test (:name :no-silly-compiler-notes-from-character-function)
3127 (dolist (name '(char-code char-int character char-name standard-char-p
3128 graphic-char-p alpha-char-p upper-case-p lower-case-p
3129 both-case-p digit-char-p alphanumericp digit-char-p))
3130 (checked-compile `(lambda (x)
3131 (declare (character x) (optimize (speed 3)))
3132 (,name x))
3133 :allow-notes nil))
3134 (dolist (name '(char= char/= char< char> char<= char>=
3135 char-lessp char-greaterp char-not-greaterp
3136 char-not-lessp))
3137 (checked-compile `(lambda (x y)
3138 (declare (character x y) (optimize speed))
3139 (,name x y))
3140 :allow-notes nil)))
3142 ;;; optimizing make-array
3143 (with-test (:name (make-array :open-code-initial-contents))
3144 (flet ((test (form)
3145 (assert (not (ctu:find-named-callees
3146 (checked-compile form))))))
3147 (test `(lambda (x y z)
3148 (make-array '(3) :initial-contents (list x y z))))
3149 (test `(lambda (x y z)
3150 (make-array '3 :initial-contents (vector x y z))))
3151 (test `(lambda (x y z)
3152 (make-array '3 :initial-contents `(,x ,y ,z))))))
3154 ;;; optimizing array-in-bounds-p
3155 (with-test (:name :optimize-array-in-bounds-p)
3156 (locally
3157 (macrolet ((find-callees (&body body)
3158 `(ctu:find-named-callees
3159 (checked-compile '(lambda () ,@body))
3160 :name 'array-in-bounds-p))
3161 (must-optimize (&body exprs)
3162 `(progn
3163 ,@(loop for expr in exprs
3164 collect `(assert (not (find-callees
3165 ,expr))))))
3166 (must-not-optimize (&body exprs)
3167 `(progn
3168 ,@(loop for expr in exprs
3169 collect `(assert (find-callees
3170 ,expr))))))
3171 (must-optimize
3172 ;; in bounds
3173 (let ((a (make-array '(1))))
3174 (array-in-bounds-p a 0))
3175 ;; exceeds upper bound (constant)
3176 (let ((a (make-array '(1))))
3177 (array-in-bounds-p a 1))
3178 ;; exceeds upper bound (interval)
3179 (let ((a (make-array '(1))))
3180 (array-in-bounds-p a (+ 1 (random 2))))
3181 ;; negative lower bound (constant)
3182 (let ((a (make-array '(1))))
3183 (array-in-bounds-p a -1))
3184 ;; negative lower bound (interval)
3185 (let ((a (make-array 3))
3186 (i (- (random 1) 20)))
3187 (array-in-bounds-p a i))
3188 ;; multiple known dimensions
3189 (let ((a (make-array '(1 1))))
3190 (array-in-bounds-p a 0 0))
3191 ;; union types
3192 (let ((s (the (simple-string 10) (eval "0123456789"))))
3193 (array-in-bounds-p s 9)))
3194 (must-not-optimize
3195 ;; don't trust non-simple array length in safety=1
3196 (let ((a (the (array * (10 20)) (make-array '(10 20) :adjustable t))))
3197 (eval `(adjust-array ,a '(0 0)))
3198 (array-in-bounds-p a 9 0))
3199 ;; multiple unknown dimensions
3200 (let ((a (make-array (list (random 20) (random 5)))))
3201 (array-in-bounds-p a 5 2))
3202 ;; some other known dimensions
3203 (let ((a (make-array (list 1 (random 5)))))
3204 (array-in-bounds-p a 0 2))
3205 ;; subscript might be negative
3206 (let ((a (make-array '(5 10))))
3207 (array-in-bounds-p a 1 (- (random 3) 2)))
3208 ;; subscript might be too large
3209 (let ((a (make-array '(5 10))))
3210 (array-in-bounds-p a (random 6) 1))
3211 ;; unknown upper bound
3212 (let ((a (make-array '(5 10))))
3213 (array-in-bounds-p a (get-universal-time) 1))
3214 ;; unknown lower bound
3215 (let ((a (make-array '(5 30))))
3216 (array-in-bounds-p a 0 (- (get-universal-time))))
3217 ;; in theory we should be able to optimize
3218 ;; the following but the current implementation
3219 ;; doesn't cut it because the array type's
3220 ;; dimensions get reported as (* *).
3221 (let ((a (make-array (list (random 20) 1))))
3222 (array-in-bounds-p a 5 2))))))
3224 ;;; optimizing (EXPT -1 INTEGER)
3225 (with-test (:name (expt -1 integer))
3226 (dolist (x '(-1 -1.0 -1.0d0))
3227 (let ((fun (checked-compile `(lambda (x) (expt ,x (the fixnum x))))))
3228 (assert (not (ctu:find-named-callees fun)))
3229 (dotimes (i 12)
3230 (if (oddp i)
3231 (assert (eql x (funcall fun i)))
3232 (assert (eql (- x) (funcall fun i))))))))
3234 (with-test (:name :float-division-using-exact-reciprocal)
3235 (flet ((test (lambda-form arg res &key (check-insts t))
3236 (let* ((fun (checked-compile lambda-form))
3237 (disassembly (with-output-to-string (s)
3238 (disassemble fun :stream s))))
3239 ;; Let's make sure there is no division at runtime: for x86 and
3240 ;; x86-64 that implies an FDIV, DIVSS, or DIVSD instruction, so
3241 ;; look for DIV in the disassembly. It's a terrible KLUDGE, but
3242 ;; it works.
3243 #+(or x86 x86-64)
3244 (when check-insts
3245 (assert (not (search "DIV" disassembly))))
3246 ;; No generic arithmetic!
3247 (assert (not (search "GENERIC" disassembly)))
3248 (assert (eql res (funcall fun arg))))))
3249 (dolist (c '(128 64 32 16 8 4 2 1 1/2 1/4 1/8 1/16 1/32 1/64))
3250 (dolist (type '(single-float double-float))
3251 (let* ((cf (coerce c type))
3252 (arg (- (random (* 2 cf)) cf))
3253 (r1 (eval `(/ ,arg ,cf)))
3254 (r2 (eval `(/ ,arg ,(- cf)))))
3255 (test `(lambda (x) (declare (,type x)) (/ x ,cf)) arg r1)
3256 (test `(lambda (x) (declare (,type x)) (/ x ,(- cf))) arg r2)
3257 ;; rational args should get optimized as well
3258 (test `(lambda (x) (declare (,type x)) (/ x ,c)) arg r1)
3259 (test `(lambda (x) (declare (,type x)) (/ x ,(- c))) arg r2))))
3260 ;; Also check that inexact reciprocals (1) are not used by default (2) are
3261 ;; used with FLOAT-ACCURACY=0.
3262 (dolist (type '(single-float double-float))
3263 (let ((trey (coerce 3 type))
3264 (one (coerce 1 type)))
3265 (test `(lambda (x) (declare (,type x)) (/ x 3)) trey one
3266 :check-insts nil)
3267 (test `(lambda (x)
3268 (declare (,type x)
3269 (optimize (sb-c::float-accuracy 0)))
3270 (/ x 3))
3271 trey (eval `(* ,trey (/ ,trey))))))))
3273 (with-test (:name :float-multiplication-by-one)
3274 (flet ((test (lambda-form arg &optional (result arg))
3275 (let* ((fun1 (checked-compile lambda-form))
3276 (fun2 (funcall (checked-compile
3277 `(lambda ()
3278 (declare (optimize (sb-c::float-accuracy 0)))
3279 ,lambda-form))))
3280 (disassembly1 (with-output-to-string (s)
3281 (disassemble fun1 :stream s)))
3282 (disassembly2 (with-output-to-string (s)
3283 (disassemble fun2 :stream s))))
3284 ;; Multiplication at runtime should be eliminated only with
3285 ;; FLOAT-ACCURACY=0. (To catch SNaNs.)
3286 #+(or x86 x86-64)
3287 (assert (and (search "MUL" disassembly1)
3288 (not (search "MUL" disassembly2))))
3289 ;; Not generic arithmetic, please!
3290 (assert (and (not (search "GENERIC" disassembly1))
3291 (not (search "GENERIC" disassembly2))))
3292 (assert (eql result (funcall fun1 arg)))
3293 (assert (eql result (funcall fun2 arg))))))
3294 (dolist (type '(single-float double-float))
3295 (let* ((one (coerce 1 type))
3296 (arg (random (* 2 one)))
3297 (-r (- arg)))
3298 (test `(lambda (x) (declare (,type x)) (* x 1)) arg)
3299 (test `(lambda (x) (declare (,type x)) (* x -1)) arg -r)
3300 (test `(lambda (x) (declare (,type x)) (* x ,one)) arg)
3301 (test `(lambda (x) (declare (,type x)) (* x ,(- one))) arg -r)))))
3303 (with-test (:name :float-addition-of-zero)
3304 (flet ((test (lambda-form arg &optional (result arg))
3305 (let* ((fun1 (checked-compile lambda-form))
3306 (fun2 (funcall (checked-compile
3307 `(lambda ()
3308 (declare (optimize (sb-c::float-accuracy 0)))
3309 ,lambda-form))))
3310 (disassembly1 (with-output-to-string (s)
3311 (disassemble fun1 :stream s)))
3312 (disassembly2 (with-output-to-string (s)
3313 (disassemble fun2 :stream s))))
3314 ;; Let's make sure there is no addition at runtime: for x86 and
3315 ;; x86-64 that implies an FADD, ADDSS, or ADDSD instruction, so
3316 ;; look for the ADDs in the disassembly. It's a terrible KLUDGE,
3317 ;; but it works. Unless FLOAT-ACCURACY is zero, we leave the
3318 ;; addition in to catch SNaNs.
3319 #+x86
3320 (assert (and (search "FADD" disassembly1)
3321 (not (search "FADD" disassembly2))))
3322 #+x86-64
3323 (let ((inst (if (typep result 'double-float)
3324 "ADDSD" "ADDSS")))
3325 (assert (and (search inst disassembly1)
3326 (not (search inst disassembly2)))))
3327 (assert (eql result (funcall fun1 arg)))
3328 (assert (eql result (funcall fun2 arg))))))
3329 (test `(lambda (x) (declare (single-float x)) (+ x 0)) 123.45)
3330 (test `(lambda (x) (declare (single-float x)) (+ x 0.0)) 543.21)
3331 (test `(lambda (x) (declare (single-float x)) (+ x 0.0d0)) 42.00 42.d0)
3332 (test `(lambda (x) (declare (double-float x)) (+ x 0)) 123.45d0)
3333 (test `(lambda (x) (declare (double-float x)) (+ x 0.0)) 543.21d0)
3334 (test `(lambda (x) (declare (double-float x)) (+ x 0.0d0)) 42.d0)))
3336 (with-test (:name :float-substraction-of-zero)
3337 (flet ((test (lambda-form arg &optional (result arg))
3338 (let* ((fun1 (compile nil lambda-form))
3339 (fun2 (funcall (compile nil `(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 ;; Let's make sure there is no substraction at runtime: for x86
3347 ;; and x86-64 that implies an FSUB, SUBSS, or SUBSD instruction,
3348 ;; so look for SUB in the disassembly. It's a terrible KLUDGE,
3349 ;; but it works. Unless FLOAT-ACCURACY is zero, we leave the
3350 ;; substraction in in to catch SNaNs.
3351 #+x86
3352 (assert (and (search "FSUB" disassembly1)
3353 (not (search "FSUB" disassembly2))))
3354 #+x86-64
3355 (let ((inst (if (typep result 'double-float)
3356 "SUBSD" "SUBSS")))
3357 (assert (and (search inst disassembly1)
3358 (not (search inst disassembly2)))))
3359 (assert (eql result (funcall fun1 arg)))
3360 (assert (eql result (funcall fun2 arg))))))
3361 (test `(lambda (x) (declare (single-float x)) (- x 0)) 123.45)
3362 (test `(lambda (x) (declare (single-float x)) (- x 0.0)) 543.21)
3363 (test `(lambda (x) (declare (single-float x)) (- x 0.0d0)) 42.00 42.d0)
3364 (test `(lambda (x) (declare (double-float x)) (- x 0)) 123.45d0)
3365 (test `(lambda (x) (declare (double-float x)) (- x 0.0)) 543.21d0)
3366 (test `(lambda (x) (declare (double-float x)) (- x 0.0d0)) 42.d0)))
3368 (with-test (:name :float-multiplication-by-two)
3369 (flet ((test (lambda-form arg &optional (result arg))
3370 (let* ((fun1 (compile nil lambda-form))
3371 (fun2 (funcall (compile nil `(lambda ()
3372 (declare (optimize (sb-c::float-accuracy 0)))
3373 ,lambda-form))))
3374 (disassembly1 (with-output-to-string (s)
3375 (disassemble fun1 :stream s)))
3376 (disassembly2 (with-output-to-string (s)
3377 (disassemble fun2 :stream s))))
3378 ;; Let's make sure there is no multiplication at runtime: for x86
3379 ;; and x86-64 that implies an FMUL, MULSS, or MULSD instruction,
3380 ;; so look for MUL in the disassembly. It's a terrible KLUDGE,
3381 ;; but it works.
3382 #+(or x86 x86-64)
3383 (assert (and (not (search "MUL" disassembly1))
3384 (not (search "MUL" disassembly2))))
3385 (assert (eql result (funcall fun1 arg)))
3386 (assert (eql result (funcall fun2 arg))))))
3387 (test `(lambda (x) (declare (single-float x)) (* x 2)) 123.45 246.9)
3388 (test `(lambda (x) (declare (single-float x)) (* x 2.0)) 543.21 1086.42)
3389 (test `(lambda (x) (declare (single-float x)) (* x 2.0d0)) 42.00 84.d0)
3390 (test `(lambda (x) (declare (double-float x)) (* x 2)) 123.45d0 246.9d0)
3391 (test `(lambda (x) (declare (double-float x)) (* x 2.0)) 543.21d0 1086.42d0)
3392 (test `(lambda (x) (declare (double-float x)) (* x 2.0d0)) 42.0d0 84.0d0)))
3394 (with-test (:name :bug-392203)
3395 ;; Used to hit an AVER in COMVERT-MV-CALL.
3396 (assert (zerop (funcall
3397 (checked-compile
3398 `(lambda ()
3399 (flet ((k (&rest x) (declare (ignore x)) 0))
3400 (multiple-value-call #'k #'k))))))))
3402 (with-test (:name :allocate-closures-failing-aver)
3403 (let ((f (checked-compile `(lambda ()
3404 (labels ((k (&optional x) #'k))))
3405 :allow-style-warnings t)))
3406 (assert (null (funcall f)))))
3408 (with-test (:name :flush-vector-creation :skipped-on :interpreter)
3409 (let ((f (checked-compile `(lambda ()
3410 (dotimes (i 1024)
3411 (vector i i i))
3412 t))))
3413 (ctu:assert-no-consing (funcall f))))
3415 (with-test (:name :array-type-predicates)
3416 (dolist (et (list* '(integer -1 200) '(integer -256 1)
3417 '(integer 0 128)
3418 '(integer 0 (128))
3419 '(double-float 0d0 (1d0))
3420 '(single-float (0s0) (1s0))
3421 '(or (eql 1d0) (eql 10d0))
3422 '(member 1 2 10)
3423 '(complex (member 10 20))
3424 '(complex (member 10d0 20d0))
3425 '(complex (member 10s0 20s0))
3426 '(or integer double-float)
3427 '(mod 1)
3428 '(member #\a #\b)
3429 '(eql #\a)
3430 #+sb-unicode 'extended-char
3431 #+sb-unicode '(eql #\cyrillic_small_letter_yu)
3432 sb-kernel::*specialized-array-element-types*))
3433 (when et
3434 (let* ((v (make-array 3 :element-type et))
3435 (fun (checked-compile
3436 `(lambda ()
3437 (list (if (typep ,v '(simple-array ,et (*)))
3438 :good
3439 :bad)
3440 (if (typep (elt ,v 0) '(simple-array ,et (*)))
3441 :bad
3442 :good))))))
3443 (assert (equal '(:good :good) (funcall fun)))))))
3445 (with-test (:name :truncate-float)
3446 (let ((s (checked-compile `(lambda (x)
3447 (declare (single-float x))
3448 (truncate x))))
3449 (d (checked-compile `(lambda (x)
3450 (declare (double-float x))
3451 (truncate x))))
3452 (s-inlined (checked-compile
3453 `(lambda (x)
3454 (declare (type (single-float 0.0s0 1.0s0) x))
3455 (truncate x))))
3456 (d-inlined (checked-compile
3457 `(lambda (x)
3458 (declare (type (double-float 0.0d0 1.0d0) x))
3459 (truncate x)))))
3460 ;; Check that there is no generic arithmetic
3461 (assert (not (search "GENERIC"
3462 (with-output-to-string (out)
3463 (disassemble s :stream out)))))
3464 (assert (not (search "GENERIC"
3465 (with-output-to-string (out)
3466 (disassemble d :stream out)))))
3467 ;; Check that we actually inlined the call when we were supposed to.
3468 (assert (not (search "UNARY-TRUNCATE"
3469 (with-output-to-string (out)
3470 (disassemble s-inlined :stream out)))))
3471 (assert (not (search "UNARY-TRUNCATE"
3472 (with-output-to-string (out)
3473 (disassemble d-inlined :stream out)))))))
3475 (with-test (:name (make-array :unnamed-dimension-leaf))
3476 (let ((fun (checked-compile `(lambda (stuff)
3477 (make-array (map 'list 'length stuff))))))
3478 (assert (equalp #2A((0 0 0) (0 0 0))
3479 (funcall fun '((1 2) (1 2 3)))))))
3481 (with-test (:name :fp-decoding-funs-not-flushable-in-safe-code)
3482 (dolist (name '(float-sign float-radix float-digits float-precision decode-float
3483 integer-decode-float))
3484 (let ((fun (checked-compile `(lambda (x)
3485 (declare (optimize safety))
3486 (,name x)
3487 nil))))
3488 (flet ((test (arg)
3489 (unless (eq :error
3490 (handler-case
3491 (funcall fun arg)
3492 (error () :error)))
3493 (error "(~S ~S) did not error"
3494 name arg))))
3495 ;; No error
3496 (funcall fun 1.0)
3497 ;; Error
3498 (test 'not-a-float)
3499 (when (member name '(decode-float integer-decode-float))
3500 (test sb-ext:single-float-positive-infinity))))))
3502 (with-test (:name :sap-ref-16)
3503 (let* ((fun (checked-compile
3504 `(lambda (x y)
3505 (declare (type sb-sys:system-area-pointer x)
3506 (type (integer 0 100) y))
3507 (sb-sys:sap-ref-16 x (+ 4 y)))))
3508 (vector (coerce '(0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15)
3509 '(simple-array (unsigned-byte 8) (*))))
3510 (sap (sb-sys:vector-sap vector))
3511 (ret (funcall fun sap 0)))
3512 ;; test for either endianness
3513 (assert (or (= ret (+ (* 5 256) 4)) (= ret (+ (* 4 256) 5))))))
3515 (with-test (:name (compile coerce :type-warning))
3516 (dolist (type '(t (unsigned-byte 8) (unsigned-byte 16) (unsigned-byte 32)
3517 (signed-byte 8) (signed-byte 16) (signed-byte 32)))
3518 (let ((fun (checked-compile `(lambda (x)
3519 (declare (type simple-vector x))
3520 (coerce x '(vector ,type))))))
3521 (assert (typep (funcall fun #(1)) `(simple-array ,type (*)))))))
3523 (with-test (:name (compile truncate double-float))
3524 (let ((fun (checked-compile `(lambda (x)
3525 (multiple-value-bind (q r)
3526 (truncate (coerce x 'double-float))
3527 (declare (type unsigned-byte q)
3528 (type double-float r))
3529 (list q r))))))
3530 (assert (equal (funcall fun 1.0d0) '(1 0.0d0)))))
3532 (with-test (:name :set-slot-value-no-warning)
3533 (let ((notes (nth-value
3534 4 (checked-compile `(lambda (x y)
3535 (declare (optimize speed safety))
3536 (setf (slot-value x 'bar) y))))))
3537 (assert (= 1 (length notes)))))
3539 (with-test (:name (concatenate :string-opt))
3540 (flet ((test (type grep)
3541 (let* ((fun (checked-compile `(lambda (a b c d e)
3542 (concatenate ',type a b c d e))))
3543 (args '("foo" #(#\.) "bar" (#\-) "quux"))
3544 (res (apply fun args)))
3545 (assert (search grep (with-output-to-string (out)
3546 (disassemble fun :stream out))))
3547 (assert (equal (apply #'concatenate type args)
3548 res))
3549 (assert (typep res type)))))
3550 (test 'string "%CONCATENATE-TO-STRING")
3551 (test 'simple-string "%CONCATENATE-TO-STRING")
3552 (test 'base-string "%CONCATENATE-TO-BASE-STRING")
3553 (test 'simple-base-string "%CONCATENATE-TO-BASE-STRING")))
3555 (with-test (:name (satisfies :no-local-fun))
3556 (let ((fun (checked-compile
3557 `(lambda (arg)
3558 (labels ((local-not-global-bug (x)
3560 (bar (x)
3561 (typep x '(satisfies local-not-global-bug))))
3562 (bar arg))))))
3563 (assert (eq 'local-not-global-bug
3564 (handler-case
3565 (funcall fun 42)
3566 (undefined-function (c)
3567 (cell-error-name c)))))))
3569 ;;; Prior to 1.0.32.x, dumping a fasl with a function with a default
3570 ;;; argument that is a complex structure (needing make-load-form
3571 ;;; processing) failed an AVER. The first attempt at a fix caused
3572 ;;; doing the same in-core to break.
3573 (with-test (:name :bug-310132)
3574 (checked-compile `(lambda (&optional (foo #p"foo/bar")))
3575 :allow-style-warnings t))
3577 (with-test (:name :bug-309129)
3578 (multiple-value-bind (fun failurep warnings)
3579 (checked-compile `(lambda (v) (values (svref v 0) (vector-pop v)))
3580 :allow-failure t :allow-warnings t)
3581 (assert failurep)
3582 (assert (= 1 (length warnings)))
3583 (handler-case (funcall fun #(1))
3584 (type-error (c)
3585 ;; we used to put simply VECTOR into EXPECTED-TYPE, rather
3586 ;; than explicitly (AND VECTOR (NOT SIMPLE-ARRAY))
3587 (assert (not (typep (type-error-datum c) (type-error-expected-type c)))))
3588 (:no-error (&rest values)
3589 (declare (ignore values))
3590 (error "no error")))))
3592 (with-test (:name (round :unary :type-derivation))
3593 (let ((fun (checked-compile
3594 `(lambda (zone)
3595 (multiple-value-bind (h m) (truncate (abs zone) 1.0)
3596 (declare (ignore h))
3597 (round (* 60.0 m)))))))
3598 (assert (= (funcall fun 0.5) 30))))
3600 (with-test (:name :bug-525949)
3601 (let ((fun (checked-compile
3602 `(lambda ()
3603 (labels ((always-one () 1)
3604 (f (z)
3605 (let ((n (funcall z)))
3606 (declare (fixnum n))
3607 (the double-float (expt n 1.0d0)))))
3608 (f #'always-one))))))
3609 (assert (= 1.0d0 (funcall fun)))))
3611 (with-test (:name :%array-data-vector-type-derivation)
3612 (let* ((f (checked-compile
3613 `(lambda (ary)
3614 (declare (type (simple-array (unsigned-byte 32) (3 3)) ary))
3615 (setf (aref ary 0 0) 0))))
3616 (text (with-output-to-string (s)
3617 (disassemble f :stream s))))
3618 (assert (not (search "OBJECT-NOT-SIMPLE-ARRAY-UNSIGNED-BYTE-32-ERROR" text)))))
3620 (with-test (:name :array-storage-vector-type-derivation)
3621 (let ((f (checked-compile
3622 `(lambda (ary)
3623 (declare (type (simple-array (unsigned-byte 32) (3 3)) ary))
3624 (ctu:compiler-derived-type (array-storage-vector ary))))))
3625 (assert (equal '(simple-array (unsigned-byte 32) (9))
3626 (funcall f (make-array '(3 3) :element-type '(unsigned-byte 32)))))))
3628 (with-test (:name :bug-523612)
3629 (let ((fun (checked-compile
3630 `(lambda (&key toff)
3631 (make-array 3 :element-type 'double-float
3632 :initial-contents
3633 (if toff (list toff 0d0 0d0) (list 0d0 0d0 0d0)))))))
3634 (assert (equalp (vector 0.0d0 0.0d0 0.0d0) (funcall fun :toff nil)))
3635 (assert (equalp (vector 2.3d0 0.0d0 0.0d0) (funcall fun :toff 2.3d0)))))
3637 (with-test (:name :bug-309788)
3638 (let ((fun (checked-compile `(lambda (x)
3639 (declare (optimize speed))
3640 (let ((env nil))
3641 (typep x 'fixnum env))))))
3642 (assert (not (ctu:find-named-callees fun)))))
3644 (with-test (:name :bug-309124)
3645 (let ((fun (checked-compile `(lambda (x)
3646 (declare (integer x))
3647 (declare (optimize speed))
3648 (cond ((typep x 'fixnum)
3649 "hala")
3650 ((typep x 'fixnum)
3651 "buba")
3652 ((typep x 'bignum)
3653 "hip")
3655 "zuz"))))))
3656 (assert (equal (list "hala" "hip")
3657 (sort (ctu:find-code-constants fun :type 'string)
3658 #'string<)))))
3660 (with-test (:name :bug-316078)
3661 (let ((fun (checked-compile
3662 `(lambda (x)
3663 (declare (type (and simple-bit-vector (satisfies bar)) x)
3664 (optimize speed))
3665 (elt x 5)))))
3666 (assert (not (ctu:find-named-callees fun)))
3667 (assert (= 1 (funcall fun #*000001)))
3668 (assert (= 0 (funcall fun #*000010)))))
3670 (with-test (:name :mult-by-one-in-float-acc-zero)
3671 (assert (eql 1.0 (funcall (checked-compile
3672 `(lambda (x)
3673 (declare (optimize (sb-c::float-accuracy 0)))
3674 (* x 1.0)))
3675 1)))
3676 (assert (eql -1.0 (funcall (checked-compile
3677 `(lambda (x)
3678 (declare (optimize (sb-c::float-accuracy 0)))
3679 (* x -1.0)))
3680 1)))
3681 (assert (eql 1.0d0 (funcall (checked-compile
3682 `(lambda (x)
3683 (declare (optimize (sb-c::float-accuracy 0)))
3684 (* x 1.0d0)))
3685 1)))
3686 (assert (eql -1.0d0 (funcall (checked-compile
3687 `(lambda (x)
3688 (declare (optimize (sb-c::float-accuracy 0)))
3689 (* x -1.0d0)))
3690 1))))
3692 (with-test (:name :dotimes-non-integer-counter-value)
3693 (assert-error (dotimes (i 8.6)) type-error))
3695 (with-test (:name :bug-454681)
3696 ;; This used to break due to reference to a dead lambda-var during
3697 ;; inline expansion.
3698 (assert (checked-compile
3699 `(lambda ()
3700 (multiple-value-bind (iterator+977 getter+978)
3701 (does-not-exist-but-does-not-matter)
3702 (flet ((iterator+976 ()
3703 (funcall iterator+977)))
3704 (declare (inline iterator+976))
3705 (let ((iterator+976 #'iterator+976))
3706 (funcall iterator+976)))))
3707 :allow-style-warnings t)))
3709 (with-test (:name :complex-float-local-fun-args)
3710 ;; As of 1.0.27.14, the lambda below failed to compile due to the
3711 ;; compiler attempting to pass unboxed complex floats to Z and the
3712 ;; MOVE-ARG method not expecting the register being used as a
3713 ;; temporary frame pointer. Reported by sykopomp in #lispgames,
3714 ;; reduced test case provided by _3b`.
3715 (checked-compile `(lambda (a)
3716 (labels ((z (b c)
3717 (declare ((complex double-float) b c))
3718 (* b (z b c))))
3719 (loop for i below 10 do
3720 (setf a (z a a)))))))
3722 (with-test (:name :bug-309130)
3723 (flet ((test (form)
3724 (let ((warnings (nth-value
3725 2 (checked-compile form :allow-warnings t))))
3726 (assert (= 1 (length warnings))))))
3727 (test `(lambda () (svref (make-array 8 :adjustable t) 1)))
3728 (test `(lambda (x)
3729 (declare (optimize (debug 0)))
3730 (declare (type vector x))
3731 (list (fill-pointer x) (svref x 1))))
3732 (test `(lambda (x)
3733 (list (vector-push (svref x 0) x))))
3734 (test `(lambda (x)
3735 (list (vector-push-extend (svref x 0) x))))))
3737 (with-test (:name :bug-646796)
3738 (assert (= 42 (funcall (checked-compile
3739 `(lambda ()
3740 (load-time-value (the (values fixnum) 42))))))))
3742 (with-test (:name :bug-654289)
3743 ;; Test that compile-times don't explode when quoted constants
3744 ;; get big.
3745 (labels ((time-n (n)
3746 (gc :full t) ; Let's not confuse the issue with GC
3747 (let* ((tree (make-tree (expt 10 n) nil))
3748 (t0 (get-internal-run-time))
3749 (f (compile nil `(lambda (x) (eq x (quote ,tree)))))
3750 (t1 (get-internal-run-time)))
3751 (assert (funcall f tree))
3752 (- t1 t0)))
3753 (make-tree (n acc)
3754 (cond ((zerop n) acc)
3755 (t (make-tree (1- n) (cons acc acc))))))
3756 (let* ((times (loop for i from 0 upto 4
3757 collect (time-n i)))
3758 (max-small (reduce #'max times :end 3))
3759 (max-big (reduce #'max times :start 3)))
3760 ;; This way is hopefully fairly CPU-performance insensitive.
3761 (unless (> (+ (truncate internal-time-units-per-second 10)
3762 (* 2 max-small))
3763 max-big)
3764 (error "Bad scaling or test? ~S" times)))))
3766 (with-test (:name :bug-309063)
3767 (let ((fun (compile nil `(lambda (x)
3768 (declare (type (integer 0 0) x))
3769 (ash x 100)))))
3770 (assert (zerop (funcall fun 0)))))
3772 (with-test (:name :bug-655872)
3773 (let ((f (compile nil `(lambda (x)
3774 (declare (optimize (safety 3)))
3775 (aref (locally (declare (optimize (safety 0)))
3776 (coerce x '(simple-vector 128)))
3777 60))))
3778 (long (make-array 100 :element-type 'fixnum)))
3779 (dotimes (i 100)
3780 (setf (aref long i) i))
3781 ;; 1. COERCE doesn't check the length in unsafe code.
3782 (assert (eql 60 (funcall f long)))
3783 ;; 2. The compiler doesn't trust the length from COERCE
3784 (assert (eq :caught
3785 (handler-case
3786 (funcall f (list 1 2 3))
3787 (sb-int:invalid-array-index-error (e)
3788 (assert (eql 60 (type-error-datum e)))
3789 (assert (equal '(integer 0 (3)) (type-error-expected-type e)))
3790 :caught))))))
3792 (with-test (:name :bug-655203-regression)
3793 (let ((fun (compile nil
3794 `(LAMBDA (VARIABLE)
3795 (LET ((CONTINUATION
3796 (LAMBDA
3797 (&OPTIONAL DUMMY &REST OTHER)
3798 (DECLARE (IGNORE OTHER))
3799 (PRIN1 DUMMY)
3800 (PRIN1 VARIABLE))))
3801 (FUNCALL CONTINUATION (LIST 1 2)))))))
3802 ;; This used to signal a bogus type-error.
3803 (assert (equal (with-output-to-string (*standard-output*)
3804 (funcall fun t))
3805 "(1 2)T"))))
3807 (with-test (:name :constant-concatenate-compile-time)
3808 (flet ((make-lambda (n)
3809 `(lambda (x)
3810 (declare (optimize (speed 3) (space 0)))
3811 (concatenate 'string x ,(make-string n)))))
3812 (let* ((l0 (make-lambda 1))
3813 (l1 (make-lambda 10))
3814 (l2 (make-lambda 100))
3815 (l3 (make-lambda 1000))
3816 (t0 (get-internal-run-time))
3817 (f0 (checked-compile l0))
3818 (t1 (get-internal-run-time))
3819 (f1 (checked-compile l1))
3820 (t2 (get-internal-run-time))
3821 (f2 (checked-compile l2))
3822 (t3 (get-internal-run-time))
3823 (f3 (checked-compile l3))
3824 (t4 (get-internal-run-time))
3825 (d0 (- t1 t0))
3826 (d1 (- t2 t1))
3827 (d2 (- t3 t2))
3828 (d3 (- t4 t3))
3829 (short-avg (/ (+ d0 d1 d2) 3)))
3830 (assert (and f0 f1 f2 f3))
3831 (assert (< d3 (* 10 short-avg))))))
3833 (with-test (:name :bug-384892)
3834 (assert (equal
3835 ;; The assertion that BOOLEAN becomes (MEMBER T NIL)
3836 ;; is slightly brittle, but the rest of the
3837 ;; assertion is ok.
3838 '(function (fixnum fixnum &key (:k1 (member t nil)))
3839 (values (member t) &optional))
3840 (sb-kernel:%simple-fun-type
3841 (checked-compile `(lambda (x y &key k1)
3842 (declare (fixnum x y))
3843 (declare (boolean k1))
3844 (declare (ignore x y k1))
3845 t))))))
3847 (with-test (:name :bug-309448)
3848 ;; Like all tests trying to verify that something doesn't blow up
3849 ;; compile-times this is bound to be a bit brittle, but at least
3850 ;; here we try to establish a decent baseline.
3851 (labels ((time-it (lambda want &optional times)
3852 (gc :full t) ; let's keep GCs coming from other code out...
3853 (let* ((start (get-internal-run-time))
3854 (iterations 0)
3855 (fun (if times
3856 (loop repeat times
3857 for result = (checked-compile lambda)
3858 finally (return result))
3859 (loop for result = (checked-compile lambda)
3860 do (incf iterations)
3861 until (> (get-internal-run-time) (+ start 10))
3862 finally (return result))))
3863 (end (get-internal-run-time))
3864 (got (funcall fun)))
3865 (unless (eql want got)
3866 (error "wanted ~S, got ~S" want got))
3867 (values (- end start) iterations)))
3868 (test-it (simple result1 complex result2)
3869 (multiple-value-bind (time-simple iterations)
3870 (time-it simple result1)
3871 (assert (>= (* 10 (1+ time-simple))
3872 (time-it complex result2 iterations))))))
3873 ;; This is mostly identical as the next one, but doesn't create
3874 ;; hairy unions of numeric types.
3875 (test-it `(lambda ()
3876 (labels ((bar (baz bim)
3877 (let ((n (+ baz bim)))
3878 (* n (+ n 1) bim))))
3879 (let ((a (bar 1 1))
3880 (b (bar 1 1))
3881 (c (bar 1 1)))
3882 (- (+ a b) c))))
3884 `(lambda ()
3885 (labels ((bar (baz bim)
3886 (let ((n (+ baz bim)))
3887 (* n (+ n 1) bim))))
3888 (let ((a (bar 1 1))
3889 (b (bar 1 5))
3890 (c (bar 1 15)))
3891 (- (+ a b) c))))
3892 -3864)
3893 (test-it `(lambda ()
3894 (labels ((sum-d (n)
3895 (let ((m (truncate 999 n)))
3896 (/ (* n m (1+ m)) 2))))
3897 (- (+ (sum-d 3)
3898 (sum-d 3))
3899 (sum-d 3))))
3900 166833
3901 `(lambda ()
3902 (labels ((sum-d (n)
3903 (let ((m (truncate 999 n)))
3904 (/ (* n m (1+ m)) 2))))
3905 (- (+ (sum-d 3)
3906 (sum-d 5))
3907 (sum-d 15))))
3908 233168)))
3910 (with-test (:name :regression-1.0.44.34)
3911 (checked-compile
3912 `(lambda (z &rest args)
3913 (declare (dynamic-extent args))
3914 (flet ((foo (w v) (list v w)))
3915 (setq z 0)
3916 (flet ((foo ()
3917 (foo z args)))
3918 (declare (sb-int:truly-dynamic-extent #'foo))
3919 (call #'foo nil))))
3920 :allow-style-warnings t))
3922 (with-test (:name :bug-713626)
3923 (let ((f (eval '(constantly 42))))
3924 (assert (= 42 (funcall (checked-compile
3925 `(lambda () (funcall ,f 1 2 3))))))))
3927 (with-test (:name :known-fun-allows-other-keys)
3928 (funcall (checked-compile
3929 `(lambda () (directory "." :allow-other-keys t))))
3930 (funcall (checked-compile
3931 `(lambda () (directory "." :bar t :allow-other-keys t)))))
3933 (with-test (:name :bug-551227)
3934 ;; This function causes constraint analysis to perform a
3935 ;; ref-substitution that alters the A referred to in (G A) at in the
3936 ;; consequent of the IF to refer to be NUMBER, from the
3937 ;; LET-converted inline-expansion of MOD. This leads to attempting
3938 ;; to CLOSE-OVER a variable that simply isn't in scope when it is
3939 ;; referenced.
3940 (checked-compile
3941 `(lambda (a)
3942 (if (let ((s a))
3943 (block :block
3944 (map nil
3945 (lambda (e)
3946 (return-from :block
3947 (f (mod a e))))
3948 s)))
3949 (g a)))
3950 :allow-style-warnings t))
3952 (with-test (:name :funcall-lambda-inlined)
3953 (assert (not
3954 (ctu:find-code-constants
3955 (checked-compile `(lambda (x y)
3956 (+ x (funcall (lambda (z) z) y))))
3957 :type 'function))))
3959 (with-test (:name :bug-720382)
3960 (multiple-value-bind (fun failurep warnings)
3961 (checked-compile `(lambda (b) ((lambda () b) 1)) :allow-warnings t)
3962 (assert failurep)
3963 (assert (= 1 (length warnings)))
3964 (assert-error (funcall fun 0))))
3966 (with-test (:name :multiple-args-to-function)
3967 (let ((form `(flet ((foo (&optional (x 13)) x))
3968 (funcall (function foo 42))))
3969 #+sb-eval (*evaluator-mode* :interpret))
3970 #+sb-eval
3971 (assert (eq :error
3972 (handler-case (eval form)
3973 (error () :error))))
3974 (multiple-value-bind (fun warn fail)
3975 (compile nil `(lambda () ,form))
3976 (assert (and warn fail))
3977 (assert (eq :error
3978 (handler-case (funcall fun)
3979 (error () :error)))))))
3981 ;;; This doesn't test LVAR-FUN-IS directly, but captures it
3982 ;;; pretty accurately anyways.
3983 (with-test (:name :lvar-fun-is :skipped-on :interpreter)
3984 (dolist (fun (list
3985 (lambda (x) (member x x :test #'eq))
3986 (lambda (x) (member x x :test 'eq))
3987 (lambda (x) (member x x :test #.#'eq))))
3988 (assert (equal (list #'sb-kernel:%member-eq)
3989 (ctu:find-named-callees fun))))
3990 (dolist (fun (list
3991 (lambda (x)
3992 (declare (notinline eq))
3993 (member x x :test #'eq))
3994 (lambda (x)
3995 (declare (notinline eq))
3996 (member x x :test 'eq))
3997 (lambda (x)
3998 (declare (notinline eq))
3999 (member x x :test #.#'eq))))
4000 (assert (member #'sb-kernel:%member-test
4001 (ctu:find-named-callees fun)))))
4003 (with-test (:name :delete-to-delq-opt :skipped-on :interpreter)
4004 (dolist (fun (list (lambda (x y)
4005 (declare (list y))
4006 (delete x y :test #'eq))
4007 (lambda (x y)
4008 (declare (fixnum x) (list y))
4009 (delete x y))
4010 (lambda (x y)
4011 (declare (symbol x) (list y))
4012 (delete x y :test #'eql))))
4013 (assert (equal (list #'sb-int:delq)
4014 (ctu:find-named-callees fun)))))
4016 (with-test (:name :bug-767959)
4017 ;; This used to signal an error.
4018 (compile nil `(lambda ()
4019 (declare (optimize sb-c:store-coverage-data))
4020 (assoc
4022 '((:ordinary . ordinary-lambda-list))))))
4024 ;; This test failed formerly because the source transform of TYPEP would be
4025 ;; disabled when storing coverage data, thus giving no semantics to
4026 ;; expressions such as (TYPEP x 'INTEGER). The compiler could therefore not
4027 ;; prove that the else clause of the IF is unreachable - which it must be
4028 ;; since X is asserted to be fixnum. The conflicting requirement on X
4029 ;; that it be acceptable to LENGTH signaled a full warning.
4030 ;; Nobody on sbcl-devel could remember why the source transform was disabled,
4031 ;; but nobody disagreed with undoing the disabling.
4032 (with-test (:name :sb-cover-and-typep)
4033 (multiple-value-bind (fun warnings-p failure-p)
4034 (compile nil '(lambda (x)
4035 (declare (fixnum x) (optimize sb-c:store-coverage-data))
4036 (if (typep x 'integer) x (length x))))
4037 (assert (and fun (not warnings-p) (not failure-p)))))
4039 (with-test (:name :member-on-long-constant-list)
4040 ;; This used to blow stack with a sufficiently long list.
4041 (let ((cycle (list t)))
4042 (nconc cycle cycle)
4043 (compile nil `(lambda (x)
4044 (member x ',cycle)))))
4046 (with-test (:name :bug-722734)
4047 (assert-error
4048 (funcall (compile
4050 '(lambda ()
4051 (eql (make-array 6)
4052 (list unbound-variable-1 unbound-variable-2)))))))
4054 (with-test (:name :bug-771673)
4055 (assert (equal `(the foo bar) (macroexpand `(truly-the foo bar))))
4056 ;; Make sure the compiler doesn't use THE, and check that setf-expansions
4057 ;; work.
4058 (let ((f (compile nil `(lambda (x y)
4059 (setf (truly-the fixnum (car x)) y)))))
4060 (let* ((cell (cons t t)))
4061 (funcall f cell :ok)
4062 (assert (equal '(:ok . t) cell)))))
4064 (with-test (:name (:bug-793771 +))
4065 (let ((f (compile nil `(lambda (x y)
4066 (declare (type (single-float 2.0) x)
4067 (type (single-float (0.0)) y))
4068 (+ x y)))))
4069 (assert (equal `(function ((single-float 2.0) (single-float (0.0)))
4070 (values (single-float 2.0) &optional))
4071 (sb-kernel:%simple-fun-type f)))))
4073 (with-test (:name (:bug-793771 -))
4074 (let ((f (compile nil `(lambda (x y)
4075 (declare (type (single-float * 2.0) x)
4076 (type (single-float (0.0)) y))
4077 (- x y)))))
4078 (assert (equal `(function ((single-float * 2.0) (single-float (0.0)))
4079 (values (single-float * 2.0) &optional))
4080 (sb-kernel:%simple-fun-type f)))))
4082 (with-test (:name (:bug-793771 *))
4083 (let ((f (compile nil `(lambda (x)
4084 (declare (type (single-float (0.0)) x))
4085 (* x 0.1)))))
4086 (assert (equal `(function ((single-float (0.0)))
4087 (values (or (member 0.0) (single-float (0.0))) &optional))
4088 (sb-kernel:%simple-fun-type f)))))
4090 (with-test (:name (:bug-793771 /))
4091 (let ((f (compile nil `(lambda (x)
4092 (declare (type (single-float (0.0)) x))
4093 (/ x 3.0)))))
4094 (assert (equal `(function ((single-float (0.0)))
4095 (values (or (member 0.0) (single-float (0.0))) &optional))
4096 (sb-kernel:%simple-fun-type f)))))
4098 (with-test (:name (:bug-486812 single-float))
4099 (compile nil `(lambda ()
4100 (sb-kernel:make-single-float -1))))
4102 (with-test (:name (:bug-486812 double-float))
4103 (compile nil `(lambda ()
4104 (sb-kernel:make-double-float -1 0))))
4106 (with-test (:name :bug-729765)
4107 (compile nil `(lambda (a b)
4108 (declare ((integer 1 1) a)
4109 ((integer 0 1) b)
4110 (optimize debug))
4111 (lambda () (< b a)))))
4113 ;; Actually tests the assembly of RIP-relative operands to comparison
4114 ;; functions (one of the few x86 instructions that have extra bytes
4115 ;; *after* the mem operand's effective address, resulting in a wrong
4116 ;; offset).
4117 (with-test (:name :cmpps)
4118 (let ((foo (compile nil `(lambda (x)
4119 (= #C(2.0 3.0) (the (complex single-float) x))))))
4120 (assert (funcall foo #C(2.0 3.0)))
4121 (assert (not (funcall foo #C(1.0 2.0))))))
4123 (with-test (:name :cmppd)
4124 (let ((foo (compile nil `(lambda (x)
4125 (= #C(2d0 3d0) (the (complex double-float) x))))))
4126 (assert (funcall foo #C(2d0 3d0)))
4127 (assert (not (funcall foo #C(1d0 2d0))))))
4129 (with-test (:name :lvar-externally-checkable-type-nil)
4130 ;; Used to signal a BUG during compilation.
4131 (let ((fun (compile nil `(lambda (a) (parse-integer "12321321" (the (member :start) a) 1)))))
4132 (multiple-value-bind (i p) (funcall fun :start)
4133 (assert (= 2321321 i))
4134 (assert (= 8 p)))
4135 (multiple-value-bind (i e) (ignore-errors (funcall fun :end))
4136 (assert (not i))
4137 (assert (typep e 'type-error)))))
4139 (with-test (:name :simple-type-error-in-bound-propagation-a)
4140 (compile nil `(lambda (i)
4141 (declare (unsigned-byte i))
4142 (expt 10 (expt 7 (- 2 i))))))
4144 (with-test (:name :simple-type-error-in-bound-propagation-b)
4145 (assert (equal `(FUNCTION (UNSIGNED-BYTE)
4146 (VALUES (SINGLE-FLOAT -1F0 1F0) &OPTIONAL))
4147 (sb-kernel:%simple-fun-type
4148 (compile nil `(lambda (i)
4149 (declare (unsigned-byte i))
4150 (cos (expt 10 (+ 4096 i)))))))))
4152 (with-test (:name :fixed-%more-arg-values)
4153 (let ((fun (compile nil `(lambda (&rest rest)
4154 (declare (optimize (safety 0)))
4155 (apply #'cons rest)))))
4156 (assert (equal '(car . cdr) (funcall fun 'car 'cdr)))))
4158 (with-test (:name :bug-826970)
4159 (let ((fun (compile nil `(lambda (a b c)
4160 (declare (type (member -2 1) b))
4161 (array-in-bounds-p a 4 b c)))))
4162 (assert (funcall fun (make-array '(5 2 2)) 1 1))))
4164 (with-test (:name :bug-826971)
4165 (let* ((foo "foo")
4166 (fun (compile nil `(lambda (p1 p2)
4167 (schar (the (eql ,foo) p1) p2)))))
4168 (assert (eql #\f (funcall fun foo 0)))))
4170 (with-test (:name :bug-738464)
4171 (multiple-value-bind (fun warn fail)
4172 (compile nil `(lambda ()
4173 (flet ((foo () 42))
4174 (declare (ftype non-function-type foo))
4175 (foo))))
4176 (assert (eql 42 (funcall fun)))
4177 (assert (and warn (not fail)))))
4179 (with-test (:name :bug-832005)
4180 (let ((fun (compile nil `(lambda (x)
4181 (declare (type (complex single-float) x))
4182 (+ #C(0.0 1.0) x)))))
4183 (assert (= (funcall fun #C(1.0 2.0))
4184 #C(1.0 3.0)))))
4186 ;; A refactoring 1.0.12.18 caused lossy computation of primitive
4187 ;; types for member types.
4188 (with-test (:name :member-type-primitive-type)
4189 (let ((fun (compile nil `(lambda (p1 p2 p3)
4190 (if p1
4191 (the (member #c(1.2d0 1d0)) p2)
4192 (the (eql #c(1.0 1.0)) p3))))))
4193 (assert (eql (funcall fun 1 #c(1.2d0 1d0) #c(1.0 1.0))
4194 #c(1.2d0 1.0d0)))))
4196 ;; Fall-through jump elimination made control flow fall through to trampolines.
4197 ;; Reported by Eric Marsden on sbcl-devel@ 2011.10.26, with a test case
4198 ;; reproduced below (triggered a corruption warning and a memory fault).
4199 (with-test (:name :bug-883500)
4200 (funcall (compile nil `(lambda (a)
4201 (declare (type (integer -50 50) a))
4202 (declare (optimize (speed 0)))
4203 (mod (mod a (min -5 a)) 5)))
4206 ;; Test for literals too large for the ISA (e.g. (SIGNED-BYTE 13) on SPARC).
4207 #+sb-unicode
4208 (with-test (:name :bug-883519)
4209 (compile nil `(lambda (x)
4210 (declare (type character x))
4211 (eql x #\U0010FFFF))))
4213 ;; Wide fixnum platforms had buggy address computation in atomic-incf/aref
4214 (with-test (:name :bug-887220)
4215 (let ((incfer (compile
4217 `(lambda (vector index)
4218 (declare (type (simple-array sb-ext:word (4))
4219 vector)
4220 (type (mod 4) index))
4221 (sb-ext:atomic-incf (aref vector index) 1)
4222 vector))))
4223 (assert (equalp (funcall incfer
4224 (make-array 4 :element-type 'sb-ext:word
4225 :initial-element 0)
4227 #(0 1 0 0)))))
4229 (with-test (:name :catch-interferes-with-debug-names)
4230 (let ((fun (funcall
4231 (compile nil
4232 `(lambda ()
4233 (catch 'out
4234 (flet ((foo ()
4235 (throw 'out (lambda () t))))
4236 (foo))))))))
4237 (assert (equal '(lambda () :in foo) (sb-kernel:%fun-name fun)))))
4239 (with-test (:name :interval-div-signed-zero)
4240 (let ((fun (compile nil
4241 `(Lambda (a)
4242 (declare (type (member 0 -272413371076) a))
4243 (ffloor (the number a) -63243.127451934015d0)))))
4244 (multiple-value-bind (q r) (funcall fun 0)
4245 (assert (eql -0d0 q))
4246 (assert (eql 0d0 r)))))
4248 (with-test (:name :non-constant-keyword-typecheck)
4249 (let ((fun (compile nil
4250 `(lambda (p1 p3 p4)
4251 (declare (type keyword p3))
4252 (tree-equal p1 (cons 1 2) (the (member :test) p3) p4)))))
4253 (assert (funcall fun (cons 1.0 2.0) :test '=))))
4255 (with-test (:name :truncate-wild-values)
4256 (multiple-value-bind (q r)
4257 (handler-bind ((warning #'error))
4258 (let ((sb-c::*check-consistency* t))
4259 (funcall (compile nil
4260 `(lambda (a)
4261 (declare (type (member 1d0 2d0) a))
4262 (block return-value-tag
4263 (funcall
4264 (the function
4265 (catch 'debug-catch-tag
4266 (return-from return-value-tag
4267 (progn (truncate a)))))))))
4268 2d0)))
4269 (assert (eql 2 q))
4270 (assert (eql 0d0 r))))
4272 (with-test (:name :boxed-fp-constant-for-full-call)
4273 (let ((fun (compile nil
4274 `(lambda (x)
4275 (declare (double-float x))
4276 (unknown-fun 1.0d0 (+ 1.0d0 x))))))
4277 (assert (equal '(1.0d0) (ctu:find-code-constants fun :type 'double-float)))))
4279 (with-test (:name :only-one-boxed-constant-for-multiple-uses)
4280 (let* ((big (1+ most-positive-fixnum))
4281 (fun (compile nil
4282 `(lambda (x)
4283 (unknown-fun ,big (+ ,big x))))))
4284 (assert (= 1 (length (ctu:find-code-constants fun :type `(eql ,big)))))))
4286 (with-test (:name :fixnum+float-coerces-fixnum
4287 :skipped-on :x86)
4288 (let ((fun (compile nil
4289 `(lambda (x y)
4290 (declare (fixnum x)
4291 (single-float y))
4292 (+ x y)))))
4293 (assert (not (ctu:find-named-callees fun)))
4294 (assert (not (search "GENERIC"
4295 (with-output-to-string (s)
4296 (disassemble fun :stream s)))))))
4298 (with-test (:name :bug-803508)
4299 (compile nil `(lambda ()
4300 (print
4301 (lambda (bar)
4302 (declare (dynamic-extent bar))
4303 (foo bar))))))
4305 (with-test (:name :bug-803508-b)
4306 (compile nil `(lambda ()
4307 (list
4308 (lambda (bar)
4309 (declare (dynamic-extent bar))
4310 (foo bar))))))
4312 (with-test (:name :bug-803508-c)
4313 (compile nil `(lambda ()
4314 (list
4315 (lambda (bar &optional quux)
4316 (declare (dynamic-extent bar quux))
4317 (foo bar quux))))))
4319 (with-test (:name :cprop-with-constant-but-assigned-to-closure-variable)
4320 (compile nil `(lambda (b c d)
4321 (declare (type (integer -20545789 207590862) c))
4322 (declare (type (integer -1 -1) d))
4323 (let ((i (unwind-protect 32 (shiftf d -1))))
4324 (or (if (= d c) 2 (= 3 b)) 4)))))
4326 (with-test (:name :bug-913232
4327 :fails-on :interpreter) ; no idea why it fails randomly
4328 (compile nil `(lambda (x)
4329 (declare (optimize speed)
4330 (type (or (and (or (integer -100 -50)
4331 (integer 100 200)) (satisfies foo))
4332 (and (or (integer 0 10) (integer 20 30)) a)) x))
4334 (compile nil `(lambda (x)
4335 (declare (optimize speed)
4336 (type (and fixnum a) x))
4337 x)))
4339 (with-test (:name :bug-959687)
4340 (multiple-value-bind (fun warn fail)
4341 (compile nil `(lambda (x)
4342 (case x
4344 :its-a-t)
4345 (otherwise
4346 :somethign-else))))
4347 (assert (and warn fail))
4348 (assert (not (ignore-errors (funcall fun t)))))
4349 (multiple-value-bind (fun warn fail)
4350 (compile nil `(lambda (x)
4351 (case x
4352 (otherwise
4353 :its-an-otherwise)
4355 :somethign-else))))
4356 (assert (and warn fail))
4357 (assert (not (ignore-errors (funcall fun t))))))
4359 (with-test (:name :bug-924276)
4360 (assert (eq :style-warning
4361 (handler-case
4362 (compile nil `(lambda (a)
4363 (cons a (symbol-macrolet ((b 1))
4364 (declare (ignorable a))
4365 :c))))
4366 (style-warning ()
4367 :style-warning)))))
4369 (with-test (:name :bug-974406)
4370 (let ((fun32 (compile nil `(lambda (x)
4371 (declare (optimize speed (safety 0)))
4372 (declare (type (integer 53 86) x))
4373 (logand (+ x 1032791128) 11007078467))))
4374 (fun64 (compile nil `(lambda (x)
4375 (declare (optimize speed (safety 0)))
4376 (declare (type (integer 53 86) x))
4377 (logand (+ x 1152921504606846975)
4378 38046409652025950207)))))
4379 (assert (= (funcall fun32 61) 268574721))
4380 (assert (= (funcall fun64 61) 60)))
4381 (let (result)
4382 (do ((width 5 (1+ width)))
4383 ((= width 130))
4384 (dotimes (extra 4)
4385 (let ((fun (compile nil `(lambda (x)
4386 (declare (optimize speed (safety 0)))
4387 (declare (type (integer 1 16) x))
4388 (logand
4389 (+ x ,(1- (ash 1 width)))
4390 ,(logior (ash 1 (+ width 1 extra))
4391 (1- (ash 1 width))))))))
4392 (unless (= (funcall fun 16) (logand 15 (1- (ash 1 width))))
4393 (push (cons width extra) result)))))
4394 (assert (null result))))
4396 ;; On x86-64 MOVE-IMMEDIATE of fixnum values into memory either directly
4397 ;; uses a MOV into memory or goes through a temporary register if the
4398 ;; value is larger than a certain number of bits. Check that it respects
4399 ;; the limits of immediate arguments to the MOV instruction (if not, the
4400 ;; assembler will fail an assertion) and doesn't have sign-extension
4401 ;; problems. (The test passes fixnum constants through the MOVE VOP
4402 ;; which calls MOVE-IMMEDIATE.)
4403 (with-test (:name :constant-fixnum-move)
4404 (let ((f (compile nil `(lambda (g)
4405 (funcall g
4406 ;; The first three args are
4407 ;; uninteresting as they are
4408 ;; passed in registers.
4409 1 2 3
4410 ,@(loop for i from 27 to 32
4411 collect (expt 2 i)))))))
4412 (assert (every #'plusp (funcall f #'list)))))
4414 (with-test (:name (:malformed-ignore :lp-1000239) :skipped-on :interpreter)
4415 (assert-error
4416 (eval '(lambda () (declare (ignore (function . a)))))
4417 sb-int:simple-program-error)
4418 (assert-error
4419 (eval '(lambda () (declare (ignore (function a b)))))
4420 sb-int:simple-program-error)
4421 (assert-error
4422 (eval '(lambda () (declare (ignore (function)))))
4423 sb-int:simple-program-error)
4424 (assert-error
4425 (eval '(lambda () (declare (ignore (a)))))
4426 sb-int:simple-program-error)
4427 (assert-error
4428 (eval '(lambda () (declare (ignorable (a b)))))
4429 sb-int:simple-program-error))
4431 (with-test (:name :malformed-type-declaraions)
4432 (compile nil '(lambda (a) (declare (type (integer 1 2 . 3) a)))))
4434 (with-test (:name :compiled-program-error-escaped-source)
4435 (assert
4436 (handler-case
4437 (funcall (compile nil `(lambda () (lambda ("foo")))))
4438 (sb-int:compiled-program-error (e)
4439 (let ((source (read-from-string (sb-kernel::program-error-source e))))
4440 (equal source '#'(lambda ("foo"))))))))
4442 (with-test (:name :escape-analysis-for-nlxs :skipped-on :interpreter)
4443 (flet ((test (check lambda &rest args)
4444 (let* ((cell-note nil)
4445 (fun (handler-bind ((compiler-note
4446 (lambda (note)
4447 (when (search
4448 "Allocating a value-cell at runtime for"
4449 (princ-to-string note))
4450 (setf cell-note t)))))
4451 (compile nil lambda))))
4452 (assert (eql check cell-note))
4453 (if check
4454 (assert
4455 (eq :ok
4456 (handler-case
4457 (dolist (arg args nil)
4458 (setf fun (funcall fun arg)))
4459 (sb-int:simple-control-error (e)
4460 (when (equal
4461 (simple-condition-format-control e)
4462 "attempt to RETURN-FROM a block or GO to a tag that no longer exists")
4463 :ok)))))
4464 (ctu:assert-no-consing (apply fun args))))))
4465 (test nil `(lambda (x)
4466 (declare (optimize speed))
4467 (block out
4468 (flet ((ex () (return-from out 'out!)))
4469 (typecase x
4470 (cons (or (car x) (ex)))
4471 (t (ex)))))) :foo)
4472 (test t `(lambda (x)
4473 (declare (optimize speed))
4474 (funcall
4475 (block nasty
4476 (flet ((oops () (return-from nasty t)))
4477 #'oops)))) t)
4478 (test t `(lambda (r)
4479 (declare (optimize speed))
4480 (block out
4481 (flet ((ex () (return-from out r)))
4482 (lambda (x)
4483 (typecase x
4484 (cons (or (car x) (ex)))
4485 (t (ex))))))) t t)
4486 (test t `(lambda (x)
4487 (declare (optimize speed))
4488 (flet ((eh (x)
4489 (flet ((meh () (return-from eh 'meh)))
4490 (lambda ()
4491 (typecase x
4492 (cons (or (car x) (meh)))
4493 (t (meh)))))))
4494 (funcall (eh x)))) t t)))
4496 (with-test (:name (:bug-1050768 :symptom))
4497 ;; Used to signal an error.
4498 (compile nil
4499 `(lambda (string position)
4500 (char string position)
4501 (array-in-bounds-p string (1+ position)))))
4503 (with-test (:name (:bug-1050768 :cause))
4504 (let ((types `((string string)
4505 ((or (simple-array character 24) (vector t 24))
4506 (or (simple-array character 24) (vector t))))))
4507 (dolist (pair types)
4508 (destructuring-bind (orig conservative) pair
4509 (assert sb-c::(type= (specifier-type cl-user::conservative)
4510 (conservative-type (specifier-type cl-user::orig))))))))
4512 (with-test (:name (:smodular64 :wrong-width))
4513 (let ((fun (compile nil
4514 '(lambda (x)
4515 (declare (type (signed-byte 64) x))
4516 (sb-c::mask-signed-field 64 (- x 7033717698976965573))))))
4517 (assert (= (funcall fun 10038) -7033717698976955535))))
4519 (with-test (:name (:smodular32 :wrong-width))
4520 (let ((fun (compile nil '(lambda (x)
4521 (declare (type (signed-byte 31) x))
4522 (sb-c::mask-signed-field 31 (- x 1055131947))))))
4523 (assert (= (funcall fun 10038) -1055121909))))
4525 (with-test (:name :first-open-coded)
4526 (let ((fun (compile nil `(lambda (x) (first x)))))
4527 (assert (not (ctu:find-named-callees fun)))))
4529 (with-test (:name :second-open-coded)
4530 (let ((fun (compile nil `(lambda (x) (second x)))))
4531 (assert (not (ctu:find-named-callees fun)))))
4533 (with-test (:name :svref-of-symbol-macro)
4534 (compile nil `(lambda (x)
4535 (symbol-macrolet ((sv x))
4536 (values (svref sv 0) (setf (svref sv 0) 99))))))
4538 ;; The compiler used to update the receiving LVAR's type too
4539 ;; aggressively when converting a large constant to a smaller
4540 ;; (potentially signed) one, causing other branches to be
4541 ;; inferred as dead.
4542 (with-test (:name :modular-cut-constant-to-width)
4543 (let ((test (compile nil
4544 `(lambda (x)
4545 (logand 254
4546 (case x
4547 ((3) x)
4548 ((2 2 0 -2 -1 2) 9223372036854775803)
4549 (t 358458651)))))))
4550 (assert (= (funcall test -10470605025) 26))))
4552 (with-test (:name :append-type-derivation)
4553 (let ((test-cases
4554 '((lambda () (append 10)) (integer 10 10)
4555 (lambda () (append nil 10)) (integer 10 10)
4556 (lambda (x) (append x 10)) (or (integer 10 10) cons)
4557 (lambda (x) (append x (cons 1 2))) cons
4558 (lambda (x y) (append x (cons 1 2) y)) cons
4559 (lambda (x y) (nconc x (the list y) x)) t
4560 (lambda (x y) (nconc (the atom x) y)) t
4561 (lambda (x y) (nconc (the (or null (eql 10)) x) y)) t
4562 (lambda (x y) (nconc (the (or cons vector) x) y)) cons
4563 (lambda (x y) (nconc (the sequence x) y)) t
4564 (lambda (x y) (print (length y)) (append x y)) sequence
4565 (lambda (x y) (print (length y)) (append x y)) sequence
4566 (lambda (x y) (append (the (member (a) (b)) x) y)) cons
4567 (lambda (x y) (append (the (member (a) (b) c) x) y)) cons
4568 (lambda (x y) (append (the (member (a) (b) nil) x) y)) t)))
4569 (loop for (function result-type) on test-cases by #'cddr
4570 do (assert (sb-kernel:type= (sb-kernel:specifier-type
4571 (car (cdaddr (sb-kernel:%simple-fun-type
4572 (compile nil function)))))
4573 (sb-kernel:specifier-type result-type))))))
4575 (with-test (:name :bug-504121)
4576 (compile nil `(lambda (s)
4577 (let ((p1 #'upper-case-p))
4578 (funcall
4579 (lambda (g)
4580 (funcall p1 g))))
4581 (let ((p2 #'(lambda (char) (upper-case-p char))))
4582 (funcall p2 s)))))
4584 (with-test (:name (:bug-504121 :optional-missing))
4585 (compile nil `(lambda (s)
4586 (let ((p1 #'upper-case-p))
4587 (funcall
4588 (lambda (g &optional x)
4589 (funcall p1 g))))
4590 (let ((p2 #'(lambda (char) (upper-case-p char))))
4591 (funcall p2 s)))))
4593 (with-test (:name (:bug-504121 :optional-superfluous))
4594 (compile nil `(lambda (s)
4595 (let ((p1 #'upper-case-p))
4596 (funcall
4597 (lambda (g &optional x)
4598 (funcall p1 g))
4599 #\1 2 3))
4600 (let ((p2 #'(lambda (char) (upper-case-p char))))
4601 (funcall p2 s)))))
4603 (with-test (:name (:bug-504121 :key-odd))
4604 (compile nil `(lambda (s)
4605 (let ((p1 #'upper-case-p))
4606 (funcall
4607 (lambda (g &key x)
4608 (funcall p1 g))
4609 #\1 :x))
4610 (let ((p2 #'(lambda (char) (upper-case-p char))))
4611 (funcall p2 s)))))
4613 (with-test (:name (:bug-504121 :key-unknown))
4614 (compile nil `(lambda (s)
4615 (let ((p1 #'upper-case-p))
4616 (funcall
4617 (lambda (g &key x)
4618 (funcall p1 g))
4619 #\1 :y 2))
4620 (let ((p2 #'(lambda (char) (upper-case-p char))))
4621 (funcall p2 s)))))
4623 (with-test (:name :bug-1181684)
4624 (compile nil `(lambda ()
4625 (let ((hash #xD13CCD13))
4626 (setf hash (logand most-positive-word
4627 (ash hash 5)))))))
4629 (with-test (:name (:local-&optional-recursive-inline :bug-1180992))
4630 (compile nil
4631 `(lambda ()
4632 (labels ((called (&optional a))
4633 (recursed (&optional b)
4634 (called)
4635 (recursed)))
4636 (declare (inline recursed called))
4637 (recursed)))))
4639 (with-test (:name :constant-fold-logtest)
4640 (assert (equal (sb-kernel:%simple-fun-type
4641 (compile nil `(lambda (x)
4642 (declare (type (mod 1024) x)
4643 (optimize speed))
4644 (logtest x 2048))))
4645 '(function ((unsigned-byte 10)) (values null &optional)))))
4647 ;; type mismatches on LVARs with multiple potential sources used to
4648 ;; be reported as mismatches with the value NIL. Make sure we get
4649 ;; a warning, but that it doesn't complain about a constant NIL ...
4650 ;; of type FIXNUM.
4651 (with-test (:name (:multiple-use-lvar-interpreted-as-NIL :cast))
4652 (block nil
4653 (handler-bind ((sb-int:type-warning
4654 (lambda (c)
4655 (assert
4656 (not (search "Constant "
4657 (simple-condition-format-control
4658 c))))
4659 (return))))
4660 (compile nil `(lambda (x y z)
4661 (declare (type fixnum y z))
4662 (aref (if x y z) 0))))
4663 (error "Where's my warning?")))
4665 (with-test (:name (:multiple-use-lvar-interpreted-as-NIL catch))
4666 (block nil
4667 (handler-bind ((style-warning
4668 (lambda (c)
4669 (assert
4670 (not (position
4672 (simple-condition-format-arguments c))))
4673 (return))))
4674 (compile nil `(lambda (x y z f)
4675 (declare (type fixnum y z))
4676 (catch (if x y z) (funcall f)))))
4677 (error "Where's my style-warning?")))
4679 ;; Smoke test for rightward shifts
4680 (with-test (:name (:ash/right-signed))
4681 (let* ((f (compile nil `(lambda (x y)
4682 (declare (type (mod ,(* 2 sb-vm:n-word-bits)) y)
4683 (type sb-vm:signed-word x)
4684 (optimize speed))
4685 (ash x (- y)))))
4686 (max (ash most-positive-word -1))
4687 (min (- -1 max)))
4688 (flet ((test (x y)
4689 (assert (= (ash x (- y))
4690 (funcall f x y)))))
4691 (dotimes (x 32)
4692 (dotimes (y (* 2 sb-vm:n-word-bits))
4693 (test x y)
4694 (test (- x) y)
4695 (test (- max x) y)
4696 (test (+ min x) y))))))
4698 (with-test (:name (:ash/right-unsigned))
4699 (let ((f (compile nil `(lambda (x y)
4700 (declare (type (mod ,(* 2 sb-vm:n-word-bits)) y)
4701 (type word x)
4702 (optimize speed))
4703 (ash x (- y)))))
4704 (max most-positive-word))
4705 (flet ((test (x y)
4706 (assert (= (ash x (- y))
4707 (funcall f x y)))))
4708 (dotimes (x 32)
4709 (dotimes (y (* 2 sb-vm:n-word-bits))
4710 (test x y)
4711 (test (- max x) y))))))
4713 (with-test (:name (:ash/right-fixnum))
4714 (let ((f (compile nil `(lambda (x y)
4715 (declare (type (mod ,(* 2 sb-vm:n-word-bits)) y)
4716 (type fixnum x)
4717 (optimize speed))
4718 (ash x (- y))))))
4719 (flet ((test (x y)
4720 (assert (= (ash x (- y))
4721 (funcall f x y)))))
4722 (dotimes (x 32)
4723 (dotimes (y (* 2 sb-vm:n-word-bits))
4724 (test x y)
4725 (test (- x) y)
4726 (test (- most-positive-fixnum x) y)
4727 (test (+ most-negative-fixnum x) y))))))
4729 ;; expected failure
4730 (with-test (:name :fold-index-addressing-positive-offset)
4731 (let ((f (compile nil `(lambda (i)
4732 (if (typep i '(integer -31 31))
4733 (aref #. (make-array 63) (+ i 31))
4734 (error "foo"))))))
4735 (funcall f -31)))
4737 ;; 5d3a728 broke something like this in CL-PPCRE
4738 (with-test (:name :fold-index-addressing-potentially-negative-index)
4739 (compile nil `(lambda (index vector)
4740 (declare (optimize speed (safety 0))
4741 ((simple-array character (*)) vector)
4742 ((unsigned-byte 24) index))
4743 (aref vector (1+ (mod index (1- (length vector))))))))
4745 (with-test (:name :constant-fold-ash/right-fixnum)
4746 (compile nil `(lambda (a b)
4747 (declare (type fixnum a)
4748 (type (integer * -84) b))
4749 (ash a b))))
4751 (with-test (:name :constant-fold-ash/right-word)
4752 (compile nil `(lambda (a b)
4753 (declare (type word a)
4754 (type (integer * -84) b))
4755 (ash a b))))
4757 (with-test (:name :nconc-derive-type)
4758 (let ((function (compile nil `(lambda (x y)
4759 (declare (type (or cons fixnum) x))
4760 (nconc x y)))))
4761 (assert (equal (sb-kernel:%simple-fun-type function)
4762 '(function ((or cons fixnum) t) (values cons &optional))))))
4764 ;; make sure that all data-vector-ref-with-offset VOPs are either
4765 ;; specialised on a 0 offset or accept signed indices
4766 (with-test (:name :data-vector-ref-with-offset-signed-index)
4767 (let ((dvr (find-symbol "DATA-VECTOR-REF-WITH-OFFSET" "SB-KERNEL")))
4768 (when dvr
4769 (assert
4770 (null
4771 (loop for info in (sb-c::fun-info-templates
4772 (sb-c::fun-info-or-lose dvr))
4773 for (nil second-arg third-arg) = (sb-c::vop-info-arg-types info)
4774 unless (or (typep second-arg '(cons (eql :constant)))
4775 (find '(integer 0 0) third-arg :test 'equal)
4776 (equal second-arg
4777 `(:or ,(sb-c::primitive-type-or-lose
4778 'sb-vm::positive-fixnum)
4779 ,(sb-c::primitive-type-or-lose
4780 'fixnum))))
4781 collect info))))))
4783 (with-test (:name :data-vector-set-with-offset-signed-index)
4784 (let ((dvr (find-symbol "DATA-VECTOR-SET-WITH-OFFSET" "SB-KERNEL")))
4785 (when dvr
4786 (assert
4787 (null
4788 (loop for info in (sb-c::fun-info-templates
4789 (sb-c::fun-info-or-lose dvr))
4790 for (nil second-arg third-arg) = (sb-c::vop-info-arg-types info)
4791 unless (or (typep second-arg '(cons (eql :constant)))
4792 (find '(integer 0 0) third-arg :test 'equal)
4793 (equal second-arg
4794 `(:or ,(sb-c::primitive-type-or-lose
4795 'sb-vm::positive-fixnum)
4796 ,(sb-c::primitive-type-or-lose
4797 'fixnum))))
4798 collect info))))))
4800 (with-test (:name :maybe-inline-ref-to-dead-lambda)
4801 (compile nil `(lambda (string)
4802 (declare (optimize speed (space 0)))
4803 (cond ((every #'digit-char-p string)
4804 nil)
4805 ((some (lambda (c)
4806 (digit-char-p c))
4807 string))))))
4809 ;; the x87 backend used to sometimes signal FP errors during boxing,
4810 ;; because converting between double and single float values was a
4811 ;; noop (fixed), and no doubt many remaining issues. We now store
4812 ;; the value outside pseudo-atomic, so any SIGFPE should be handled
4813 ;; corrrectly.
4815 ;; When it fails, this test lands into ldb.
4816 (with-test (:name :no-overflow-during-allocation)
4817 (handler-case (eval '(cosh 90))
4818 (floating-point-overflow ()
4819 t)))
4821 ;; unbounded integer types could break integer arithmetic.
4822 (with-test (:name :bug-1199127)
4823 (compile nil `(lambda (b)
4824 (declare (type (integer -1225923945345 -832450738898) b))
4825 (declare (optimize (speed 3) (space 3) (safety 2)
4826 (debug 0) (compilation-speed 1)))
4827 (loop for lv1 below 3
4828 sum (logorc2
4829 (if (>= 0 lv1)
4830 (ash b (min 25 lv1))
4832 -2)))))
4834 ;; non-trivial modular arithmetic operations would evaluate to wider results
4835 ;; than expected, and never be cut to the right final bitwidth.
4836 (with-test (:name :bug-1199428-1)
4837 (let ((f1 (compile nil `(lambda (a c)
4838 (declare (type (integer -2 1217810089) a))
4839 (declare (type (integer -6895591104928 -561736648588) c))
4840 (declare (optimize (speed 2) (space 0) (safety 2) (debug 0)
4841 (compilation-speed 3)))
4842 (logandc1 (gcd c)
4843 (+ (- a c)
4844 (loop for lv2 below 1 count t))))))
4845 (f2 (compile nil `(lambda (a c)
4846 (declare (notinline - + gcd logandc1))
4847 (declare (optimize (speed 1) (space 1) (safety 0) (debug 1)
4848 (compilation-speed 3)))
4849 (logandc1 (gcd c)
4850 (+ (- a c)
4851 (loop for lv2 below 1 count t)))))))
4852 (let ((a 530436387)
4853 (c -4890629672277))
4854 (assert (eql (funcall f1 a c)
4855 (funcall f2 a c))))))
4857 (with-test (:name :bug-1199428-2)
4858 (let ((f1 (compile nil `(lambda (a b)
4859 (declare (type (integer -1869232508 -6939151) a))
4860 (declare (type (integer -11466348357 -2645644006) b))
4861 (declare (optimize (speed 1) (space 0) (safety 2) (debug 2)
4862 (compilation-speed 2)))
4863 (logand (lognand a -6) (* b -502823994)))))
4864 (f2 (compile nil `(lambda (a b)
4865 (logand (lognand a -6) (* b -502823994))))))
4866 (let ((a -1491588365)
4867 (b -3745511761))
4868 (assert (eql (funcall f1 a b)
4869 (funcall f2 a b))))))
4871 ;; win32 is very specific about the order in which catch blocks
4872 ;; must be allocated on the stack
4873 (with-test (:name :bug-1072739)
4874 (let ((f (compile nil
4875 `(lambda ()
4876 (STRING=
4877 (LET ((% 23))
4878 (WITH-OUTPUT-TO-STRING (G13908)
4879 (PRINC
4880 (LET ()
4881 (DECLARE (OPTIMIZE (SB-EXT:INHIBIT-WARNINGS 3)))
4882 (HANDLER-CASE
4883 (WITH-OUTPUT-TO-STRING (G13909) (PRINC %A%B% G13909) G13909)
4884 (UNBOUND-VARIABLE NIL
4885 (HANDLER-CASE
4886 (WITH-OUTPUT-TO-STRING (G13914)
4887 (PRINC %A%B% G13914)
4888 (PRINC "" G13914)
4889 G13914)
4890 (UNBOUND-VARIABLE NIL
4891 (HANDLER-CASE
4892 (WITH-OUTPUT-TO-STRING (G13913)
4893 (PRINC %A%B G13913)
4894 (PRINC "%" G13913)
4895 G13913)
4896 (UNBOUND-VARIABLE NIL
4897 (HANDLER-CASE
4898 (WITH-OUTPUT-TO-STRING (G13912)
4899 (PRINC %A% G13912)
4900 (PRINC "b%" G13912)
4901 G13912)
4902 (UNBOUND-VARIABLE NIL
4903 (HANDLER-CASE
4904 (WITH-OUTPUT-TO-STRING (G13911)
4905 (PRINC %A G13911)
4906 (PRINC "%b%" G13911)
4907 G13911)
4908 (UNBOUND-VARIABLE NIL
4909 (HANDLER-CASE
4910 (WITH-OUTPUT-TO-STRING (G13910)
4911 (PRINC % G13910)
4912 (PRINC "a%b%" G13910)
4913 G13910)
4914 (UNBOUND-VARIABLE NIL
4915 (ERROR "Interpolation error in \"%a%b%\"
4916 "))))))))))))))
4917 G13908)))
4918 "23a%b%")))))
4919 (assert (funcall f))))
4921 (with-test (:name :equal-equalp-transforms)
4922 (let* ((s "foo")
4923 (bit-vector #*11001100)
4924 (values `(nil 1 2 "test"
4925 ;; Floats duplicated here to ensure we get newly created instances
4926 (read-from-string "1.1") (read-from-string "1.2d0")
4927 (read-from-string "1.1") (read-from-string "1.2d0")
4928 1.1 1.2d0 '("foo" "bar" "test")
4929 #(1 2 3 4) #*101010 (make-broadcast-stream) #p"/tmp/file"
4930 ,s (copy-seq ,s) ,bit-vector (copy-seq ,bit-vector)
4931 ,(make-hash-table) #\a #\b #\A #\C
4932 ,(make-random-state) 1/2 2/3)))
4933 ;; Test all permutations of different types
4934 (assert
4935 (loop
4936 for x in values
4937 always (loop
4938 for y in values
4939 always
4940 (and (eq (funcall (compile nil `(lambda (x y)
4941 (equal (the ,(type-of x) x)
4942 (the ,(type-of y) y))))
4943 x y)
4944 (equal x y))
4945 (eq (funcall (compile nil `(lambda (x y)
4946 (equalp (the ,(type-of x) x)
4947 (the ,(type-of y) y))))
4948 x y)
4949 (equalp x y))))))
4950 (assert
4951 (funcall (compile
4953 `(lambda (x y)
4954 (equal (the (cons (or simple-bit-vector simple-base-string))
4956 (the (cons (or (and bit-vector (not simple-array))
4957 (simple-array character (*))))
4958 y))))
4959 (list (string 'list))
4960 (list "LIST")))
4961 (assert
4962 (funcall (compile
4964 `(lambda (x y)
4965 (equalp (the (cons (or simple-bit-vector simple-base-string))
4967 (the (cons (or (and bit-vector (not simple-array))
4968 (simple-array character (*))))
4969 y))))
4970 (list (string 'list))
4971 (list "lisT")))))
4973 (with-test (:name (restart-case optimize speed compiler-note)
4974 ;; Cannot-DX note crashes test driver unless we have this:
4975 :skipped-on '(not :stack-allocatable-fixed-objects))
4976 (handler-bind ((compiler-note #'error))
4977 (compile nil '(lambda ()
4978 (declare (optimize speed))
4979 (restart-case () (c ()))))
4980 (compile nil '(lambda ()
4981 (declare (optimize speed))
4982 (let (x)
4983 (restart-case (setf x (car (compute-restarts)))
4984 (c ()))
4985 x)))))
4987 (with-test (:name :copy-more-arg
4988 :fails-on '(not (or :x86 :x86-64 :arm :arm64)))
4989 ;; copy-more-arg might not copy in the right direction
4990 ;; when there are more fixed args than stack frame slots,
4991 ;; and thus end up splatting a single argument everywhere.
4992 ;; Failing platforms still start their stack frames at 8 slots, so
4993 ;; this is less likely to happen.
4994 (let ((limit 33))
4995 (labels ((iota (n)
4996 (loop for i below n collect i))
4997 (test-function (function skip)
4998 ;; function should just be (subseq x skip)
4999 (loop for i from skip below (+ skip limit) do
5000 (let* ((values (iota i))
5001 (f (apply function values))
5002 (subseq (subseq values skip)))
5003 (assert (equal f subseq)))))
5004 (make-function (n)
5005 (let ((gensyms (loop for i below n collect (gensym))))
5006 (compile nil `(lambda (,@gensyms &rest rest)
5007 (declare (ignore ,@gensyms))
5008 rest)))))
5009 (dotimes (i limit)
5010 (test-function (make-function i) i)))))
5012 (with-test (:name :apply-aref)
5013 (flet ((test (form)
5014 (let (warning)
5015 (handler-bind ((warning (lambda (c) (setf warning c))))
5016 (compile nil `(lambda (x y) (setf (apply #'sbit x y) 10))))
5017 (assert (not warning)))))
5018 (test `(lambda (x y) (setf (apply #'aref x y) 21)))
5019 (test `(lambda (x y) (setf (apply #'bit x y) 1)))
5020 (test `(lambda (x y) (setf (apply #'sbit x y) 0)))))
5022 (with-test (:name :warn-on-the-values-constant)
5023 (multiple-value-bind (fun warnings-p failure-p)
5024 (compile nil
5025 ;; The compiler used to elide this test without
5026 ;; noting that the type demands multiple values.
5027 '(lambda () (the (values fixnum fixnum) 1)))
5028 (declare (ignore warnings-p))
5029 (assert (functionp fun))
5030 (assert failure-p)))
5032 ;; quantifiers shouldn't cons themselves.
5033 (with-test (:name :quantifiers-no-consing
5034 :skipped-on '(or :interpreter
5035 (not :stack-allocatable-closures)))
5036 (let ((constantly-t (lambda (x) x t))
5037 (constantly-nil (lambda (x) x nil))
5038 (list (make-list 1000 :initial-element nil))
5039 (vector (make-array 1000 :initial-element nil)))
5040 (macrolet ((test (quantifier)
5041 (let ((function (make-symbol (format nil "TEST-~A" quantifier))))
5042 `(flet ((,function (function sequence)
5043 (,quantifier function sequence)))
5044 (ctu:assert-no-consing (,function constantly-t list))
5045 (ctu:assert-no-consing (,function constantly-nil vector))))))
5046 (test some)
5047 (test every)
5048 (test notany)
5049 (test notevery))))
5051 (with-test (:name :propagate-complex-type-tests)
5052 (flet ((test (type value)
5053 (let ((ftype (sb-kernel:%simple-fun-type
5054 (checked-compile `(lambda (x)
5055 (if (typep x ',type)
5057 ',value))))))
5058 (assert (typep ftype `(cons (eql function))))
5059 (assert (= 3 (length ftype)))
5060 (let* ((return (third ftype))
5061 (rtype (second return)))
5062 (assert (typep return `(cons (eql values)
5063 (cons t
5064 (cons (eql &optional)
5065 null)))))
5066 (assert (and (subtypep rtype type)
5067 (subtypep type rtype)))))))
5068 (mapc (lambda (params)
5069 (apply #'test params))
5070 `(((unsigned-byte 17) 0)
5071 ((member 1 3 5 7) 5)
5072 ((or symbol (eql 42)) t)))))
5074 (with-test (:name :constant-fold-complex-type-tests)
5075 (assert (equal (sb-kernel:%simple-fun-type
5076 (checked-compile `(lambda (x)
5077 (if (typep x '(member 1 3))
5078 (typep x '(member 1 3 15))
5079 t))))
5080 `(function (t) (values (member t) &optional))))
5081 (assert (equal (sb-kernel:%simple-fun-type
5082 (checked-compile `(lambda (x)
5083 (declare (type (member 1 3) x))
5084 (typep x '(member 1 3 15)))))
5085 `(function ((or (integer 1 1) (integer 3 3)))
5086 (values (member t) &optional)))))
5088 (with-test (:name :quietly-row-major-index-no-dimensions)
5089 (checked-compile `(lambda (x) (array-row-major-index x))))
5091 (with-test (:name :array-rank-transform)
5092 (checked-compile `(lambda (a) (array-rank (the an-imaginary-type a)))
5093 :allow-style-warnings t))
5095 (with-test (:name (:array-rank-fold :bug-1252108))
5096 (let ((notes (nth-value
5097 4 (checked-compile
5098 `(lambda (a)
5099 (typecase a
5100 ((array t 2)
5101 (when (= (array-rank a) 3)
5102 (array-dimension a 2)))))))))
5103 (assert (= 1 (length notes)))))
5105 (assert-error (upgraded-array-element-type 'an-undefined-type))
5107 (with-test (:name :xchg-misencoding)
5108 (assert (eql (funcall (checked-compile
5109 `(lambda (a b)
5110 (declare (optimize (speed 3) (safety 2))
5111 (type single-float a))
5112 (unless (eql b 1/2)
5113 (min a -1f0))))
5114 0f0 1)
5115 -1f0)))
5117 (with-test (:name :malformed-declare)
5118 (assert (nth-value
5119 1 (checked-compile `(lambda (x)
5120 (declare (unsigned-byte (x)))
5122 :allow-failure t))))
5124 (with-test (:name :no-dubious-asterisk-warning)
5125 (checked-compile
5126 `(lambda (foo)
5127 (macrolet ((frob-some-stuff (&rest exprs)
5128 (let ((temps
5129 (mapcar
5130 (lambda (x)
5131 (if (symbolp x) (copy-symbol x) (gensym)))
5132 exprs)))
5133 `(let ,(mapcar #'list temps exprs)
5134 (if (and ,@temps)
5135 (format t "Got~@{ ~S~^ and~}~%" ,@temps))))))
5136 (frob-some-stuff *print-base* (car foo))))))
5138 (with-test (:name :interr-type-specifier-hashing)
5139 (let ((specifiers
5140 (remove
5141 'simple-vector
5142 (map 'list
5143 (lambda (saetp)
5144 (sb-c::type-specifier
5145 (sb-c::specifier-type
5146 `(simple-array ,(sb-vm:saetp-specifier saetp) (*)))))
5147 sb-vm:*specialized-array-element-type-properties*))))
5148 (assert (sb-c::%interr-symbol-for-type-spec `(or ,@specifiers)))
5149 (assert (sb-c::%interr-symbol-for-type-spec
5150 `(or ,@specifiers system-area-pointer)))))
5152 (with-test (:name :simple-rank-1-array-*-p-works)
5153 (assert (funcall (checked-compile
5154 `(lambda () (typep #() '(simple-array * (*)))))))
5155 (loop for saetp across sb-vm:*specialized-array-element-type-properties*
5157 (dotimes (n-dimensions 3) ; test ranks 0, 1, and 2.
5158 (let ((dims (make-list n-dimensions :initial-element 2)))
5159 (dolist (adjustable-p '(nil t))
5160 (let ((a (make-array dims :element-type (sb-vm:saetp-specifier saetp)
5161 :adjustable adjustable-p)))
5162 (assert (eq (and (= n-dimensions 1) (not adjustable-p))
5163 (typep a '(simple-array * (*)))))))))))
5165 (with-test (:name :array-subtype-tests
5166 :skipped-on '(:not (:or :x86 :x86-64)))
5167 (assert (funcall (checked-compile
5168 `(lambda ()
5169 (typep #() '(or simple-vector simple-string))))))
5170 (flet ((approx-lines-of-assembly-code (type-expr)
5171 (count #\Newline
5172 (with-output-to-string (s)
5173 (disassemble
5174 `(lambda (x)
5175 (declare (optimize (sb-c::verify-arg-count 0)))
5176 (typep x ',type-expr))
5177 :stream s)))))
5178 ;; These are fragile, but less bad than the possibility of messing up
5179 ;; any vops, especially since the generic code in 'vm-type' checks for
5180 ;; a vop by its name in a place that would otherwise be agnostic of the
5181 ;; backend were it not for my inability to test all platforms.
5182 (assert (< (approx-lines-of-assembly-code
5183 '(simple-array * (*))) 25))
5184 ;; this tested all possible widetags one at a time, e.g. in VECTOR-SAP
5185 (assert (< (approx-lines-of-assembly-code
5186 '(sb-kernel:simple-unboxed-array (*))) 25))
5187 ;; This is actually a strange type but it's what ANSI-STREAM-READ-N-BYTES
5188 ;; declares as its buffer, which would choke in %BYTE-BLT if you gave it
5189 ;; (simple-array t (*)). But that's a different problem.
5190 (assert (< (approx-lines-of-assembly-code
5191 '(or system-area-pointer (simple-array * (*)))) 29))
5192 ;; And this was used by %BYTE-BLT which tested widetags one-at-a-time.
5193 (assert (< (approx-lines-of-assembly-code
5194 '(or system-area-pointer (sb-kernel:simple-unboxed-array (*))))
5195 29))))
5197 (with-test (:name :local-argument-mismatch-error-string)
5198 (multiple-value-bind (fun failurep warnings)
5199 (checked-compile `(lambda (x)
5200 (flet ((foo ()))
5201 (foo x)))
5202 :allow-warnings t)
5203 (declare (ignore failurep))
5204 (assert (= 1 (length warnings)))
5205 (multiple-value-bind (ok err) (ignore-errors (funcall fun 42))
5206 (assert (not ok))
5207 (assert (search "FLET FOO" (princ-to-string err))))))
5209 (with-test (:name :bug-1310574-0)
5210 (checked-compile `(lambda (a)
5211 (typecase a
5212 ((or (array * (* * 3)) (array * (* * 4)))
5213 (case (array-rank a)
5214 (2 (aref a 1 2))))))))
5216 (with-test (:name :bug-1310574-1)
5217 (checked-compile `(lambda (a)
5218 (typecase a
5219 ((or (array * ()) (array * (1)) (array * (1 2)))
5220 (case (array-rank a)
5221 (3 (aref a 1 2 3))))))))
5223 (with-test (:name :bug-573747)
5224 (assert (nth-value
5225 1 (checked-compile `(lambda (x) (progn (declare (integer x)) (* x 6)))
5226 :allow-failure t))))
5228 ;; Something in this function used to confuse lifetime analysis into
5229 ;; recording multiple conflicts for a single TNs in the dolist block.
5230 (with-test (:name :bug-1327008)
5231 (handler-bind (((or style-warning compiler-note)
5232 (lambda (c)
5233 (muffle-warning c))))
5234 (compile nil
5235 `(lambda (scheduler-spec
5236 schedule-generation-method
5237 utc-earliest-time utc-latest-time
5238 utc-other-earliest-time utc-other-latest-time
5239 &rest keys
5240 &key queue
5241 maximum-mileage
5242 maximum-extra-legs
5243 maximum-connection-time
5244 slice-number
5245 scheduler-hints
5246 permitted-route-locations prohibited-route-locations
5247 preferred-connection-locations disfavored-connection-locations
5248 origins destinations
5249 permitted-carriers prohibited-carriers
5250 permitted-operating-carriers prohibited-operating-carriers
5251 start-airports end-airports
5252 circuity-limit
5253 specified-circuity-limit-extra-miles
5254 (preferred-carriers :unspecified)
5255 &allow-other-keys)
5256 (declare (optimize speed))
5257 (let ((table1 (list nil))
5258 (table2 (list nil))
5259 (skip-flifo-checks (getf scheduler-spec :skip-flifo-checks))
5260 (construct-gaps-p (getf scheduler-spec :construct-gaps-p))
5261 (gap-locations (getf scheduler-spec :gap-locations))
5262 (result-array (make-array 100))
5263 (number-dequeued 0)
5264 (n-new 0)
5265 (n-calcs 0)
5266 (exit-reason 0)
5267 (prev-start-airports origins)
5268 (prev-end-airports destinations)
5269 (prev-permitted-carriers permitted-carriers))
5270 (flet ((run-with-hint (hint random-magic other-randomness
5271 maximum-extra-legs
5272 preferred-origins
5273 preferred-destinations
5274 same-pass-p)
5275 (let* ((hint-permitted-carriers (first hint))
5276 (preferred-end-airports
5277 (ecase schedule-generation-method
5278 (:DEPARTURE preferred-destinations)
5279 (:ARRIVAL preferred-origins)))
5280 (revised-permitted-carriers
5281 (cond ((and hint-permitted-carriers
5282 (not (eq permitted-carriers :ANY)))
5283 (intersection permitted-carriers
5284 hint-permitted-carriers))
5285 (hint-permitted-carriers)
5286 (permitted-carriers)))
5287 (revised-maximum-mileage
5288 (min (let ((maximum-mileage 0))
5289 (dolist (o start-airports)
5290 (dolist (d end-airports)
5291 (setf maximum-mileage
5292 (max maximum-mileage (mileage o d)))))
5293 (round (+ (* circuity-limit maximum-mileage)
5294 (or specified-circuity-limit-extra-miles
5295 (hairy-calculation slice-number)))))
5296 maximum-mileage)))
5297 (when (or (not (equal start-airports prev-start-airports))
5298 (not (equal end-airports prev-end-airports))
5299 (and (not (equal revised-permitted-carriers
5300 prev-permitted-carriers))))
5301 (incf n-calcs)
5302 (calculate-vectors
5303 prohibited-carriers
5304 permitted-operating-carriers
5305 prohibited-operating-carriers
5306 permitted-route-locations
5307 prohibited-route-locations
5308 construct-gaps-p
5309 gap-locations
5310 preferred-carriers)
5311 (setf prev-permitted-carriers revised-permitted-carriers))
5312 (multiple-value-bind (this-number-dequeued
5313 this-exit-reason
5314 this-n-new)
5315 (apply #'schedule-loop
5316 utc-earliest-time utc-other-earliest-time
5317 utc-latest-time utc-other-latest-time
5318 scheduler-spec schedule-generation-method
5319 queue
5320 :maximum-mileage revised-maximum-mileage
5321 :maximum-extra-legs maximum-extra-legs
5322 :maximum-connection-time maximum-connection-time
5323 :same-pass-p same-pass-p
5324 :preferred-end-airports preferred-end-airports
5325 :maximum-blah random-magic
5326 :skip-flifo-checks skip-flifo-checks
5327 :magic1 table1
5328 :magic2 table2
5329 :preferred-connection-locations preferred-connection-locations
5330 :disfavored-connection-locations disfavored-connection-locations
5331 keys)
5332 (when other-randomness
5333 (loop for i fixnum from n-new to (+ n-new (1- this-n-new))
5334 do (hairy-calculation i result-array)))
5335 (incf number-dequeued this-number-dequeued)
5336 (incf n-new this-n-new)
5337 (setq exit-reason (logior exit-reason this-exit-reason))))))
5338 (let ((n-hints-processed 0))
5339 (dolist (hint scheduler-hints)
5340 (run-with-hint hint n-hints-processed t 0
5341 nil nil nil)
5342 (incf n-hints-processed)))
5343 (run-with-hint nil 42 nil maximum-extra-legs
5344 '(yyy) '(xxx) t))
5345 exit-reason)))))
5347 (with-test (:name :dead-code-in-optional-dispatch)
5348 ;; the translation of each optional entry is
5349 ;; (let ((#:g (error "nope"))) (funcall #<clambda> ...))
5350 ;; but the funcall is unreachable. Since this is an artifact of how the
5351 ;; lambda is converted, it should not generate a note as if in user code.
5352 (checked-compile
5353 `(lambda (a &optional (b (error "nope")) (c (error "nope")))
5354 (values c b a))))
5356 (with-test (:name :nth-value-of-non-constant-N :skipped-on :interpreter)
5357 (labels ((foo (n f) (nth-value n (funcall f)))
5358 (bar () (values 0 1 2 3 4 5 6 7 8 9)))
5359 (assert (= (foo 5 #'bar) 5)) ; basic correctness
5360 (assert (eq (foo 12 #'bar) nil))
5361 (ctu:assert-no-consing (eql (foo 953 #'bar) 953))))
5363 (with-test (:name :position-derive-type-optimizer)
5364 (assert-code-deletion-note
5365 '(lambda (x) ; the call to POSITION can't return 4
5366 (let ((i (position x #(a b c d) :test 'eq)))
5367 (case i (4 'nope) (t 'okeydokey))))))
5369 ;; Assert that DO-PACKED-TNS has unsurprising behavior if the body RETURNs.
5370 ;; This isn't a test in the problem domain of CL - it's of an internal macro,
5371 ;; and x86-64-specific not because of broken-ness, but because it uses
5372 ;; known random TNs to play with. Printing "skipped on" for other backends
5373 ;; would be somewhat misleading in as much as it means nothing about
5374 ;; the correctness of the test on other architectures.
5375 #+x86-64
5376 (with-test (:name :do-packed-tn-iterator)
5377 (dotimes (i (ash 1 6))
5378 (labels ((make-tns (n)
5379 (mapcar 'copy-structure
5380 (subseq `sb-vm::(,rax-tn ,rbx-tn ,rcx-tn) 0 n)))
5381 (link (list)
5382 (when list
5383 (setf (sb-c::tn-next (car list)) (link (cdr list)))
5384 (car list))))
5385 (let* ((normal (make-tns (ldb (byte 2 0) i)))
5386 (restricted (make-tns (ldb (byte 2 2) i)))
5387 (wired (make-tns (ldb (byte 2 4) i)))
5388 (expect (append normal restricted wired))
5389 (comp (sb-c::make-empty-component))
5390 (ir2-comp (sb-c::make-ir2-component)))
5391 (setf (sb-c::component-info comp) ir2-comp
5392 (sb-c::ir2-component-normal-tns ir2-comp) (link normal)
5393 (sb-c::ir2-component-restricted-tns ir2-comp) (link restricted)
5394 (sb-c::ir2-component-wired-tns ir2-comp) (link wired))
5395 (let* ((list)
5396 (result (sb-c::do-packed-tns (tn comp 42) (push tn list))))
5397 (assert (eq result 42))
5398 (assert (equal expect (nreverse list))))
5399 (let* ((n 0) (list)
5400 (result (sb-c::do-packed-tns (tn comp 'bar)
5401 (push tn list)
5402 (if (= (incf n) 4) (return 'foo)))))
5403 (assert (eq result (if (>= (length expect) 4) 'foo 'bar)))
5404 (assert (equal (subseq expect 0 (min 4 (length expect)))
5405 (nreverse list))))))))
5407 ;; lp# 310267
5408 (with-test (:name (optimize :quality-multiply-specified :bug-310267))
5409 (let ((sb-c::*policy* sb-c::*policy*)) ; to keep this test pure
5410 (assert-signal (proclaim '(optimize space debug (space 0)))
5411 style-warning)
5412 (flet ((test (form)
5413 (assert (= 1 (length (nth-value
5414 3 (checked-compile
5415 form :allow-style-warnings t)))))))
5416 (test `(lambda () (declare (optimize speed (speed 0))) 5))
5417 (test `(lambda () (declare (optimize speed) (optimize (speed 0))) 5))
5418 (test `(lambda ()
5419 (declare (optimize speed)) (declare (optimize (speed 0)))
5420 5)))
5422 ;; these are OK
5423 (assert-no-signal (proclaim '(optimize (space 3) space)))
5424 (checked-compile `(lambda () (declare (optimize speed (speed 3))) 5))
5425 (checked-compile `(lambda () (declare (optimize speed) (optimize (speed 3))) 5))
5426 (checked-compile `(lambda ()
5427 (declare (optimize speed)) (declare (optimize (speed 3)))
5428 5))))
5430 (with-test (:name (truncate :type-derivation))
5431 (assert (= 4 (funcall (checked-compile
5432 `(lambda (a b)
5433 (truncate a (the (rational (1) (3)) b))))
5434 10 5/2))))
5436 (with-test (:name :constantp-on-a-literal-function-works)
5437 (assert (constantp `(the (function (list) t) ,#'car))))
5439 (with-test (:name :arg-count-error)
5440 (assert (eq :win (handler-case (funcall (intern "CONS") 1 2 3)
5441 (sb-int:simple-program-error () :win)
5442 (condition () :lose)))))
5444 (with-test (:name :mv-conversion)
5445 (checked-compile `(lambda (a)
5446 (tagbody (go 0)
5447 (list (unwind-protect a))
5448 (multiple-value-call #'list
5449 (values (catch 'ct5 (go 0))))
5450 0))))
5452 (with-test (:name (:null-cleanups-1 :bug-1416704 :bug-404441))
5453 (let ((x (funcall
5454 (checked-compile
5455 `(lambda ()
5456 (lambda (x)
5457 (declare (optimize speed))
5458 (if x
5459 (funcall (flet ((bar () 10)) #'bar))
5460 (funcall (flet ((fez ()
5461 (funcall (flet ((foo () 20)) #'foo))))
5462 #'fez)))))))))
5463 (assert (= (funcall x t) 10))
5464 (assert (= (funcall x nil) 20))))
5466 (with-test (:name (:null-cleanups-2 :bug-1416704 :bug-404441))
5467 (let ((fun (funcall
5468 (checked-compile
5469 `(lambda ()
5470 (lambda (x)
5471 (declare (optimize speed))
5472 (let* ((a2 (lambda () 20))
5473 (a4 (lambda ()))
5474 (a0 (flet ((f () (funcall a2)))
5475 #'f))
5476 (a3 (lambda ()
5477 (if x
5478 (if x
5479 (throw 'x 10)
5480 (let ((a5 (lambda () (funcall a4))))
5481 (funcall a5)))
5482 (funcall a0)))))
5483 (funcall a3))))))))
5484 (assert (= (catch 'x (funcall fun t)) 10))
5485 (assert (= (catch 'x (funcall fun nil)) 20))))
5488 (with-test (:name :locall-already-let-converted)
5489 (assert (eq (funcall
5490 (funcall
5491 (checked-compile
5492 `(lambda ()
5493 (flet ((call (ff)
5494 (flet ((f () (return-from f ff)))
5495 (declare (inline f))
5497 (f))))
5498 (declare (inline call))
5499 (call 1)
5500 (call (lambda () 'result)))))))
5501 'result)))
5503 (with-test (:name :debug-dump-elsewhere)
5504 (assert (eql (catch 'x
5505 (funcall
5506 (checked-compile
5507 `(lambda ()
5508 (declare (optimize debug))
5509 (throw 'x *)))))
5510 *)))
5512 (with-test (:name (typep :quasiquoted-constant))
5513 (assert (null (ctu:find-named-callees
5514 (checked-compile
5515 `(lambda (x)
5516 (typep x `(signed-byte ,sb-vm:n-word-bits))))))))
5518 (with-test (:name (logior :transform))
5519 (multiple-value-bind (fun failurep warnings)
5520 (checked-compile `(lambda (c)
5521 (flet ((f (x)
5522 (the integer x)))
5523 (logior c (f nil))))
5524 :allow-warnings t)
5525 (assert failurep)
5526 (assert (= 1 (length warnings)))
5527 (assert-error (funcall fun 10) type-error)))
5529 (with-test (:name :eql/integer-folding)
5530 (checked-compile
5531 `(lambda (a)
5532 (fceiling (the (member 2.3 21672589639883401935) a)))))
5534 (with-test (:name (position :derive-type))
5535 (let ((f (checked-compile
5536 `(lambda (x)
5537 (declare (type (simple-string 90) x))
5538 (declare (muffle-conditions code-deletion-note))
5539 (let ((b (position #\i x)))
5540 (if (and (integerp b) (> b 100))
5541 'yikes 'okey-dokey))))))
5542 ;; The function can not return YIKES
5543 (assert (not (ctu:find-code-constants f :type '(eql yikes))))))
5545 (with-test (:name :compile-file-error-position-reporting)
5546 (dolist (input '("data/wonky1.lisp" "data/wonky2.lisp" "data/wonky3.lisp"))
5547 (let ((expect (with-open-file (f input) (read f))))
5548 (assert (stringp expect))
5549 (let ((err-string (with-output-to-string (*error-output*)
5550 (compile-file input :print nil))))
5551 (assert (search expect err-string))))))
5553 (with-test (:name (coerce :derive-type))
5554 (macrolet ((check (type ll form &rest values)
5555 `(assert (equal (funcall (checked-compile
5556 `(lambda ,',ll
5557 (ctu:compiler-derived-type ,',form)))
5558 ,@values)
5559 ',type))))
5560 (check list
5562 (coerce a 'list)
5563 nil)
5564 (check (unsigned-byte 32)
5566 (coerce a '(unsigned-byte 32))
5568 (check character
5569 (a x)
5570 (coerce a (array-element-type (the (array character) x)))
5572 "abc")
5573 (check (unsigned-byte 32)
5574 (a x)
5575 (coerce a (array-element-type (the (array (unsigned-byte 32)) x)))
5577 (make-array 10 :element-type '(unsigned-byte 32)))))
5579 (with-test (:name :associate-args)
5580 (flet ((test (form argument)
5581 (multiple-value-bind (fun failurep warnings)
5582 (checked-compile form :allow-warnings t)
5583 (assert failurep)
5584 (assert (= 1 (length warnings)))
5585 (assert-error (funcall fun argument)))))
5586 (test `(lambda (x) (+ 1 x nil)) 2)
5587 (test `(lambda (x) (/ 1 x nil)) 4)))
5589 (with-test (:name :eager-substitute-single-use-lvar)
5590 (assert (= (funcall
5591 (compile nil
5592 `(lambda (a)
5593 (declare (optimize (debug 0) (safety 0)))
5594 (let ((a (the fixnum a))
5595 (x 1)
5597 (tagbody
5598 (flet ((jump () (go loop)))
5599 (jump))
5600 loop
5601 (setf z (the fixnum (if (= x 1) #xFFF a)))
5602 (unless (= x 0)
5603 (setf x 0)
5604 (go loop)))
5605 z)))
5606 2))))
5608 (with-test (:name :vop-on-eql-type)
5609 (assert (= (funcall
5610 (funcall (compile nil
5611 `(lambda (b)
5612 (declare ((eql -7) b)
5613 (optimize debug))
5614 (lambda (x)
5615 (logior x b))))
5618 -5)))
5620 (flet ((test (form)
5621 (multiple-value-bind (fun failurep)
5622 (checked-compile `(lambda () ,form)
5623 :allow-failure t)
5624 (assert failurep)
5625 (assert-error (funcall fun) sb-int:compiled-program-error))))
5627 (with-test (:name (compile macrolet :malformed))
5628 (test '(macrolet (foo () 'bar)))
5629 (test '(macrolet x))
5630 (test '(symbol-macrolet x))
5631 (test '(symbol-macrolet (x))))
5633 (with-test (:name (compile flet :malformed))
5634 (test '(flet (foo () 'bar)))
5635 (test '(flet x))
5636 (test '(labels (foo () 'bar)))
5637 (test '(labels x))))
5639 (with-test (:name :compile-load-time-value-interpreted-mode)
5640 ;; This test exercises the same pattern as HANDLER-BIND (to a
5641 ;; degree). In particular a HANDLER-BIND that was compiled when the
5642 ;; *EVALUATOR-MODE* was :INTERPRET would not compile its class
5643 ;; predicates, because LOAD-TIME-VALUE just called EVAL, and you
5644 ;; would get back a list with an interpreted function in it.
5646 ;; In the code below, this function when called would generate a new
5647 ;; symbol each time. But if the compiler processes the guts as it
5648 ;; should, you get back a compiled lambda which returns a constant
5649 ;; symbol.
5650 (let ((f (let ((sb-ext:*evaluator-mode* :interpret))
5651 (checked-compile
5652 `(lambda ()
5653 (load-time-value
5654 (list (lambda ()
5655 (macrolet ((foo ()
5656 (sb-int:keywordicate (gensym))))
5657 (foo))))))))))
5658 (eq (funcall (car (funcall f)))
5659 (funcall (car (funcall f))))))
5661 (with-test (:name :constant-fold-%eql/integer)
5662 (assert (null
5663 (funcall (checked-compile
5664 `(lambda (x)
5665 (declare (type (complex single-float) x)
5666 (optimize (debug 2)))
5667 (member (the (eql #c(0.0 0.0)) x)
5668 '(1 2 3 9912477572127105188))))
5669 #C(0.0 0.0)))))
5671 (with-test (:name (compile svref :constant))
5672 (assert
5673 (= (funcall (checked-compile
5674 `(lambda () (svref #(1 2 3) 1))))
5675 2)))
5677 (with-test (:name (compile char-equal :type-intersection))
5678 (assert
5679 (eq (funcall (checked-compile
5680 `(lambda (x y)
5681 (char-equal (the (member #\a #\B) x)
5682 (the (eql #\A) y))))
5683 #\a #\A)
5684 t)))
5686 (with-test (:name (oddp fixnum :no-consing))
5687 (let ((f (compile nil '(lambda (x) (oddp x)))))
5688 (ctu:assert-no-consing (funcall f most-positive-fixnum))))
5689 (with-test (:name (oddp bignum :no-consing))
5690 (let ((f (compile nil '(lambda (x) (oddp x))))
5691 (x (* most-positive-fixnum most-positive-fixnum 3)))
5692 (ctu:assert-no-consing (funcall f x))))
5693 (with-test (:name (logtest fixnum :no-consing :bug-1277690))
5694 (let ((f (compile nil '(lambda (x) (logtest x most-positive-fixnum)))))
5695 (ctu:assert-no-consing (funcall f 1))))
5696 (with-test (:name (logtest bignum :no-consing))
5697 (let ((f (compile nil '(lambda (x) (logtest x 1))))
5698 (x (* most-positive-fixnum most-positive-fixnum 3)))
5699 (ctu:assert-no-consing (funcall f x))))
5701 (with-test (:name (:randomized :mask-signed-field))
5702 (let (result)
5703 (dotimes (i 1000)
5704 (let* ((ool (compile nil '(lambda (s i) (sb-c::mask-signed-field s i))))
5705 (size (random (* sb-vm:n-word-bits 2)))
5706 (constant (compile nil `(lambda (i) (sb-c::mask-signed-field ,size i))))
5707 (arg (- (random (* most-positive-fixnum 8)) (* most-positive-fixnum 4)))
5708 (declared (compile nil `(lambda (i) (declare (type (integer ,(- (abs arg)) ,(abs arg)) i)) (sb-c::mask-signed-field ,size i))))
5709 (ool-answer (funcall ool size arg))
5710 (constant-answer (funcall constant arg))
5711 (declared-answer (funcall declared arg)))
5712 (unless (= ool-answer constant-answer declared-answer)
5713 (push (list size arg ool-answer constant-answer declared-answer) result))))
5714 (assert (null result))))
5716 (with-test (:name :array-dimensions-*)
5717 (= (funcall (compile nil `(lambda (array)
5718 (declare ((or (vector t) (array character)) array))
5719 (array-dimension array 0)))
5720 #(1 2 3))
5723 (with-test (:name :generate-type-checks-on-dead-blocks)
5724 (assert (equalp (funcall (compile nil `(lambda (a b)
5725 (declare (optimize (safety 3))
5726 (type (member vector 42) a))
5727 (map a 'list (the vector b) #*)))
5728 'vector #())
5729 #())))
5731 (with-test (:name (make-list :large 1))
5732 (checked-compile `(lambda ()
5733 (make-list (expt 2 28) :initial-element 0))))
5735 (with-test (:name (make-list :large 2)
5736 :skipped-on '(not :64-bit))
5737 (checked-compile `(lambda ()
5738 (make-list (expt 2 30) :initial-element 0))))
5740 (with-test (:name :bad-cond)
5741 (assert-error
5742 (checked-compile
5743 '(lambda () (cond (t 10) 20)))))
5745 (with-test (:name :removed-dx-cast)
5746 (assert (= (funcall
5747 (checked-compile `(lambda ()
5748 (loop
5749 (let ((x (the integer (return 0))))
5750 (declare (dynamic-extent x))
5751 (unwind-protect x 1))))))
5752 0)))
5754 (with-test (:name :isqrt-derivation)
5755 (assert (eql (funcall (checked-compile
5756 `(lambda (i)
5757 (isqrt (count (the bit i) #*11101))))
5759 2)))