0.8.5.32:
[sbcl/lichteblau.git] / tests / compiler.pure.lisp
blobac15d8c8ed2dc4523b2d15cffde23f9c4bddee7b
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 ;;; Exercise a compiler bug (by crashing the compiler).
17 ;;;
18 ;;; This test code is from Douglas Crosher's simplified TICKLE-BUG
19 ;;; (2000-09-06 on cmucl-imp).
20 ;;;
21 ;;; The bug was fixed by Douglas Crosher's patch, massaged for SBCL by
22 ;;; Martin Atzmueller (2000-09-13 on sbcl-devel).
23 (funcall (compile nil
24 '(lambda ()
25 (labels ((fun1 ()
26 (fun2))
27 (fun2 ()
28 (when nil
29 (tagbody
30 tag
31 (fun2)
32 (go tag)))
33 (when nil
34 (tagbody
35 tag
36 (fun1)
37 (go tag)))))
39 (fun1)
40 nil))))
42 ;;; Exercise a compiler bug (by crashing the compiler).
43 ;;;
44 ;;; Tim Moore gave a patch for this bug in CMU CL 2000-05-24 on
45 ;;; cmucl-imp, and Martin Atzmueller applied it to SBCL.
46 (funcall (compile nil
47 '(lambda (x)
48 (or (integerp x)
49 (block used-by-some-y?
50 (flet ((frob (stk)
51 (dolist (y stk)
52 (unless (rejected? y)
53 (return-from used-by-some-y? t)))))
54 (declare (inline frob))
55 (frob (rstk x))
56 (frob (mrstk x)))
57 nil))))
58 13)
60 ;;; bug 112, reported by Martin Atzmueller 2001-06-25 (originally
61 ;;; from Bruno Haible in CMU CL bugs collection), fixed by
62 ;;; Alexey Dejneka 2002-01-27
63 (assert (= 1 ; (used to give 0 under bug 112)
64 (let ((x 0))
65 (declare (special x))
66 (let ((x 1))
67 (let ((y x))
68 (declare (special x)) y)))))
69 (assert (= 1 ; (used to give 1 even under bug 112, still works after fix)
70 (let ((x 0))
71 (declare (special x))
72 (let ((x 1))
73 (let ((y x) (x 5))
74 (declare (special x)) y)))))
76 ;;; another LET-related bug fixed by Alexey Dejneka at the same
77 ;;; time as bug 112
78 (multiple-value-bind (fun warnings-p failure-p)
79 ;; should complain about duplicate variable names in LET binding
80 (compile nil
81 '(lambda ()
82 (let (x
83 (x 1))
84 (list x))))
85 (declare (ignore warnings-p))
86 (assert (functionp fun))
87 (assert failure-p))
89 ;;; bug 169 (reported by Alexey Dejneka 2002-05-12, fixed by David
90 ;;; Lichteblau 2002-05-21)
91 (progn
92 (multiple-value-bind (fun warnings-p failure-p)
93 (compile nil
94 ;; Compiling this code should cause a STYLE-WARNING
95 ;; about *X* looking like a special variable but not
96 ;; being one.
97 '(lambda (n)
98 (let ((*x* n))
99 (funcall (symbol-function 'x-getter))
100 (print *x*))))
101 (assert (functionp fun))
102 (assert warnings-p)
103 (assert (not failure-p)))
104 (multiple-value-bind (fun warnings-p failure-p)
105 (compile nil
106 ;; Compiling this code should not cause a warning
107 ;; (because the DECLARE turns *X* into a special
108 ;; variable as its name suggests it should be).
109 '(lambda (n)
110 (let ((*x* n))
111 (declare (special *x*))
112 (funcall (symbol-function 'x-getter))
113 (print *x*))))
114 (assert (functionp fun))
115 (assert (not warnings-p))
116 (assert (not failure-p))))
118 ;;; a bug in 0.7.4.11
119 (dolist (i '(a b 1 2 "x" "y"))
120 ;; In sbcl-0.7.4.11, the compiler tried to source-transform the
121 ;; TYPEP here but got confused and died, doing
122 ;; (ASSOC '(AND INTEGERP (SATISFIES PLUSP)))
123 ;; *BACKEND-TYPE-PREDICATES*
124 ;; :TEST #'TYPE=)
125 ;; and blowing up because TYPE= tried to call PLUSP on the
126 ;; characters of the MEMBER-TYPE representing STANDARD-CHAR.
127 (when (typep i '(and integer (satisfies oddp)))
128 (print i)))
129 (dotimes (i 14)
130 (when (typep i '(and integer (satisfies oddp)))
131 (print i)))
133 ;;; bug 156 (reported by APD sbcl-devel 2002-04-12, fixed by CSR patch
134 ;;; sbcl-devel 2002-07-02): FUNCTION-LAMBDA-EXPRESSION of
135 ;;; interactively-compiled functions was broken by sleaziness and
136 ;;; confusion in the assault on 0.7.0, so this expression used to
137 ;;; signal TYPE-ERROR when it found NIL instead of a DEBUG-SOURCE.
138 (eval '(function-lambda-expression #'(lambda (x) x)))
140 ;;; bug caught and fixed by Raymond Toy cmucl-imp 2002-07-10: &REST
141 ;;; variable is not optional.
142 (assert (null (ignore-errors (eval '(funcall (lambda (&rest) 12))))))
144 ;;; on the PPC, we got the magic numbers in undefined_tramp wrong for
145 ;;; a while; fixed by CSR 2002-07-18
146 (multiple-value-bind (value error)
147 (ignore-errors (some-undefined-function))
148 (assert (null value))
149 (assert (eq (cell-error-name error) 'some-undefined-function)))
151 ;;; Non-symbols shouldn't be allowed as VARs in lambda lists. (Where VAR
152 ;;; is a variable name, as in section 3.4.1 of the ANSI spec.)
153 (assert (null (ignore-errors (eval '(lambda ("foo") 12)))))
154 (assert (ignore-errors (eval '(lambda (foo) 12))))
155 (assert (null (ignore-errors (eval '(lambda (&optional 12) "foo")))))
156 (assert (ignore-errors (eval '(lambda (&optional twelve) "foo"))))
157 (assert (null (ignore-errors (eval '(lambda (&optional (12 12)) "foo")))))
158 (assert (ignore-errors (eval '(lambda (&optional (twelve 12)) "foo"))))
159 (assert (null (ignore-errors (eval '(lambda (&key #\c) "foo")))))
160 (assert (ignore-errors (eval '(lambda (&key c) "foo"))))
161 (assert (null (ignore-errors (eval '(lambda (&key (#\c #\c)) "foo")))))
162 (assert (ignore-errors (eval '(lambda (&key (c #\c)) "foo"))))
163 (assert (null (ignore-errors (eval '(lambda (&key ((#\c #\c) #\c)) "foo")))))
164 (assert (ignore-errors (eval '(lambda (&key ((:c cbyanyothername) #\c)) "foo"))))
166 ;;; As reported and fixed by Antonio Martinez-Shotton sbcl-devel
167 ;;; 2002-09-12, this failed in sbcl-0.7.7.23. (with failed AVER
168 ;;; "(LEAF-HAS-SOURCE-NAME-P LEAF)")
169 (assert (= (funcall (eval `(lambda (x) (funcall ,(lambda (y) (+ y 3)) x))) 14)
170 17))
172 ;;; bug 181: bad type specifier dropped compiler into debugger
173 (assert (list (compile nil '(lambda (x)
174 (declare (type (0) x))
175 x))))
177 (let ((f (compile nil '(lambda (x)
178 (make-array 1 :element-type '(0))))))
179 (assert (null (ignore-errors (funcall f)))))
181 ;;; the following functions must not be flushable
182 (dolist (form '((make-sequence 'fixnum 10)
183 (concatenate 'fixnum nil)
184 (map 'fixnum #'identity nil)
185 (merge 'fixnum nil nil #'<)))
186 (assert (not (eval `(locally (declare (optimize (safety 0)))
187 (ignore-errors (progn ,form t)))))))
189 (dolist (form '((values-list (car (list '(1 . 2))))
190 (fboundp '(set bet))
191 (atan #c(1 1) (car (list #c(2 2))))
192 (nthcdr (car (list (floor (cos 3)))) '(1 2 3 4 5))
193 (nthcdr (car (list 5)) '(1 2 . 3))))
194 (assert (not (eval `(locally (declare (optimize (safety 3)))
195 (ignore-errors (progn ,form t)))))))
197 ;;; a bug in the MAP deftransform caused non-VECTOR array specifiers
198 ;;; to cause errors in the compiler. Fixed by CSR in 0.7.8.10
199 (assert (list (compile nil '(lambda (x) (map 'simple-array 'identity x)))))
201 ;;; bug 129: insufficient syntax checking in MACROLET
202 (multiple-value-bind (result error)
203 (ignore-errors (eval '(macrolet ((foo x `',x)) (foo 1 2 3))))
204 (assert (null result))
205 (assert (typep error 'error)))
207 ;;; bug 124: environment of MACROLET-introduced macro expanders
208 (assert (equal
209 (macrolet ((mext (x) `(cons :mext ,x)))
210 (macrolet ((mint (y) `'(:mint ,(mext y))))
211 (list (mext '(1 2))
212 (mint (1 2)))))
213 '((:MEXT 1 2) (:MINT (:MEXT 1 2)))))
215 ;;; bug 48c: SYMBOL-MACROLET should signal PROGRAM-ERROR if introduced
216 ;;; symbol is declared to be SPECIAL
217 (multiple-value-bind (result error)
218 (ignore-errors (funcall (lambda ()
219 (symbol-macrolet ((s '(1 2)))
220 (declare (special s))
221 s))))
222 (assert (null result))
223 (assert (typep error 'program-error)))
225 ;;; ECASE should treat a bare T as a literal key
226 (multiple-value-bind (result error)
227 (ignore-errors (ecase 1 (t 0)))
228 (assert (null result))
229 (assert (typep error 'type-error)))
231 (multiple-value-bind (result error)
232 (ignore-errors (ecase 1 (t 0) (1 2)))
233 (assert (eql result 2))
234 (assert (null error)))
236 ;;; FTYPE should accept any functional type specifier
237 (compile nil '(lambda (x) (declare (ftype function f)) (f x)))
239 ;;; FUNCALL of special operators and macros should signal an
240 ;;; UNDEFINED-FUNCTION error
241 (multiple-value-bind (result error)
242 (ignore-errors (funcall 'quote 1))
243 (assert (null result))
244 (assert (typep error 'undefined-function))
245 (assert (eq (cell-error-name error) 'quote)))
246 (multiple-value-bind (result error)
247 (ignore-errors (funcall 'and 1))
248 (assert (null result))
249 (assert (typep error 'undefined-function))
250 (assert (eq (cell-error-name error) 'and)))
252 ;;; PSETQ should behave when given complex symbol-macro arguments
253 (multiple-value-bind (sequence index)
254 (symbol-macrolet ((x (aref a (incf i)))
255 (y (aref a (incf i))))
256 (let ((a (copy-seq #(0 1 2 3 4 5 6 7 8 9)))
257 (i 0))
258 (psetq x (aref a (incf i))
259 y (aref a (incf i)))
260 (values a i)))
261 (assert (equalp sequence #(0 2 2 4 4 5 6 7 8 9)))
262 (assert (= index 4)))
264 (multiple-value-bind (result error)
265 (ignore-errors
266 (let ((x (list 1 2)))
267 (psetq (car x) 3)
269 (assert (null result))
270 (assert (typep error 'program-error)))
272 ;;; COPY-SEQ should work on known-complex vectors:
273 (assert (equalp #(1)
274 (let ((v (make-array 0 :fill-pointer 0)))
275 (vector-push-extend 1 v)
276 (copy-seq v))))
278 ;;; to support INLINE functions inside MACROLET, it is necessary for
279 ;;; FUNCTION-LAMBDA-EXPRESSION to return a proper lambda expression in
280 ;;; certain circumstances, one of which is when compile is called from
281 ;;; top-level.
282 (assert (equal
283 (function-lambda-expression
284 (compile nil '(lambda (x) (block nil (print x)))))
285 '(lambda (x) (block nil (print x)))))
287 ;;; bug 62: too cautious type inference in a loop
288 (assert (nth-value
290 (compile nil
291 '(lambda (a)
292 (declare (optimize speed (safety 0)))
293 (typecase a
294 (array (loop (print (car a)))))))))
296 ;;; Bug reported by Robert E. Brown sbcl-devel 2003-02-02: compiler
297 ;;; failure
298 (compile nil
299 '(lambda (key tree collect-path-p)
300 (let ((lessp (key-lessp tree))
301 (equalp (key-equalp tree)))
302 (declare (type (function (t t) boolean) lessp equalp))
303 (let ((path '(nil)))
304 (loop for node = (root-node tree)
305 then (if (funcall lessp key (node-key node))
306 (left-child node)
307 (right-child node))
308 when (null node)
309 do (return (values nil nil nil))
310 do (when collect-path-p
311 (push node path))
312 (when (funcall equalp key (node-key node))
313 (return (values node path t))))))))
315 ;;; CONSTANTLY should return a side-effect-free function (bug caught
316 ;;; by Paul Dietz' test suite)
317 (let ((i 0))
318 (let ((fn (constantly (progn (incf i) 1))))
319 (assert (= i 1))
320 (assert (= (funcall fn) 1))
321 (assert (= i 1))
322 (assert (= (funcall fn) 1))
323 (assert (= i 1))))
325 ;;; Bug 240 reported by tonyms on #lisp IRC 2003-02-25 (modified version)
326 (loop for (fun warns-p) in
327 '(((lambda (&optional *x*) *x*) t)
328 ((lambda (&optional *x* &rest y) (values *x* y)) t)
329 ((lambda (&optional *print-length*) (values *print-length*)) nil)
330 ((lambda (&optional *print-length* &rest y) (values *print-length* y)) nil)
331 ((lambda (&optional *x*) (declare (special *x*)) (values *x*)) nil)
332 ((lambda (&optional *x* &rest y) (declare (special *x*)) (values *x* y)) nil))
333 for real-warns-p = (nth-value 1 (compile nil fun))
334 do (assert (eq warns-p real-warns-p)))
336 ;;; Bug reported by Gilbert Baumann on #lisp IRC 2003-03-26
337 (assert (equal (funcall (eval '(lambda (x &optional (y (pop x))) (list x y)))
338 '(1 2))
339 '((2) 1)))
341 ;;; Bug reported by Paul Dietz on cmucl-imp and fixed by Gerd
342 ;;; Moellmann: CONVERT-MORE-CALL failed on the following call
343 (assert (eq (eval '((lambda (&key) 'u) :allow-other-keys nil)) 'u))
345 (raises-error? (multiple-value-bind (a b c)
346 (eval '(truncate 3 4))
347 (declare (integer c))
348 (list a b c))
349 type-error)
351 (assert (equal (multiple-value-list (the (values &rest integer)
352 (eval '(values 3))))
353 '(3)))
355 ;;; Bug relating to confused representation for the wild function
356 ;;; type:
357 (assert (null (funcall (eval '(lambda () (multiple-value-list (values)))))))
359 ;;; &ENVIRONMENT parameter should be bound first (from Paul Dietz'
360 ;;; test suite)
361 (assert (eql (macrolet ((foo () 1))
362 (macrolet ((%f (&optional (x (macroexpand '(foo) env)) &environment env)
364 (%f)))
367 ;;; MACROLET should check for duplicated names
368 (dolist (ll '((x (z x))
369 (x y &optional z x w)
370 (x y &optional z z)
371 (x &rest x)
372 (x &rest (y x))
373 (x &optional (y nil x))
374 (x &optional (y nil y))
375 (x &key x)
376 (x &key (y nil x))
377 (&key (y nil z) (z nil w))
378 (&whole x &optional x)
379 (&environment x &whole x)))
380 (assert (nth-value 2
381 (handler-case
382 (compile nil
383 `(lambda ()
384 (macrolet ((foo ,ll nil)
385 (bar (&environment env)
386 `',(macro-function 'foo env)))
387 (bar))))
388 (error (c)
389 (values nil t t))))))
391 (assert (typep (eval `(the arithmetic-error
392 ',(make-condition 'arithmetic-error)))
393 'arithmetic-error))
395 (assert (not (nth-value
396 2 (compile nil '(lambda ()
397 (make-array nil :initial-element 11))))))
399 (assert (raises-error? (funcall (eval #'open) "assertoid.lisp"
400 :external-format '#:nonsense)))
401 (assert (raises-error? (funcall (eval #'load) "assertoid.lisp"
402 :external-format '#:nonsense)))
404 (assert (= (the (values integer symbol) (values 1 'foo 13)) 1))
406 (let ((f (compile nil
407 '(lambda (v)
408 (declare (optimize (safety 3)))
409 (list (the fixnum (the (real 0) (eval v))))))))
410 (assert (raises-error? (funcall f 0.1) type-error))
411 (assert (raises-error? (funcall f -1) type-error)))
413 ;;; the implicit block does not enclose lambda list
414 (let ((forms '((defmacro #1=#:foo (&optional (x (return-from #1#))))
415 #+nil(macrolet ((#2=#:foo (&optional (x (return-from #2#))))))
416 (define-compiler-macro #3=#:foo (&optional (x (return-from #3#))))
417 (deftype #4=#:foo (&optional (x (return-from #4#))))
418 (define-setf-expander #5=#:foo (&optional (x (return-from #5#))))
419 (defsetf #6=#:foo (&optional (x (return-from #6#))) ()))))
420 (dolist (form forms)
421 (assert (nth-value 2 (compile nil `(lambda () ,form))))))
423 (assert (nth-value 2 (compile nil
424 '(lambda ()
425 (svref (make-array '(8 9) :adjustable t) 1)))))
427 ;;; CHAR= did not check types of its arguments (reported by Adam Warner)
428 (raises-error? (funcall (compile nil '(lambda (x y z) (char= x y z)))
429 #\a #\b nil)
430 type-error)
431 (raises-error? (funcall (compile nil
432 '(lambda (x y z)
433 (declare (optimize (speed 3) (safety 3)))
434 (char/= x y z)))
435 nil #\a #\a)
436 type-error)
438 ;;; Compiler lost return type of MAPCAR and friends
439 (dolist (fun '(mapcar mapc maplist mapl))
440 (assert (nth-value 2 (compile nil
441 `(lambda (x)
442 (1+ (,fun #'print x)))))))
444 (assert (nth-value 2 (compile nil
445 '(lambda ()
446 (declare (notinline mapcar))
447 (1+ (mapcar #'print '(1 2 3)))))))
449 ;;; bug found by Paul Dietz: (SETF AREF) for bit vectors with constant
450 ;;; index was effectless
451 (let ((f (compile nil '(lambda (a v)
452 (declare (type simple-bit-vector a) (type bit v))
453 (declare (optimize (speed 3) (safety 0)))
454 (setf (aref a 0) v)
455 a))))
456 (let ((y (make-array 2 :element-type 'bit :initial-element 0)))
457 (assert (equal y #*00))
458 (funcall f y 1)
459 (assert (equal y #*10))))
461 (handler-bind ((sb-ext:compiler-note #'error))
462 (compile nil '(lambda (x)
463 (declare (type (simple-array (simple-string 3) (5)) x))
464 (aref (aref x 0) 0))))
466 ;;; compiler failure
467 (let ((f (compile nil '(lambda (x) (typep x '(not (member 0d0)))))))
468 (assert (funcall f 1d0)))
470 (compile nil '(lambda (x)
471 (declare (double-float x))
472 (let ((y (* x pi)))
473 (atan y y))))
475 ;;; bogus optimization of BIT-NOT
476 (multiple-value-bind (result x)
477 (eval '(let ((x (eval #*1001)))
478 (declare (optimize (speed 2) (space 3))
479 (type (bit-vector) x))
480 (values (bit-not x nil) x)))
481 (assert (equal x #*1001))
482 (assert (equal result #*0110)))
484 ;;; the VECTOR type in CONCATENATE/MERGE/MAKE-SEQUENCE means (VECTOR T).
485 (handler-bind ((sb-ext:compiler-note #'error))
486 (assert (equalp (funcall
487 (compile
489 '(lambda ()
490 (let ((x (make-sequence 'vector 10 :initial-element 'a)))
491 (setf (aref x 4) 'b)
492 x))))
493 #(a a a a b a a a a a))))
495 ;;; this is not a check for a bug, but rather a test of compiler
496 ;;; quality
497 (dolist (type '((integer 0 *) ; upper bound
498 (real (-1) *)
499 float ; class
500 (real * (-10)) ; lower bound
502 (assert (nth-value
503 1 (compile nil
504 `(lambda (n)
505 (declare (optimize (speed 3) (compilation-speed 0)))
506 (loop for i from 1 to (the (integer -17 10) n) by 2
507 collect (when (> (random 10) 5)
508 (the ,type (- i 11)))))))))
510 ;;; bug 278b
512 ;;; We suppose that INTEGER arithmetic cannot be efficient, and the
513 ;;; compiler has an optimized VOP for +; so this code should cause an
514 ;;; efficiency note.
515 (assert (eq (block nil
516 (handler-case
517 (compile nil '(lambda (i)
518 (declare (optimize speed))
519 (declare (type integer i))
520 (+ i 2)))
521 (sb-ext:compiler-note (c) (return :good))))
522 :good))
524 ;;; bug 277: IGNORE/IGNORABLE declarations should be acceptable for
525 ;;; symbol macros
526 (assert (not (nth-value 1 (compile nil '(lambda (u v)
527 (symbol-macrolet ((x u)
528 (y v))
529 (declare (ignore x)
530 (ignorable y))
531 (list u v)))))))
533 ;;; bug reported by Paul Dietz: wrong optimizer for (EXPT ... 0)
534 (loop for (x type) in
535 '((14 integer)
536 (14 rational)
537 (-14/3 (rational -8 11))
538 (3s0 short-float)
539 (4f0 single-float)
540 (5d0 double-float)
541 (6l0 long-float)
542 (14 real)
543 (13/2 real)
544 (2s0 real)
545 (2d0 real)
546 (#c(-3 4) (complex fixnum))
547 (#c(-3 4) (complex rational))
548 (#c(-3/7 4) (complex rational))
549 (#c(2s0 3s0) (complex short-float))
550 (#c(2f0 3f0) (complex single-float))
551 (#c(2d0 3d0) (complex double-float))
552 (#c(2l0 3l0) (complex long-float))
553 (#c(2d0 3s0) (complex float))
554 (#c(2 3f0) (complex real))
555 (#c(2 3d0) (complex real))
556 (#c(-3/7 4) (complex real))
557 (#c(-3/7 4) complex)
558 (#c(2 3l0) complex))
559 do (dolist (zero '(0 0s0 0f0 0d0 0l0))
560 (dolist (real-zero (list zero (- zero)))
561 (let* ((src `(lambda (x) (expt (the ,type x) ,real-zero)))
562 (fun (compile nil src))
563 (result (1+ (funcall (eval #'*) x real-zero))))
564 (assert (eql result (funcall fun x)))))))
566 ;;; (SIGNED-BYTE 1) [ returned from the logxor derive-type optimizer ]
567 ;;; wasn't recognized as a good type specifier.
568 (let ((fun (lambda (x y)
569 (declare (type (integer -1 0) x y) (optimize speed))
570 (logxor x y))))
571 (assert (= (funcall fun 0 0) 0))
572 (assert (= (funcall fun 0 -1) -1))
573 (assert (= (funcall fun -1 -1) 0)))
575 ;;; from PFD's torture test, triggering a bug in our effective address
576 ;;; treatment.
577 (compile
579 `(lambda (a b)
580 (declare (type (integer 8 22337) b))
581 (logandc2
582 (logandc2
583 (* (logandc1 (max -29303 b) 4) b)
584 (abs (logorc1 (+ (logandc1 -11 b) 2607688420) -31153924)))
585 (logeqv (max a 0) b))))
587 ;;; Alpha floating point modes weren't being reset after an exception,
588 ;;; leading to an exception on the second compile, below.
589 (compile nil '(lambda (x y) (declare (type (double-float 0.0d0) x y)) (/ x y)))
590 (handler-case (/ 1.0 0.0)
591 ;; provoke an exception
592 (arithmetic-error ()))
593 (compile nil '(lambda (x y) (declare (type (double-float 0.0d0) x y)) (/ x y)))
595 ;;; bug reported by Paul Dietz: component last block does not have
596 ;;; start ctran
597 (compile nil
598 '(lambda ()
599 (declare (notinline + logand)
600 (optimize (speed 0)))
601 (LOGAND
602 (BLOCK B5
603 (FLET ((%F1 ()
604 (RETURN-FROM B5 -220)))
605 (LET ((V7 (%F1)))
606 (+ 359749 35728422))))
607 -24076)))
609 ;;; bug 294 reported by Paul Dietz: miscompilation of REM and MOD
610 (assert (= (funcall (compile nil `(lambda (b)
611 (declare (optimize (speed 3))
612 (type (integer 2 152044363) b))
613 (rem b (min -16 0))))
614 108251912)
617 (assert (= (funcall (compile nil `(lambda (c)
618 (declare (optimize (speed 3))
619 (type (integer 23062188 149459656) c))
620 (mod c (min -2 0))))
621 95019853)
622 -1))
624 ;;; bug reported by Paul Dietz: block splitting inside FLUSH-DEAD-CODE
625 (compile nil
626 '(LAMBDA (A B C)
627 (BLOCK B6
628 (LOGEQV (REM C -6758)
629 (REM B (MAX 44 (RETURN-FROM B6 A)))))))
631 (compile nil '(lambda ()
632 (block nil
633 (flet ((foo (x y) (if (> x y) (print x) (print y))))
634 (foo 1 2)
635 (bar)
636 (foo (return 14) 2)))))
638 ;;; bug in Alpha backend: not enough sanity checking of arguments to
639 ;;; instructions
640 (assert (= (funcall (compile nil
641 '(lambda (x)
642 (declare (fixnum x))
643 (ash x -257)))
644 1024)
647 ;;; bug found by WHN and pfdietz: compiler failure while referencing
648 ;;; an entry point inside a deleted lambda
649 (compile nil '(lambda ()
650 (let (r3533)
651 (flet ((bbfn ()
652 (setf r3533
653 (progn
654 (flet ((truly (fn bbd)
655 (let (r3534)
656 (let ((p3537 nil))
657 (unwind-protect
658 (multiple-value-prog1
659 (progn
660 (setf r3534
661 (progn
662 (bubf bbd t)
663 (flet ((c-3536 ()
664 (funcall fn)))
665 (cdec #'c-3536
666 (vector bbd))))))
667 (setf p3537 t))
668 (unless p3537
669 (error "j"))))
670 r3534))
671 (c (pd) (pdc pd)))
672 (let ((a (smock a))
673 (b (smock b))
674 (b (smock c)))))))))
675 (wum #'bbfn "hc3" (list)))
676 r3533)))
677 (compile nil '(lambda () (flet ((%f () (unwind-protect nil))) nil)))
679 ;;; the strength reduction of constant multiplication used (before
680 ;;; sbcl-0.8.4.x) to lie to the compiler. This meant that, under
681 ;;; certain circumstances, the compiler would derive that a perfectly
682 ;;; reasonable multiplication never returned, causing chaos. Fixed by
683 ;;; explicitly doing modular arithmetic, and relying on the backends
684 ;;; being smart.
685 (assert (= (funcall
686 (compile nil
687 '(lambda (x)
688 (declare (type (integer 178956970 178956970) x)
689 (optimize speed))
690 (* x 24)))
691 178956970)
692 4294967280))
694 ;;; bug in modular arithmetic and type specifiers
695 (assert (= (funcall (compile nil (lambda (x) (logand x x 0)))
699 ;;; MISC.99 from Paul Dietz' random tester: FAST-ASH-MOD32-C VOP
700 ;;; produced wrong result for shift >=32 on X86
701 (assert (= 0 (funcall
702 (compile nil
703 '(lambda (a)
704 (declare (type (integer 4303063 101130078) a))
705 (mask-field (byte 18 2) (ash a 77))))
706 57132532)))
708 ;;; MISC.101 and MISC.103: FLUSH-DEST did not mark the USE's block for
709 ;;; type check regeneration
710 (assert (eql (funcall
711 (compile nil '(lambda (a c)
712 (declare (type (integer 185501219873 303014665162) a))
713 (declare (type (integer -160758 255724) c))
714 (declare (optimize (speed 3)))
715 (let ((v8
716 (- -554046873252388011622614991634432
717 (ignore-errors c)
718 (unwind-protect 2791485))))
719 (max (ignore-errors a)
720 (let ((v6 (- v8 (restart-case 980))))
721 (min v8 v6))))))
722 259448422916 173715)
723 259448422916))
724 (assert (eql (funcall
725 (compile nil '(lambda (a b)
726 (min -80
727 (abs
728 (ignore-errors
730 (logeqv b
731 (block b6
732 (return-from b6
733 (load-time-value -6876935))))
734 (if (logbitp 1 a) b (setq a -1522022182249))))))))
735 -1802767029877 -12374959963)
736 -80))
738 ;;; various MISC.*, related to NODEs/LVARs with derived type NIL
739 (assert (eql (funcall (compile nil '(lambda (c)
740 (declare (type (integer -3924 1001809828) c))
741 (declare (optimize (speed 3)))
742 (min 47 (if (ldb-test (byte 2 14) c)
743 -570344431
744 (ignore-errors -732893970)))))
745 705347625)
746 -570344431))
747 (assert (eql (funcall
748 (compile nil '(lambda (b)
749 (declare (type (integer -1598566306 2941) b))
750 (declare (optimize (speed 3)))
751 (max -148949 (ignore-errors b))))
754 (assert (eql (funcall
755 (compile nil '(lambda (b c)
756 (declare (type (integer -4 -3) c))
757 (block b7
758 (flet ((%f1 (f1-1 f1-2 f1-3)
759 (if (logbitp 0 (return-from b7
760 (- -815145138 f1-2)))
761 (return-from b7 -2611670)
762 99345)))
763 (let ((v2 (%f1 -2464 (%f1 -1146 c c) -2)))
764 b)))))
765 2950453607 -4)
766 -815145134))
767 (assert (eql (funcall
768 (compile nil
769 '(lambda (b c)
770 (declare (type (integer -29742055786 23602182204) b))
771 (declare (type (integer -7409 -2075) c))
772 (declare (optimize (speed 3)))
773 (floor
774 (labels ((%f2 ()
775 (block b6
776 (ignore-errors (return-from b6
777 (if (= c 8) b 82674))))))
778 (%f2)))))
779 22992834060 -5833)
780 82674))
781 (assert (equal (multiple-value-list
782 (funcall
783 (compile nil '(lambda (a)
784 (declare (type (integer -944 -472) a))
785 (declare (optimize (speed 3)))
786 (round
787 (block b3
788 (return-from b3
789 (if (= 55957 a) -117 (ignore-errors
790 (return-from b3 a))))))))
791 -589))
792 '(-589 0)))
794 ;;; MISC.158
795 (assert (zerop (funcall
796 (compile nil
797 '(lambda (a b c)
798 (declare (type (integer 79828 2625480458) a))
799 (declare (type (integer -4363283 8171697) b))
800 (declare (type (integer -301 0) c))
801 (if (equal 6392154 (logxor a b))
802 1706
803 (let ((v5 (abs c)))
804 (logand v5
805 (logior (logandc2 c v5)
806 (common-lisp:handler-case
807 (ash a (min 36 22477)))))))))
808 100000 0 0)))