b5d651224629136b53de6a0f204d173fb556f85f
[sbcl.git] / tests / compiler.impure.lisp
1 ;;;; This file is for compiler tests which have side effects (e.g.
2 ;;;; executing DEFUN) but which don't need any special side-effecting
3 ;;;; environmental stuff (e.g. DECLAIM of particular optimization
4 ;;;; settings). Similar tests which *do* expect special settings may
5 ;;;; be in files compiler-1.impure.lisp, compiler-2.impure.lisp, etc.
6
7 ;;;; This software is part of the SBCL system. See the README file for
8 ;;;; more information.
9 ;;;;
10 ;;;; While most of SBCL is derived from the CMU CL system, the test
11 ;;;; files (like this one) were written from scratch after the fork
12 ;;;; from CMU CL.
13 ;;;;
14 ;;;; This software is in the public domain and is provided with
15 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
16 ;;;; more information.
17
18 (when (eq sb-ext:*evaluator-mode* :interpret)
19   (sb-ext:exit :code 104))
20
21 (load "test-util.lisp")
22 (load "compiler-test-util.lisp")
23 (load "assertoid.lisp")
24 (use-package "TEST-UTIL")
25 (use-package "ASSERTOID")
26
27 ;;; Old CMU CL code assumed that the names of "keyword" arguments are
28 ;;; necessarily self-evaluating symbols, but ANSI Common Lisp allows
29 ;;; them to be any symbols, not necessarily keywords, and thus not
30 ;;; necessarily self-evaluating. Make sure that this works.
31 (defun newfangled-cons (&key ((left-thing x)) ((right-thing y)))
32   (cons x y))
33 (assert (equal (cons 1 2) (newfangled-cons 'right-thing 2 'left-thing 1)))
34
35 ;;; ANSI specifically says that duplicate keys are OK in lambda lists,
36 ;;; with no special exception for macro lambda lists. (As reported by
37 ;;; Pierre Mai on cmucl-imp 2001-03-30, Python didn't think so. The
38 ;;; rest of the thread had some entertainment value, at least for me
39 ;;; (WHN). The unbelievers were besmote and now even CMU CL will
40 ;;; conform to the spec in this regard. Who needs diplomacy when you
41 ;;; have brimstone?:-)
42 (defmacro ayup-duplicate-keys-are-ok-i-see-the-lite (&key k)
43   k)
44 (assert (equal (ayup-duplicate-keys-are-ok-i-see-the-lite :k 112) 112))
45 (assert (equal (ayup-duplicate-keys-are-ok-i-see-the-lite :k 'x :k 'y) 'x))
46
47 ;;; As reported by Alexey Dejneka (sbcl-devel 2002-01-30), in
48 ;;; sbcl-0.7.1 plus his patch (i.e. essentially sbcl-0.7.1.2), the
49 ;;; compiler barfed on this, blowing up in FIND-IN-PHYSENV looking for
50 ;;; the LAMBDA-VAR named NUM. That was fixed in sbcl-0.7.1.3.
51 (defun parse-num (index)
52   (let (num x)
53     (flet ((digs ()
54              (setq num index))
55            (z ()
56              (let ()
57                (setq x nil))))
58       (when (and (digs) (digs)) x))))
59
60 ;;; Bug 132: The compiler used to fail to compile INTEGER-valued CATCH
61 ;;; tags. This was fixed by Alexey Dejneka in sbcl-0.7.1.14. (INTEGER
62 ;;; catch tags are still a bad idea because EQ is used to compare
63 ;;; tags, and EQ comparison on INTEGERs is unportable; but now it's a
64 ;;; compiler warning instead of a failure to compile.)
65 (defun foo ()
66   (catch 0 (print 1331)))
67
68 ;;; Bug 150: In sbcl-0.7.1.15, compiling this code caused a failure in
69 ;;; SB-C::ADD-TEST-CONSTRAINTS:
70 ;;;    The value NIL is not of type SB-C::CONTINUATION.
71 ;;; This bug was fixed by APD in sbcl-0.7.1.30.
72 (defun bug150-test1 ()
73   (let* ()
74     (flet ((wufn () (glorp table1 4.9)))
75       (gleep *uustk* #'wufn "#1" (list)))
76     (if (eql (lo foomax 3.2))
77         (values)
78         (error "not ~S" '(eql (lo foomax 3.2))))
79     (values)))
80 ;;; A simpler test case for bug 150: The compiler died with the
81 ;;; same type error when trying to compile this.
82 (defun bug150-test2 ()
83   (let ()
84     (<)))
85
86 ;;; bug 147, fixed by APD 2002-04-28
87 ;;;
88 ;;; This test case used to crash the compiler, e.g. with
89 ;;;   failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)"
90 (defun bug147 (string ind)
91   (flet ((digs ()
92            (let (old-index)
93              (if (and (< ind ind)
94                       (typep (char string ind) '(member #\1)))
95                  nil))))))
96
97 ;;; bug reported and fixed by Matthias Hoelzl sbcl-devel 2002-05-13
98 (defmacro foo-2002-05-13 () ''x)
99 (eval '(foo-2002-05-13))
100 (compile 'foo-2002-05-13)
101 (foo-2002-05-13) ; (The bug caused UNDEFINED-FUNCTION to be signalled here.)
102
103 ;;; floating point pain on the PPC.
104 ;;;
105 ;;; This test case used to fail to compile on most powerpcs prior to
106 ;;; sbcl-0.7.4.2x, as floating point traps were being incorrectly
107 ;;; masked.
108 (defun floating-point-pain (x)
109   (declare (single-float x))
110   (log x))
111
112 ;;; bug found and fixed ca. sbcl-0.7.5.12: The INTERSECTION-TYPE
113 ;;; here satisfies "is a subtype of ARRAY-TYPE", but can't be
114 ;;; accessed with ARRAY-TYPE accessors like
115 ;;; ARRAY-TYPE-SPECIALIZED-ELEMENT-TYPE, so ARRAY-related
116 ;;; DEFTRANSFORMs died with TYPE-ERROR at compile time when
117 ;;; compiling the DEFUN here.
118 (defun stupid-input-to-smart-array-deftransforms-0-7-5-12 (v)
119   (declare (type (and simple-vector fwd-type-ref) v))
120   (aref v 0))
121
122 ;;; Ca. sbcl-0.7.5.15 the compiler would fail an internal consistency
123 ;;; check on this code because it expected all calls to %INSTANCE-REF
124 ;;; to be transformed away, but its expectations were dashed by perverse
125 ;;; code containing app programmer errors like this.
126 (defstruct something-known-to-be-a-struct x y)
127 (multiple-value-bind (fun warnings-p failure-p)
128     (compile nil
129              '(lambda ()
130                 (labels ((a1 (a2 a3)
131                              (cond (t (a4 a2 a3))))
132                          (a4 (a2 a3 a5 a6)
133                              (declare (type (or simple-vector null) a5 a6))
134                              (something-known-to-be-a-struct-x a5))
135                          (a8 (a2 a3)
136                              (a9 #'a1 a10 a2 a3))
137                          (a11 (a2 a3)
138                               (cond ((and (funcall a12 a2)
139                                           (funcall a12 a3))
140                                      (funcall a13 a2 a3))
141                                     (t
142                                      (when a14
143                                      (let ((a15 (a1 a2 a3)))
144                                        ))
145                                      a16))))
146                   (values #'a17 #'a11))))
147   ;; Python sees the structure accessor on the known-not-to-be-a-struct
148   ;; A5 value and is very, very disappointed in you. (But it doesn't
149   ;; signal BUG any more.)
150   (assert failure-p))
151
152 ;;; On the SPARC, there was an erroneous definition of some VOPs used
153 ;;; to compile LOGANDs, which would lead to compilation of the
154 ;;; following function giving rise to a compile-time error (bug
155 ;;; spotted and fixed by Raymond Toy for CMUCL)
156 (defun logand-sparc-bogons (a0 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
157   (declare (type (unsigned-byte 32) a0)
158            (type (signed-byte 32) a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
159            ;; to ensure that the call is a candidate for
160            ;; transformation
161            (optimize (speed 3) (safety 0) (compilation-speed 0) (debug 0)))
162   (values
163    ;; the call that fails compilation
164    (logand a0 a10)
165    ;; a call to prevent the other arguments from being optimized away
166    (logand a1 a2 a3 a4 a5 a6 a7 a8 a9)))
167
168 ;;; bug 192, reported by Einar Floystad Dorum sbcl-devel 2002-08-14,
169 ;;; fixed in sbcl-0.7.6.26: Compiling this function in 0.7.6 caused
170 ;;; the compiler to try to constant-fold DATA-VECTOR-REF, which is OK,
171 ;;; except that there was no non-VOP definition of DATA-VECTOR-REF, so
172 ;;; it would fail.
173 (defun bug192 ()
174       (funcall
175        (LAMBDA (TEXT I L )
176          (LABELS ((G908 (I)
177                     (LET ((INDEX
178                            (OR
179                             (IF (= I L)
180                                 NIL
181                                 (LET ((S TEXT)
182                                       (E (ELT TEXT I)))
183                                   (DECLARE (IGNORABLE S E))
184                                   (WHEN (EQL #\a E)
185                                     (G909 (1+ I))))))))
186                       INDEX))
187                   (G909 (I)
188                     (OR
189                      (IF (= I L)
190                          NIL
191                          (LET ((S TEXT)
192                                (E (ELT TEXT I)))
193                            (DECLARE (IGNORABLE S E))
194                            (WHEN (EQL #\b E) (G910 (1+ I)))))))
195                   (G910 (I)
196                     (LET ((INDEX
197                            (OR
198                             (IF NIL
199                                 NIL
200                                 (LET ((S TEXT))
201                                   (DECLARE (IGNORABLE S))
202                                   (WHEN T I))))))
203                       INDEX)))
204            (G908 I))) "abcdefg" 0 (length "abcdefg")))
205
206 ;;; bugs #65, #70, and #109, closed by APD's patch sbcl-devel 2002-08-17
207 ;;;
208 ;;; This was "YA code deletion bug" whose symptom was the failure of
209 ;;; the assertion
210 ;;;   (EQ (C::LAMBDA-TAIL-SET C::CALLER)
211 ;;;       (C::LAMBDA-TAIL-SET (C::LAMBDA-HOME C::CALLEE)))
212 ;;; at compile time.
213 (defun bug65-1 (termx termy) ; from Carl Witty on submit bugs list, debian.org
214   (labels
215     ((alpha-equal-bound-term-lists (listx listy)
216        (or (and (null listx) (null listy))
217            (and listx listy
218                 (let ((bindings-x (bindings-of-bound-term (car listx)))
219                       (bindings-y (bindings-of-bound-term (car listy))))
220                   (if (and (null bindings-x) (null bindings-y))
221                       (alpha-equal-terms (term-of-bound-term (car listx))
222                                          (term-of-bound-term (car listy)))
223                       (and (= (length bindings-x) (length bindings-y))
224                            (prog2
225                                (enter-binding-pairs (bindings-of-bound-term (car listx))
226                                                     (bindings-of-bound-term (car listy)))
227                                (alpha-equal-terms (term-of-bound-term (car listx))
228                                                   (term-of-bound-term (car listy)))
229                              (exit-binding-pairs (bindings-of-bound-term (car listx))
230                                                  (bindings-of-bound-term (car listy)))))))
231                 (alpha-equal-bound-term-lists (cdr listx) (cdr listy)))))
232
233      (alpha-equal-terms (termx termy)
234        (if (and (variable-p termx)
235                 (variable-p termy))
236            (equal-bindings (id-of-variable-term termx)
237                            (id-of-variable-term termy))
238            (and (equal-operators-p (operator-of-term termx) (operator-of-term termy))
239                 (alpha-equal-bound-term-lists (bound-terms-of-term termx)
240                                               (bound-terms-of-term termy))))))
241
242     (or (eq termx termy)
243         (and termx termy
244              (with-variable-invocation (alpha-equal-terms termx termy))))))
245 (defun bug65-2 () ; from Bob Rogers cmucl-imp 1999-07-28
246   ;; Given an FSSP alignment file named by the argument . . .
247   (labels ((get-fssp-char ()
248              (get-fssp-char))
249            (read-fssp-char ()
250              (get-fssp-char)))
251     ;; Stub body, enough to tickle the bug.
252     (list (read-fssp-char)
253           (read-fssp-char))))
254 (defun bug70 ; from David Young cmucl-help 30 Nov 2000
255     (item sequence &key (test #'eql))
256   (labels ((find-item (obj seq test &optional (val nil))
257                       (let ((item (first seq)))
258                         (cond ((null seq)
259                                (values nil nil))
260                               ((funcall test obj item)
261                                (values val seq))
262                               (t
263                                (find-item obj
264                                           (rest seq)
265                                           test
266                                           (nconc val `(,item))))))))
267     (find-item item sequence test)))
268 (defun bug109 () ; originally from CMU CL bugs collection, reported as
269                  ; SBCL bug by MNA 2001-06-25
270   (labels
271       ((eff (&key trouble)
272             (eff)
273             ;; nil
274             ;; Uncomment and it works
275             ))
276     (eff)))
277
278 ;;; bug 192a, fixed by APD "more strict type checking" patch
279 ;;; (sbcl-devel 2002-08-07)
280 (defun bug192a (x)
281   (declare (optimize (speed 0) (safety 3)))
282   ;; Even with bug 192a, this declaration was checked as an assertion.
283   (declare (real x))
284   (+ x
285      (locally
286        ;; Because of bug 192a, this declaration was trusted without checking.
287        (declare (single-float x))
288        (sin x))))
289 (assert (null (ignore-errors (bug192a nil))))
290 (multiple-value-bind (result error) (ignore-errors (bug192a 100))
291   (assert (null result))
292   (assert (equal (type-error-expected-type error) 'single-float)))
293
294 ;;; bug 194, fixed in part by APD "more strict type checking" patch
295 ;;; (sbcl-devel 2002-08-07)
296 (progn
297   (multiple-value-bind (result error)
298       (ignore-errors (multiple-value-prog1 (progn (the real '(1 2 3)))))
299     (assert (null result))
300     (assert (typep error 'type-error)))
301   (multiple-value-bind (result error)
302       (ignore-errors (the real '(1 2 3)))
303     (assert (null result))
304     (assert (typep error 'type-error))))
305
306 (defun bug194d ()
307   (null (ignore-errors
308           (let ((arg1 1)
309                 (arg2 (identity (the real #(1 2 3)))))
310             (if (< arg1 arg2) arg1 arg2)))))
311 (assert (eq (bug194d) t))
312
313 \f
314 ;;; BUG 48a. and b. (symbol-macrolet handling), fixed by Eric Marsden
315 ;;; and Raymond Toy for CMUCL, fix ported for sbcl-0.7.6.18.
316 (multiple-value-bind (function warnings-p failure-p)
317     (compile nil '(lambda ()
318                    ;; not interested in the package lock violation here
319                    (declare (sb-ext:disable-package-locks t))
320                    (symbol-macrolet ((t nil)) t)))
321   (assert failure-p)
322   (assert (raises-error? (funcall function) program-error)))
323 (multiple-value-bind (function warnings-p failure-p)
324     (compile nil
325              '(lambda ()
326                ;; not interested in the package lock violation here
327                (declare (sb-ext:disable-package-locks *standard-input*))
328                 (symbol-macrolet ((*standard-input* nil))
329                   *standard-input*)))
330   (assert failure-p)
331   (assert (raises-error? (funcall function) program-error)))
332 (multiple-value-bind (function warnings-p failure-p)
333     (compile nil '(lambda () (symbol-macrolet ((s nil)) (declare (special s)) s)))
334   (assert failure-p)
335   (assert (raises-error? (funcall function) program-error)))
336 \f
337 ;;; bug 120a: Turned out to be constraining code looking like (if foo
338 ;;; <X> <X>) where <X> was optimized by the compiler to be the exact
339 ;;; same block in both cases, but not turned into (PROGN FOO <X>).
340 ;;; Fixed by APD in sbcl-0.7.7.2, who provided this test:
341 (declaim (inline dont-constrain-if-too-much))
342 (defun dont-constrain-if-too-much (frame up-frame)
343   (declare (optimize (speed 3) (safety 1) (debug 1)))
344   (if (or (not frame) t)
345       frame
346       "bar"))
347 (defun dont-constrain-if-too-much-aux (x y)
348   (declare (optimize (speed 3) (safety 1) (debug 1)))
349   (if x t (if y t (dont-constrain-if-too-much x y))))
350
351 (assert (null (dont-constrain-if-too-much-aux nil nil)))
352
353 ;;; TYPE-ERROR confusion ca. sbcl-0.7.7.24, reported and fixed by
354 ;;; APD sbcl-devel 2002-09-14
355 (defun exercise-0-7-7-24-bug (x)
356   (declare (integer x))
357   (let (y)
358     (setf y (the single-float (if (> x 0) x 3f0)))
359     (list y y)))
360 (multiple-value-bind (v e) (ignore-errors (exercise-0-7-7-24-bug 4))
361   (assert (null v))
362   (assert (typep e 'type-error)))
363 (assert (equal (exercise-0-7-7-24-bug -4) '(3f0 3f0)))
364
365 ;;; non-intersecting type declarations were DWIMing in a confusing
366 ;;; fashion until sbcl-0.7.7.28, when APD reported and fixed the
367 ;;; problem.
368 (defun non-intersecting-the (x)
369   (let (y)
370     (setf y (the single-float (the integer x)))
371     (list y y)))
372
373 (raises-error? (foo 3) type-error)
374 (raises-error? (foo 3f0) type-error)
375
376 ;;; until 0.8.2 SBCL did not check THEs in arguments
377 (defun the-in-arguments-aux (x)
378   x)
379 (defun the-in-arguments-1 (x)
380   (list x (the-in-arguments-aux (the (single-float 0s0) x))))
381 (defun the-in-arguments-2 (x)
382   (list x (the-in-arguments-aux (the single-float x))))
383
384 (multiple-value-bind (result condition)
385     (ignore-errors (the-in-arguments-1 1))
386   (assert (null result))
387   (assert (typep condition 'type-error)))
388 (multiple-value-bind (result condition)
389     (ignore-errors (the-in-arguments-2 1))
390   (assert (null result))
391   (assert (typep condition 'type-error)))
392
393 ;;; bug 153: a hole in a structure slot type checking
394 (declaim (optimize safety))
395 (defstruct foo153
396   (bla 0 :type fixnum))
397 (defun bug153-1 ()
398   (let ((foo (make-foo153)))
399     (setf (foo153-bla foo) '(1 . 1))
400     (format t "Is ~a of type ~a a cons? => ~a~%"
401             (foo153-bla foo)
402             (type-of (foo153-bla foo))
403             (consp (foo153-bla foo)))))
404 (defun bug153-2 (x)
405   (let ((foo (make-foo153)))
406     (setf (foo153-bla foo) x)
407     (format t "Is ~a of type ~a a cons? => ~a~%"
408             (foo153-bla foo)
409             (type-of (foo153-bla foo))
410             (consp (foo153-bla foo)))))
411
412 (multiple-value-bind (result condition)
413     (ignore-errors (bug153-1))
414   (declare (ignore result))
415   (assert (typep condition 'type-error)))
416 (multiple-value-bind (result condition)
417     (ignore-errors (bug153-2 '(1 . 1)))
418   (declare (ignore result))
419   (assert (typep condition 'type-error)))
420
421 ;;;; bug 110: the compiler flushed the argument type test and the default
422 ;;;; case in the cond.
423 ;
424 ;(locally (declare (optimize (safety 3) (speed 2)))
425 ;  (defun bug110 (x)
426 ;    (declare (optimize (safety 2) (speed 3)))
427 ;    (declare (type (or string stream) x))
428 ;    (cond ((typep x 'string) 'string)
429 ;          ((typep x 'stream) 'stream)
430 ;          (t
431 ;           'none))))
432 ;
433 ;(multiple-value-bind (result condition)
434 ;    (ignore-errors (bug110 0))
435 ;  (declare (ignore result))
436 ;  (assert (typep condition 'type-error)))
437
438 ;;; bug 202: the compiler failed to compile a function, which derived
439 ;;; type contradicted declared.
440 (declaim (ftype (function () null) bug202))
441 (defun bug202 ()
442   t)
443
444 ;;; bugs 178, 199: compiler failed to compile a call of a function
445 ;;; with a hairy type
446 (defun bug178 (x)
447       (funcall (the function (the standard-object x))))
448
449 (defun bug199-aux (f)
450   (eq nil (funcall f)))
451
452 (defun bug199 (f x)
453   (declare (type (and function (satisfies bug199-aux)) f))
454   (funcall f x))
455
456 ;;; check non-toplevel DEFMACRO
457 (defvar *defmacro-test-status* nil)
458
459 (defun defmacro-test ()
460   (fmakunbound 'defmacro-test-aux)
461   (let* ((src "defmacro-test.lisp")
462          (obj (compile-file-pathname src)))
463     (unwind-protect
464          (progn
465            (compile-file src)
466            (assert (equal *defmacro-test-status* '(function a)))
467            (setq *defmacro-test-status* nil)
468            (load obj)
469            (assert (equal *defmacro-test-status* nil))
470            (macroexpand '(defmacro-test-aux 'a))
471            (assert (equal *defmacro-test-status* '(macro 'a z-value)))
472            (eval '(defmacro-test-aux 'a))
473            (assert (equal *defmacro-test-status* '(expanded 'a z-value))))
474       (ignore-errors (delete-file obj)))))
475
476 (defmacro-test)
477
478 ;;; bug 204: EVAL-WHEN inside a local environment
479 (defvar *bug204-test-status*)
480
481 (defun bug204-test ()
482   (let* ((src "bug204-test.lisp")
483          (obj (compile-file-pathname src)))
484     (unwind-protect
485          (progn
486            (setq *bug204-test-status* nil)
487            (compile-file src)
488            (assert (equal *bug204-test-status* '((:expanded :load-toplevel)
489                                                  (:called :compile-toplevel)
490                                                  (:expanded :compile-toplevel))))
491            (setq *bug204-test-status* nil)
492            (load obj)
493            (assert (equal *bug204-test-status* '((:called :load-toplevel)))))
494       (ignore-errors (delete-file obj)))))
495
496 (bug204-test)
497
498 ;;; toplevel SYMBOL-MACROLET
499 (defvar *symbol-macrolet-test-status*)
500
501 (defun symbol-macrolet-test ()
502   (let* ((src "symbol-macrolet-test.lisp")
503          (obj (compile-file-pathname src)))
504     (unwind-protect
505          (progn
506            (setq *symbol-macrolet-test-status* nil)
507            (compile-file src)
508            (assert (equal *symbol-macrolet-test-status*
509                           '(2 1)))
510            (setq *symbol-macrolet-test-status* nil)
511            (load obj)
512            (assert (equal *symbol-macrolet-test-status* '(2))))
513       (ignore-errors (delete-file obj)))))
514
515 (symbol-macrolet-test)
516
517 ;;; On the x86, this code failed to compile until sbcl-0.7.8.37:
518 (defun x86-assembler-failure (x)
519   (declare (optimize (speed 3) (safety 0)))
520   (eq (setf (car x) 'a) nil))
521
522 ;;; bug 211: :ALLOW-OTHER-KEYS
523 (defun bug211d (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
524   (list x x-p y y-p))
525
526 (assert (equal (bug211d) '(:x nil :y nil)))
527 (assert (equal (bug211d :x 1) '(1 t :y nil)))
528 (assert (raises-error? (bug211d :y 2) program-error))
529 (assert (equal (bug211d :y 2 :allow-other-keys t :allow-other-keys nil)
530                '(:x nil t t)))
531 (assert (raises-error? (bug211d :y 2 :allow-other-keys nil) program-error))
532
533 (let ((failure-p
534        (nth-value
535         3
536         (compile 'bug211b
537                  '(lambda ()
538                    (flet ((test (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
539                             (list x x-p y y-p)))
540                      (assert (equal (test) '(:x nil :y nil)))
541                      (assert (equal (test :x 1) '(1 t :y nil)))
542                      (assert (equal (test :y 2 :allow-other-keys 11 :allow-other-keys nil)
543                                     '(:x nil 11 t)))))))))
544   (assert (not failure-p))
545   (bug211b))
546
547 (let ((failure-p
548        (nth-value
549         3
550         (compile 'bug211c
551                  '(lambda ()
552                    (flet ((test (&key (x :x x-p))
553                             (list x x-p)))
554                      (assert (equal (test) '(:x nil)))
555                      (assert (equal (test :x 1) '(1 t)))
556                      (assert (equal (test :y 2 :allow-other-keys 11 :allow-other-keys nil)
557                                     '(:x nil)))))))))
558   (assert (not failure-p))
559   (bug211c))
560
561 (dolist (form '((test :y 2)
562                 (test :y 2 :allow-other-keys nil)
563                 (test :y 2 :allow-other-keys nil :allow-other-keys t)))
564   (multiple-value-bind (result warnings-p failure-p)
565       (compile nil `(lambda ()
566                      (flet ((test (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
567                               (list x x-p y y-p)))
568                        ,form)))
569     (assert failure-p)
570     (assert (raises-error? (funcall result) program-error))))
571
572 ;;; bug 217: wrong type inference
573 (defun bug217-1 (x s)
574   (let ((f (etypecase x
575              (character #'write-char)
576              (integer #'write-byte))))
577     (funcall f x s)
578     (etypecase x
579       (character (write-char x s))
580       (integer (write-byte x s)))))
581 (bug217-1 #\1 *standard-output*)
582
583
584 ;;; bug 221: tried and died on CSUBTYPEP (not VALUES-SUBTYPEP) of the
585 ;;; function return types when inferring the type of the IF expression
586 (declaim (ftype (function (fixnum) (values package boolean)) bug221f1))
587 (declaim (ftype (function (t) (values package boolean)) bug221f2))
588 (defun bug221 (b x)
589   (funcall (if b #'bug221f1 #'bug221f2) x))
590 \f
591 ;;; bug 172: macro lambda lists were too permissive until 0.7.9.28
592 ;;; (fix provided by Matthew Danish) on sbcl-devel
593 (assert (null (ignore-errors
594                 (defmacro bug172 (&rest rest foo) `(list ,rest ,foo)))))
595
596 ;;; embedded THEs
597 (defun check-embedded-thes (policy1 policy2 x y)
598   (handler-case
599       (funcall (compile nil
600                         `(lambda (f)
601                            (declare (optimize (speed 2) (safety ,policy1)))
602                            (multiple-value-list
603                             (the (values (integer 2 3) t &optional)
604                               (locally (declare (optimize (safety ,policy2)))
605                                 (the (values t (single-float 2f0 3f0) &optional)
606                                   (funcall f)))))))
607                (lambda () (values x y)))
608     (type-error (error)
609       error)))
610
611 (assert (equal (check-embedded-thes 0 0  :a :b) '(:a :b)))
612
613 (assert (equal (check-embedded-thes 0 3  :a 2.5f0) '(:a 2.5f0)))
614 (assert (typep (check-embedded-thes 0 3  2 3.5f0) 'type-error))
615
616 (assert (equal (check-embedded-thes 0 1  :a 3.5f0) '(:a 3.5f0)))
617 (assert (typep (check-embedded-thes 0 1  2 2.5d0) 'type-error))
618
619 (assert (equal (check-embedded-thes 3 0  2 :a) '(2 :a)))
620 (assert (typep (check-embedded-thes 3 0  4 2.5f0) 'type-error))
621
622 (assert (equal (check-embedded-thes 1 0  3 :b) '(3 :b)))
623 (assert (typep (check-embedded-thes 1 0  1.0 2.5f0) 'type-error))
624
625
626 (assert (equal (check-embedded-thes 3 3  2 2.5f0) '(2 2.5f0)))
627 (assert (typep (check-embedded-thes 3 3  0 2.5f0) 'type-error))
628 (assert (typep (check-embedded-thes 3 3  2 3.5f0) 'type-error))
629 \f
630 ;;; INLINE inside MACROLET
631 (declaim (inline to-be-inlined))
632 (macrolet ((def (x) `(defun ,x (y) (+ y 1))))
633   (def to-be-inlined))
634 (defun call-inlined (z)
635   (to-be-inlined z))
636 (assert (= (call-inlined 3) 4))
637 (macrolet ((frob (x) `(+ ,x 3)))
638   (defun to-be-inlined (y)
639     (frob y)))
640 (assert (= (call-inlined 3)
641            ;; we should have inlined the previous definition, so the
642            ;; new one won't show up yet.
643            4))
644 (defun call-inlined (z)
645   (to-be-inlined z))
646 (assert (= (call-inlined 3) 6))
647 (defun to-be-inlined (y)
648   (+ y 5))
649 (assert (= (call-inlined 3) 6))
650 \f
651 ;;; DEFINE-COMPILER-MACRO to work as expected, not via weird magical
652 ;;; IR1 pseudo-:COMPILE-TOPLEVEL handling
653 (defvar *bug219-a-expanded-p* nil)
654 (defun bug219-a (x)
655   (+ x 1))
656 (define-compiler-macro bug219-a (&whole form y)
657   (setf *bug219-a-expanded-p* t)
658   (if (constantp y)
659       (+ (eval y) 2)
660       form))
661 (defun bug219-a-aux ()
662   (bug219-a 2))
663 (assert (= (bug219-a-aux)
664            (if *bug219-a-expanded-p* 4 3)))
665 (defvar *bug219-a-temp* 3)
666 (assert (= (bug219-a *bug219-a-temp*) 4))
667
668 (defvar *bug219-b-expanded-p* nil)
669 (defun bug219-b-aux1 (x)
670   (when x
671     (define-compiler-macro bug219-b (y)
672       (setf *bug219-b-expanded-p* t)
673       `(+ ,y 2))))
674 (defun bug219-b-aux2 (z)
675   (bug219-b z))
676 (assert (not *bug219-b-expanded-p*))
677 (assert (raises-error? (bug219-b-aux2 1) undefined-function))
678 (bug219-b-aux1 t)
679 (defun bug219-b-aux2 (z)
680   (bug219-b z))
681 (defun bug219-b (x)
682   x)
683 (assert (= (bug219-b-aux2 1)
684            (if *bug219-b-expanded-p* 3 1)))
685
686 ;;; bug 224: failure in unreachable code deletion
687 (defmacro do-optimizations (&body body)
688   `(dotimes (.speed. 4)
689      (dotimes (.space. 4)
690        (dotimes (.debug. 4)
691          (dotimes (.compilation-speed. 4)
692            (proclaim `(optimize (speed , .speed.) (space , .space.)
693                                 (debug , .debug.)
694                                 (compilation-speed , .compilation-speed.)))
695            ,@body)))))
696
697 (do-optimizations
698     (compile nil
699              (read-from-string
700               "(lambda () (#:localy (declare (optimize (safety 3)))
701                                     (ignore-errors (progn (values-list (car (list '(1 . 2)))) t))))")))
702
703 (do-optimizations
704     (compile nil '(lambda ()
705                    (labels ((ext ()
706                               (tagbody
707                                  (labels ((i1 () (list (i2) (i2)))
708                                           (i2 () (list (int) (i1)))
709                                           (int () (go :exit)))
710                                    (list (i1) (i1) (i1)))
711                                :exit (return-from ext)
712                                  )))
713                      (list (error "nih") (ext) (ext))))))
714
715 (do-optimizations
716   (compile nil '(lambda (x) (let ((y (error ""))) (list x y)))))
717
718 ;;; bug 223: invalid moving of global function name referencing
719 (defun bug223-int (n)
720   `(int ,n))
721
722 (defun bug223-wrap ()
723   (let ((old #'bug223-int))
724     (setf (fdefinition 'bug223-int)
725           (lambda (n)
726             (assert (> n 0))
727             `(ext ,@(funcall old (1- n)))))))
728 (compile 'bug223-wrap)
729
730 (assert (equal (bug223-int 4) '(int 4)))
731 (bug223-wrap)
732 (assert (equal (bug223-int 4) '(ext int 3)))
733 (bug223-wrap)
734 (assert (equal (bug223-int 4) '(ext ext int 2)))
735 \f
736 ;;; COERCE got its own DEFOPTIMIZER which has to reimplement most of
737 ;;; SPECIFIER-TYPE-NTH-ARG.  For a while, an illegal type would throw
738 ;;; you into the debugger on compilation.
739 (defun coerce-defopt1 (x)
740   ;; illegal, but should be compilable.
741   (coerce x '(values t)))
742 (defun coerce-defopt2 (x)
743   ;; illegal, but should be compilable.
744   (coerce x '(values t &optional)))
745 (assert (null (ignore-errors (coerce-defopt1 3))))
746 (assert (null (ignore-errors (coerce-defopt2 3))))
747 \f
748 ;;; Oops.  In part of the (CATCH ..) implementation of DEBUG-RETURN,
749 ;;; it was possible to confuse the type deriver of the compiler
750 ;;; sufficiently that compiler invariants were broken (explained by
751 ;;; APD sbcl-devel 2003-01-11).
752
753 ;;; WHN's original report
754 (defun debug-return-catch-break1 ()
755   (with-open-file (s "/tmp/foo"
756                      :direction :output
757                      :element-type (list
758                                     'signed-byte
759                                     (1+
760                                      (integer-length most-positive-fixnum))))
761     (read-byte s)
762     (read-byte s)
763     (read-byte s)
764     (read-byte s)))
765
766 ;;; APD's simplified test case
767 (defun debug-return-catch-break2 (x)
768   (declare (type (vector (unsigned-byte 8)) x))
769   (setq *y* (the (unsigned-byte 8) (aref x 4))))
770 \f
771 ;;; FUNCTION-LAMBDA-EXPRESSION should return something that's COMPILE
772 ;;; can understand.  Here's a simple test for that on a function
773 ;;; that's likely to return a hairier list than just a lambda:
774 (macrolet ((def (fn) `(progn
775                        (declaim (inline ,fn))
776                        (defun ,fn (x) (1+ x)))))
777   (def bug228))
778 (let ((x (function-lambda-expression #'bug228)))
779   (when x
780     (assert (= (funcall (compile nil x) 1) 2))))
781
782 ;;;
783 (defun bug192b (i)
784   (dotimes (j i)
785     (declare (type (mod 4) i))
786     (unless (< i 5)
787       (print j))))
788 (assert (raises-error? (bug192b 6) type-error))
789
790 (defun bug192c (x y)
791   (locally (declare (type fixnum x y))
792     (+ x (* 2 y))))
793 (assert (raises-error? (bug192c 1.1 2) type-error))
794
795 (assert (raises-error? (progn (the real (list 1)) t) type-error))
796
797 (defun bug236 (a f)
798   (declare (optimize (speed 2) (safety 0)))
799   (+ 1d0
800      (the double-float
801        (multiple-value-prog1
802            (svref a 0)
803          (unless f (return-from bug236 0))))))
804 (assert (eql (bug236 #(4) nil) 0))
805
806 ;;; Bug reported by reported by rif on c.l.l 2003-03-05
807 (defun test-type-of-special-1 (x)
808   (declare (special x)
809            (fixnum x)
810            (optimize (safety 3)))
811   (list x))
812 (defun test-type-of-special-2 (x)
813   (declare (special x)
814            (fixnum x)
815            (optimize (safety 3)))
816   (list x (setq x (/ x 2)) x))
817 (assert (raises-error? (test-type-of-special-1 3/2) type-error))
818 (assert (raises-error? (test-type-of-special-2 3) type-error))
819 (assert (equal (test-type-of-special-2 8) '(8 4 4)))
820
821 ;;; bug which existed in 0.8alpha.0.4 for several milliseconds before
822 ;;; APD fixed it in 0.8alpha.0.5
823 (defun frob8alpha04 (x y)
824   (+ x y))
825 (defun baz8alpha04 (this kids)
826   (flet ((n-i (&rest rest)
827            ;; Removing the #+NIL here makes the bug go away.
828            #+nil (format t "~&in N-I REST=~S~%" rest)
829            (apply #'frob8alpha04 this rest)))
830     (n-i kids)))
831 ;;; failed in 0.8alpha.0.4 with "The value 13 is not of type LIST."
832 (assert (= (baz8alpha04 12 13) 25))
833
834 ;;; evaluation order in structure slot writers
835 (defstruct sswo
836   a b)
837 (let* ((i 0)
838        (s (make-sswo :a (incf i) :b (incf i)))
839        (l (list s :v)))
840   (assert (= (sswo-a s) 1))
841   (assert (= (sswo-b s) 2))
842   (setf (sswo-a (pop l)) (pop l))
843   (assert (eq l nil))
844   (assert (eq (sswo-a s) :v)))
845
846 (defun bug249 (x)
847   (flet ((bar (y)
848            (declare (fixnum y))
849            (incf x)))
850     (list (bar x) (bar x) (bar x))))
851
852 (assert (raises-error? (bug249 1.0) type-error))
853
854 ;;; bug reported by ohler on #lisp 2003-07-10
855 (defun bug-ohler-2003-07-10 (a b)
856   (declare (optimize (speed 0) (safety 3) (space 0)
857                      (debug 1) (compilation-speed 0)))
858   (adjoin a b))
859
860 ;;; bug reported by Doug McNaught on sbcl-devel 2003-09-14:
861 ;;; COMPILE-FILE did not bind *READTABLE*
862 (let* ((source "bug-doug-mcnaught-20030914.lisp")
863        (fasl (compile-file-pathname source)))
864   (labels ((check ()
865              (assert (null (get-macro-character #\]))))
866            (full-check ()
867              (check)
868              (assert (typep *bug-doug-mcnaught-20030914*
869                             '(simple-array (unsigned-byte 4) (*))))
870              (assert (equalp *bug-doug-mcnaught-20030914* #(1 2 3)))
871              (makunbound '*bug-doug-mcnaught-20030914*)))
872     (compile-file source)
873     (check)
874     (load fasl)
875     (full-check)
876     (load source)
877     (full-check)
878     (delete-file fasl)))
879 \f
880 (defun expt-derive-type-bug (a b)
881   (unless (< a b)
882     (truncate (expt a b))))
883 (assert (equal (multiple-value-list (expt-derive-type-bug 1 1))
884                '(1 0)))
885
886 ;;; Problems with type checking in functions with EXPLICIT-CHECK
887 ;;; attribute (reported by Peter Graves)
888 (loop for (fun . args) in '((= a) (/= a)
889                             (< a) (<= a) (> a) (>= a))
890       do (assert (raises-error? (apply fun args) type-error)))
891
892 (defclass broken-input-stream (sb-gray:fundamental-input-stream) ())
893 (defmethod sb-gray:stream-read-char ((stream broken-input-stream))
894   (throw 'break :broken))
895 (assert (eql (block return
896                (handler-case
897                    (catch 'break
898                      (funcall (eval ''peek-char)
899                               1 (make-instance 'broken-input-stream))
900                      :test-broken)
901                  (type-error (c)
902                    (return-from return :good))))
903              :good))
904 \f
905 ;;;; MUFFLE-CONDITIONS test (corresponds to the test in the manual)
906 (defvar *compiler-note-count* 0)
907 #-(or alpha x86-64) ; FIXME: make a better test!
908 (handler-bind ((sb-ext:compiler-note (lambda (c)
909                                        (declare (ignore c))
910                                        (incf *compiler-note-count*))))
911   (let ((fun
912          (compile nil
913                   '(lambda (x)
914                     (declare (optimize speed) (fixnum x))
915                     (declare (sb-ext:muffle-conditions sb-ext:compiler-note))
916                     (values (* x 5) ; no compiler note from this
917                      (locally
918                        (declare (sb-ext:unmuffle-conditions sb-ext:compiler-note))
919                        ;; this one gives a compiler note
920                        (* x -5)))))))
921     (assert (= *compiler-note-count* 1))
922     (assert (equal (multiple-value-list (funcall fun 1)) '(5 -5)))))
923 \f
924 (handler-case
925     (eval '(flet ((%f (&key) nil)) (%f nil nil)))
926   (error (c) :good)
927   (:no-error (val) (error "no error: ~S" val)))
928 (handler-case
929     (eval '(labels ((%f (&key x) x)) (%f nil nil)))
930   (error (c) :good)
931   (:no-error (val) (error "no error: ~S" val)))
932
933 ;;; PROGV must not bind constants, or violate declared types -- ditto for SET.
934 (assert (raises-error? (set pi 3)))
935 (assert (raises-error? (progv '(pi s) '(3 pi) (symbol-value x))))
936 (declaim (cons *special-cons*))
937 (assert (raises-error? (set '*special-cons* "nope") type-error))
938 (assert (raises-error? (progv '(*special-cons*) '("no hope") (car *special-cons*)) type-error))
939
940 ;;; No bogus warnings for calls to functions with complex lambda-lists.
941 (defun complex-function-signature (&optional x &rest y &key z1 z2)
942   (cons x y))
943 (with-test (:name :complex-call-doesnt-warn)
944   (handler-bind ((warning #'error))
945     (compile nil '(lambda (x) (complex-function-signature x :z1 1 :z2 2)))))
946
947 (with-test (:name :non-required-args-update-info)
948   (let ((name (gensym "NON-REQUIRE-ARGS-TEST"))
949         (*evaluator-mode* :compile))
950     (eval `(defun ,name (x) x))
951     (assert (equal '(function (t) (values t &optional))
952                    (sb-kernel:type-specifier (sb-int:info :function :type name))))
953     (eval `(defun ,name (x &optional y) (or x y)))
954     (assert (equal '(function (t &optional t) (values t &optional))
955                    (sb-kernel:type-specifier (sb-int:info :function :type name))))))
956
957 ;;;; inline & maybe inline nested calls
958
959 (defun quux-marker (x) x)
960 (declaim (inline foo-inline))
961 (defun foo-inline (x) (quux-marker x))
962 (declaim (maybe-inline foo-maybe-inline))
963 (defun foo-maybe-inline (x) (quux-marker x))
964 ;; Pretty horrible, but does the job
965 (defun count-full-calls (name function)
966   (let ((code (with-output-to-string (s)
967                 (disassemble function :stream s)))
968         (n 0))
969     (with-input-from-string (s code)
970       (loop for line = (read-line s nil nil)
971             while line
972             when (search name line)
973             do (incf n)))
974     n))
975
976 (with-test (:name :nested-inline-calls)
977   (let ((fun (compile nil `(lambda (x)
978                              (foo-inline (foo-inline (foo-inline x)))))))
979     (assert (= 0 (count-full-calls "FOO-INLINE" fun)))
980     (assert (= 3 (count-full-calls "QUUX-MARKER" fun)))))
981
982 (with-test (:name :nested-maybe-inline-calls)
983   (let ((fun (compile nil `(lambda (x)
984                              (declare (optimize (space 0)))
985                              (foo-maybe-inline (foo-maybe-inline (foo-maybe-inline x)))))))
986     (assert (= 0 (count-full-calls "FOO-MAYBE-INLINE" fun)))
987     (assert (= 1 (count-full-calls "QUUX-MARKER" fun)))))
988
989 (with-test (:name :inline-calls)
990   (let ((fun (compile nil `(lambda (x)
991                              (list (foo-inline x)
992                                    (foo-inline x)
993                                    (foo-inline x))))))
994     (assert (= 0 (count-full-calls "FOO-INLINE" fun)))
995     (assert (= 3 (count-full-calls "QUUX-MARKER" fun)))))
996
997 (with-test (:name :maybe-inline-calls)
998   (let ((fun (compile nil `(lambda (x)
999                              (declare (optimize (space 0)))
1000                              (list (foo-maybe-inline x)
1001                                    (foo-maybe-inline x)
1002                                    (foo-maybe-inline x))))))
1003     (assert (= 0 (count-full-calls "FOO-MAYBE-INLINE" fun)))
1004     (assert (= 1 (count-full-calls "QUUX-MARKER" fun)))))
1005
1006 (with-test (:name :bug-405)
1007   ;; These used to break with a TYPE-ERROR
1008   ;;     The value NIL is not of type SB-C::PHYSENV.
1009   ;; in MERGE-LETS.
1010   (ctu:file-compile
1011    '((LET (outer-let-var)
1012        (lambda ()
1013          (print outer-let-var)
1014          (MULTIPLE-VALUE-CALL 'some-function
1015            (MULTIPLE-VALUE-CALL (LAMBDA (a) 'foo)
1016              1))))))
1017   (ctu:file-compile
1018    '((declaim (optimize (debug 3)))
1019      (defstruct bug-405-foo bar)
1020      (let ()
1021        (flet ((i (x) (frob x (bug-405-foo-bar foo))))
1022          (i :five))))))
1023
1024 ;;; bug 235a
1025 (declaim (ftype (function (cons) number) bug-235a-aux))
1026 (declaim (inline bug-235a-aux))
1027 (defun bug-235a-aux (c)
1028   (the number (car c)))
1029 (with-test (:name :bug-235a)
1030   (let ((fun (compile nil
1031                       `(lambda (x y)
1032                          (values (locally (declare (optimize (safety 0)))
1033                                    (bug-235a-aux x))
1034                                  (locally (declare (optimize (safety 3)))
1035                                    (bug-235a-aux y)))))))
1036     (assert
1037      (eq :error
1038          (handler-case
1039              (funcall fun '(:one) '(:two))
1040            (type-error (e)
1041              (assert (eq :two (type-error-datum e)))
1042              (assert (eq 'number (type-error-expected-type e)))
1043              :error))))))
1044
1045 (with-test (:name :compiled-debug-funs-leak)
1046   (sb-ext:gc :full t)
1047   (let ((usage-before (sb-kernel::dynamic-usage)))
1048     (dotimes (x 10000)
1049       (let ((f (compile nil '(lambda ()
1050                                (error "X")))))
1051         (handler-case
1052             (funcall f)
1053           (error () nil))))
1054     (sb-ext:gc :full t)
1055     (let ((usage-after (sb-kernel::dynamic-usage)))
1056       (when (< (+ usage-before 2000000) usage-after)
1057         (error "Leak")))))
1058
1059 ;;; PROGV compilation and type checking when the declared type
1060 ;;; includes a FUNCTION subtype.
1061 (declaim (type (or (function (t) (values boolean &optional)) string)
1062                *hairy-progv-var*))
1063 (defvar *hairy-progv-var* #'null)
1064 (with-test (:name :hairy-progv-type-checking)
1065   (assert (eq :error
1066               (handler-case
1067                   (progv '(*hairy-progv-var*) (list (eval 42))
1068                     *hairy-progv-var*)
1069                 (type-error () :error))))
1070   (assert (equal "GOOD!"
1071                  (progv '(*hairy-progv-var*) (list (eval "GOOD!"))
1072                     *hairy-progv-var*))))
1073
1074 (with-test (:name :fill-complex-single-float)
1075   (assert (every (lambda (x) (eql x #c(-1.0 -2.0)))
1076                  (funcall
1077                   (lambda ()
1078                     (make-array 2
1079                                 :element-type '(complex single-float)
1080                                 :initial-element #c(-1.0 -2.0)))))))
1081
1082 (with-test (:name :make-array-symbol-as-initial-element)
1083   (assert (every (lambda (x) (eq x 'a))
1084                  (funcall
1085                   (compile nil
1086                            `(lambda ()
1087                               (make-array 12 :initial-element 'a)))))))
1088
1089 ;;; This non-minimal test-case catches a nasty error when loading
1090 ;;; inline constants.
1091 (deftype matrix ()
1092   `(simple-array single-float (16)))
1093 (declaim (ftype (sb-int:sfunction (single-float single-float single-float single-float
1094                                    single-float single-float single-float single-float
1095                                    single-float single-float single-float single-float
1096                                    single-float single-float single-float single-float)
1097                                   matrix)
1098                 matrix)
1099          (inline matrix))
1100 (defun matrix (m11 m12 m13 m14
1101                m21 m22 m23 m24
1102                m31 m32 m33 m34
1103                m41 m42 m43 m44)
1104   (make-array 16
1105               :element-type 'single-float
1106               :initial-contents (list m11 m21 m31 m41
1107                                       m12 m22 m32 m42
1108                                       m13 m23 m33 m43
1109                                       m14 m24 m34 m44)))
1110 (declaim (ftype (sb-int:sfunction ((simple-array single-float (3)) single-float) matrix)
1111                 rotate-around))
1112 (defun rotate-around (a radians)
1113   (let ((c (cos radians))
1114         (s (sin radians))
1115         ;; The 1.0 here was misloaded on x86-64.
1116         (g (- 1.0 (cos radians))))
1117     (let* ((x (aref a 0))
1118            (y (aref a 1))
1119            (z (aref a 2))
1120            (gxx (* g x x)) (gxy (* g x y)) (gxz (* g x z))
1121            (gyy (* g y y)) (gyz (* g y z)) (gzz (* g z z)))
1122       (matrix
1123        (+ gxx c)        (- gxy (* s z))  (+ gxz (* s y)) 0.0
1124        (+ gxy (* s z))  (+ gyy c)        (- gyz (* s x)) 0.0
1125        (- gxz (* s y))  (+ gyz (* s x))  (+ gzz c)       0.0
1126        0.0              0.0              0.0             1.0))))
1127 (with-test (:name :regression-1.0.29.54)
1128   (assert (every #'=
1129                  '(-1.0 0.0 0.0 0.0 0.0 -1.0 0.0 0.0 0.0 0.0 -1.0 0.0 0.0 0.0 0.0 1.0)
1130                  (rotate-around
1131                   (make-array 3 :element-type 'single-float) (coerce pi 'single-float))))
1132   ;; Same bug manifests in COMPLEX-ATANH as well.
1133   (assert (= (atanh #C(-0.7d0 1.1d0)) #C(-0.28715567731069275d0 0.9394245539093365d0))))
1134
1135 (with-test (:name :slot-value-on-structure)
1136   (let ((f (compile nil `(lambda (x a b)
1137                            (declare (something-known-to-be-a-struct x))
1138                            (setf (slot-value x 'x) a
1139                                  (slot-value x 'y) b)
1140                            (list (slot-value x 'x)
1141                                  (slot-value x 'y))))))
1142     (assert (equal '(#\x #\y)
1143                    (funcall f
1144                             (make-something-known-to-be-a-struct :x "X" :y "Y")
1145                             #\x #\y)))
1146     (assert (not (ctu:find-named-callees f)))))
1147
1148 (defclass some-slot-thing ()
1149   ((slot :initarg :slot)))
1150 (with-test (:name :with-slots-the)
1151   (let ((x (make-instance 'some-slot-thing :slot "foo")))
1152     (with-slots (slot) (the some-slot-thing x)
1153       (assert (equal "foo" slot)))))
1154
1155 ;;; Missing &REST type in proclamation causing a miscompile.
1156 (declaim (ftype
1157           (function
1158            (sequence unsigned-byte
1159                      &key (:initial-element t) (:initial-contents sequence))
1160            (values sequence &optional))
1161           bug-458354))
1162 (defun bug-458354
1163     (sequence length
1164      &rest keys
1165      &key (initial-element nil iep) (initial-contents nil icp))
1166   (declare (sb-ext:unmuffle-conditions style-warning))
1167   (declare (ignorable keys initial-element iep initial-contents icp))
1168   (apply #'sb-sequence:make-sequence-like sequence length keys))
1169 (with-test (:name :bug-458354)
1170   (assert (equalp #((a b) (a b)) (bug-458354 #(1 2) 2 :initial-element '(a b)))))
1171
1172 (with-test (:name :bug-542807)
1173   (handler-bind ((style-warning #'error))
1174     (eval '(defstruct bug-542807 slot)))
1175   (let (conds)
1176     (handler-bind ((style-warning (lambda (c)
1177                                     (push c conds))))
1178       (eval '(defstruct bug-542807 slot)))
1179     (assert (= 1 (length conds)))
1180     (assert (typep (car conds) 'sb-kernel::redefinition-with-defun))))
1181
1182 (with-test (:name :defmacro-not-list-lambda-list)
1183   (assert (raises-error? (eval `(defmacro ,(gensym) "foo"))
1184                          type-error)))
1185
1186 (with-test (:name :bug-308951)
1187   (let ((x 1))
1188     (dotimes (y 10)
1189       (let ((y y))
1190         (when (funcall (eval #'(lambda (x) (eql x 2))) y)
1191           (defun bug-308951-foo (z)
1192             (incf x (incf y z))))))
1193     (defun bug-308951-bar (z)
1194       (bug-308951-foo z)
1195       (values x)))
1196   (assert (= 4 (bug-308951-bar 1))))
1197
1198 (declaim (inline bug-308914-storage))
1199 (defun bug-308914-storage (x)
1200   (the (simple-array flt (*)) (bug-308914-unknown x)))
1201
1202 (with-test (:name :bug-308914-workaround)
1203   ;; This used to hang in ORDER-UVL-SETS.
1204   (handler-case
1205       (with-timeout 10
1206         (compile nil
1207                  `(lambda (lumps &key cg)
1208                     (let ((nodes (map 'list (lambda (lump)
1209                                               (bug-308914-storage lump))
1210                                       lumps)))
1211                       (setf (aref nodes 0) 2)
1212                       (assert (every #'~= (apply #'concatenate 'list nodes) '(2 3 6 9)))))))
1213     (sb-ext:timeout ()
1214       (error "Hang in ORDER-UVL-SETS?"))))
1215
1216 (declaim (inline inlined-function-in-source-path))
1217 (defun inlined-function-in-source-path (x)
1218   (+ x x))
1219
1220 (with-test (:name :inlined-function-in-source-path)
1221   (let ((output
1222          (with-output-to-string (*error-output*)
1223            (compile nil `(lambda (x)
1224                            (declare (optimize speed))
1225                            (funcall #'inlined-function-in-source-path x))))))
1226     ;; We want the name
1227     (assert (search "INLINED-FUNCTION-IN-SOURCE-PATH" output))
1228     ;; ...not the leaf.
1229     (assert (not (search "DEFINED-FUN" output)))))
1230
1231 (defmacro bug-795705 ()
1232   t)
1233
1234 (with-test (:name :bug-795705)
1235   (assert (macro-function 'bug-795705))
1236   (fmakunbound 'bug-795705)
1237   (assert (not (macro-function 'bug-795705))))
1238
1239 (with-test (:name (load-time-value :type-derivation))
1240   (let ((name 'load-time-value-type-derivation-test))
1241     (labels ((funtype (fun)
1242                (sb-kernel:type-specifier
1243                 (sb-kernel:single-value-type
1244                  (sb-kernel:fun-type-returns
1245                   (sb-kernel:specifier-type
1246                    (sb-kernel:%simple-fun-type fun))))))
1247              (test (type1 type2 form value-cell-p)
1248              (let* ((lambda-form `(lambda ()
1249                                     (load-time-value ,form)))
1250                     (core-fun (compile nil lambda-form))
1251                     (core-type (funtype core-fun))
1252                     (core-cell (ctu:find-value-cell-values core-fun))
1253                     (defun-form `(defun ,name ()
1254                                    (load-time-value ,form)))
1255                     (file-fun (progn
1256                                 (ctu:file-compile (list defun-form) :load t)
1257                                 (symbol-function name)))
1258                     (file-type (funtype file-fun))
1259                     (file-cell (ctu:find-value-cell-values file-fun)))
1260                (if value-cell-p
1261                    (assert (and core-cell file-cell))
1262                    (assert (not (or core-cell file-cell))))
1263                (unless (subtypep core-type type1)
1264                  (error "core: wanted ~S, got ~S" type1 core-type))
1265                (unless (subtypep file-type type2)
1266                  (error "file: wanted ~S, got ~S" type2 file-type)))))
1267       (let ((* 10))
1268         (test '(integer 11 11) 'number
1269               '(+ * 1) nil))
1270       (let ((* "fooo"))
1271         (test '(integer 4 4) 'unsigned-byte
1272               '(length *) nil))
1273       (test '(integer 10 10) '(integer 10 10) 10 nil)
1274       (test 'cons 'cons '(cons t t) t))))
1275
1276 (with-test (:name (load-time-value :errors))
1277   (multiple-value-bind (warn fail)
1278       (ctu:file-compile
1279        `((defvar *load-time-value-error-value* 10)
1280          (declaim (fixnum *load-time-value-error-value*))
1281          (defun load-time-value-error-test-1 ()
1282            (the list (load-time-value *load-time-value-error-value*))))
1283        :load t)
1284     (assert warn)
1285     (assert fail))
1286   (handler-case (load-time-value-error-test-1)
1287     (type-error (e)
1288       (and (eql 10 (type-error-datum e))
1289            (eql 'list (type-error-expected-type e)))))
1290   (multiple-value-bind (warn2 fail2)
1291       (ctu:file-compile
1292        `((defun load-time-value-error-test-2 ()
1293            (the list (load-time-value 10))))
1294        :load t)
1295     (assert warn2)
1296     (assert fail2))
1297   (handler-case (load-time-value-error-test-2)
1298     (type-error (e)
1299       (and (eql 10 (type-error-datum e))
1300            (eql 'list (type-error-expected-type e))))))
1301
1302 ;;;; tests for compiler output
1303 (with-test (:name :unexpected-compiler-output)
1304   (let* ((*error-output* (make-string-output-stream))
1305          (output (with-output-to-string (*standard-output*)
1306                    (compile-file "compiler-output-test.lisp"
1307                                  :print nil :verbose nil))))
1308     (unless (zerop (length output))
1309       (error "Unexpected output: ~S" output))))
1310
1311 (with-test (:name :bug-493380)
1312   (flet ((test (forms)
1313            (catch 'debug
1314              (let ((*debugger-hook* (lambda (condition if)
1315                                       (throw 'debug
1316                                         (if (typep condition 'serious-condition)
1317                                             :debug
1318                                             :oops)))))
1319                (multiple-value-bind (warned failed) (ctu:file-compile forms)
1320                  (when (and warned failed)
1321                    :failed))))))
1322     (assert (eq :failed (test "(defun")))
1323     (assert (eq :failed (test "(defun no-pkg::foo ())")))
1324     (assert (eq :failed (test "(cl:no-such-sym)")))
1325     (assert (eq :failed (test "...")))))
1326 \f
1327 ;;;; tests not in the problem domain, but of the consistency of the
1328 ;;;; compiler machinery itself
1329
1330 (in-package "SB-C")
1331
1332 ;;; Hunt for wrong-looking things in fundamental compiler definitions,
1333 ;;; and gripe about them.
1334 ;;;
1335 ;;; FIXME: It should be possible to (1) repair the things that this
1336 ;;; code gripes about, and then (2) make the code signal errors
1337 ;;; instead of just printing complaints to standard output, in order
1338 ;;; to prevent the code from later falling back into disrepair.
1339 (defun grovel-results (function)
1340   (dolist (template (fun-info-templates (info :function :info function)))
1341     (when (template-more-results-type template)
1342       (format t "~&Template ~A has :MORE results, and translates ~A.~%"
1343               (template-name template)
1344               function)
1345       (return nil))
1346     (when (eq (template-result-types template) :conditional)
1347       ;; dunno.
1348       (return t))
1349     (let ((types (template-result-types template))
1350           (result-type (fun-type-returns (info :function :type function))))
1351       (cond
1352         ((values-type-p result-type)
1353          (do ((ltypes (append (args-type-required result-type)
1354                               (args-type-optional result-type))
1355                       (rest ltypes))
1356               (types types (rest types)))
1357              ((null ltypes)
1358               (unless (null types)
1359                 (format t "~&More types than ltypes in ~A, translating ~A.~%"
1360                         (template-name template)
1361                         function)
1362                 (return nil)))
1363            (when (null types)
1364              (unless (null ltypes)
1365                (format t "~&More ltypes than types in ~A, translating ~A.~%"
1366                        (template-name template)
1367                        function)
1368                (return nil)))))
1369         ((eq result-type (specifier-type nil))
1370          (unless (null types)
1371            (format t "~&Template ~A returns values for function ~A with RESULT-TYPE NIL.~%"
1372                    (template-name template)
1373                    function)
1374            (return nil)))
1375         ((/= (length types) 1)
1376          (format t "~&Template ~A isn't returning 1 value for ~A.~%"
1377                  (template-name template)
1378                  function)
1379          (return nil))
1380         (t t)))))
1381 (defun identify-suspect-vops (&optional (env (first
1382                                               (last *info-environment*))))
1383   (do-info (env :class class :type type :name name :value value)
1384     (when (and (eq class :function) (eq type :type))
1385       ;; OK, so we have an entry in the INFO database. Now, if ...
1386       (let* ((info (info :function :info name))
1387              (templates (and info (fun-info-templates info))))
1388         (when templates
1389           ;; ... it has translators
1390           (grovel-results name))))))
1391 (identify-suspect-vops)
1392 \f
1393 ;;;; bug 305: INLINE/NOTINLINE causing local ftype to be lost
1394
1395 (define-condition optimization-error (error) ())
1396
1397 (labels ((compile-lambda (type sense)
1398            (handler-bind ((compiler-note (lambda (_)
1399                                            (declare (ignore _))
1400                                            (error 'optimization-error))))
1401              (values
1402               (compile
1403                nil
1404                `(lambda ()
1405                   (declare
1406                    ,@(when type '((ftype (function () (integer 0 10)) bug-305)))
1407                    (,sense bug-305)
1408                    (optimize speed))
1409                   (1+ (bug-305))))
1410               nil)))
1411          (expect-error (sense)
1412            (multiple-value-bind (f e)  (ignore-errors (compile-lambda nil sense))
1413              (assert (not f))
1414              (assert (typep e 'optimization-error))))
1415          (expect-pass (sense)
1416            (multiple-value-bind (f e)  (ignore-errors (compile-lambda t sense))
1417              (assert f)
1418              (assert (not e)))))
1419   (expect-error 'inline)
1420   (expect-error 'notinline)
1421   (expect-pass 'inline)
1422   (expect-pass 'notinline))
1423
1424 ;;; bug 211e: bogus style warning from duplicated keyword argument to
1425 ;;; a local function.
1426 (handler-bind ((style-warning #'error))
1427   (let ((f (compile nil '(lambda ()
1428                           (flet ((foo (&key y) (list y)))
1429                             (list (foo :y 1 :y 2)))))))
1430     (assert (equal '((1)) (funcall f)))))
1431
1432 ;;; check that EQL is optimized when other argument is (OR SYMBOL FIXNUM).
1433 (handler-bind ((compiler-note #'error))
1434   (let ((f1 (compile nil '(lambda (x1 y1)
1435                            (declare (type (or symbol fixnum) x1)
1436                                     (optimize speed))
1437                            (eql x1 y1))))
1438         (f2 (compile nil '(lambda (x2 y2)
1439                            (declare (type (or symbol fixnum) y2)
1440                                     (optimize speed))
1441                            (eql x2 y2)))))
1442     (let ((fix (random most-positive-fixnum))
1443           (sym (gensym))
1444           (e-count 0))
1445       (assert (funcall f1 fix fix))
1446       (assert (funcall f2 fix fix))
1447       (assert (funcall f1 sym sym))
1448       (assert (funcall f2 sym sym))
1449       (handler-bind ((type-error (lambda (c)
1450                                    (incf e-count)
1451                                    (continue c))))
1452         (flet ((test (f x y)
1453                  (with-simple-restart (continue "continue with next test")
1454                    (funcall f x y)
1455                    (error "fell through with (~S ~S ~S)" f x y))))
1456           (test f1 "oops" 42)
1457           (test f1 (1+ most-positive-fixnum) 42)
1458           (test f2 42 "oops")
1459           (test f2 42 (1+ most-positive-fixnum))))
1460       (assert (= e-count 4)))))
1461
1462 ;;; bug #389 (Rick Taube sbcl-devel)
1463 (defun bes-jn (unn ux)
1464    (let ((nn unn) (x ux))
1465      (let* ((n (floor (abs nn)))
1466             (besn
1467              (if (= n 0)
1468                  (bes-j0 x)
1469                  (if (= n 1)
1470                      (bes-j1 x)
1471                      (if (zerop x)
1472                          0.0
1473                          (let ((iacc 40)
1474                                (ans 0.0)
1475                                (bigno 1.0e+10)
1476                                (bigni 1.0e-10))
1477                            (if (> (abs x) n)
1478                                (do ((tox (/ 2.0 (abs x)))
1479                                     (bjm (bes-j0 (abs x)))
1480                                     (bj (bes-j1 (abs x)))
1481                                     (j 1 (+ j 1))
1482                                     (bjp 0.0))
1483                                    ((= j n) (setf ans bj))
1484                                  (setf bjp (- (* j tox bj) bjm))
1485                                  (setf bjm bj)
1486                                  (setf bj bjp))
1487                                (let ((tox (/ 2.0 (abs x)))
1488                                      (m
1489                                       (* 2
1490                                          (floor
1491                                           (/ (+ n (sqrt (* iacc n)))
1492                                              2))))
1493                                      (jsum 0.0)
1494                                      (bjm 0.0)
1495                                      (sum 0.0)
1496                                      (bjp 0.0)
1497                                      (bj 1.0))
1498                                  (do ((j m (- j 1)))
1499                                      ((= j 0))
1500                                    (setf bjm (- (* j tox bj) bjp))
1501                                    (setf bjp bj)
1502                                    (setf bj bjm)
1503                                    (when (> (abs bj) bigno)
1504                                      (setf bj (* bj bigni))
1505                                      (setf bjp (* bjp bigni))
1506                                      (setf ans (* ans bigni))
1507                                      (setf sum (* sum bigni)))
1508                                    (if (not (= 0 jsum)) (incf sum bj))
1509                                    (setf jsum (- 1 jsum))
1510                                    (if (= j n) (setf ans bjp)))
1511                                  (setf sum (- (* 2.0 sum) bj))
1512                                  (setf ans (/ ans sum))))
1513                            (if (and (minusp x) (oddp n))
1514                                (- ans)
1515                                ans)))))))
1516        (if (and (minusp nn) (oddp nn)) (- besn) besn))))
1517
1518
1519 ;;; bug 233b: lvar lambda-var equality in constraint propagation
1520
1521 ;; Put this in a separate function.
1522 (defun test-constraint-propagation/ref ()
1523   (let ((x nil))
1524     (if (multiple-value-prog1 x (setq x t))
1525         1
1526         x)))
1527
1528 (test-util:with-test (:name (:compiler :constraint-propagation :ref))
1529   (assert (eq t (test-constraint-propagation/ref))))
1530
1531 ;; Put this in a separate function.
1532 (defun test-constraint-propagation/typep (x y)
1533   (if (typep (multiple-value-prog1 x (setq x y))
1534              'double-float)
1535       (+ x 1d0)
1536       (+ x 2)))
1537
1538 (test-util:with-test (:name (:compiler :constraint-propagation :typep))
1539   (assert (= 6.0d0 (test-constraint-propagation/typep 1d0 5))))
1540
1541 (test-util:with-test (:name (:compiler :constraint-propagation :eq/eql))
1542   (assert (eq :right (let ((c :wrong))
1543                        (if (eq (let ((x c))
1544                                  (setq c :right)
1545                                  x)
1546                                :wrong)
1547                            c
1548                            0)))))
1549
1550 ;;; Put this in a separate function.
1551 (defun test-constraint-propagation/cast (x)
1552   (when (the double-float (multiple-value-prog1
1553                               x
1554                             (setq x (1+ x))))
1555     x))
1556
1557 (test-util:with-test (:name (:compiler :constraint-propagation :cast))
1558   (assert (assertoid:raises-error?
1559            (test-constraint-propagation/cast 1) type-error)))
1560
1561 ;;; bug #399
1562 (let ((result (make-array 50000 :fill-pointer 0 :adjustable t)))
1563   (defun string->html (string &optional (max-length nil))
1564     (when (and (numberp max-length)
1565                (> max-length (array-dimension result 0)))
1566       (setf result (make-array max-length :fill-pointer 0 :adjustable t)))
1567     (let ((index 0)
1568           (left-quote? t))
1569       (labels ((add-char (it)
1570                  (setf (aref result index) it)
1571                  (incf index))
1572                (add-string (it)
1573                  (loop for ch across it do
1574                        (add-char ch))))
1575         (loop for char across string do
1576               (cond ((char= char #\<)
1577                      (add-string "&lt;"))
1578                     ((char= char #\>)
1579                      (add-string "&gt;"))
1580                     ((char= char #\&)
1581                      (add-string "&amp;"))
1582                     ((char= char #\')
1583                      (add-string "&#39;"))
1584                     ((char= char #\newline)
1585                      (add-string "<br>"))
1586                     ((char= char #\")
1587                      (if left-quote? (add-string "&#147;") (add-string "&#148;"))
1588                      (setf left-quote? (not left-quote?)))
1589                     (t
1590                      (add-char char))))
1591         (setf (fill-pointer result) index)
1592         (coerce result 'string)))))
1593
1594 ;;; Callign thru constant symbols
1595 (require :sb-introspect)
1596
1597 (declaim (inline target-fun))
1598 (defun target-fun (arg0 arg1)
1599   (+ arg0 arg1))
1600 (declaim (notinline target-fun))
1601
1602 (defun test-target-fun-called (fun res)
1603   (assert (member #'target-fun
1604                   (sb-introspect:find-function-callees #'caller-fun-1)))
1605   (assert (equal (funcall fun) res)))
1606
1607 (defun caller-fun-1 ()
1608   (funcall 'target-fun 1 2))
1609 (test-target-fun-called #'caller-fun-1 3)
1610
1611 (defun caller-fun-2 ()
1612   (declare (inline target-fun))
1613   (apply 'target-fun 1 '(3)))
1614 (test-target-fun-called #'caller-fun-2 4)
1615
1616 (defun caller-fun-3 ()
1617   (flet ((target-fun (a b)
1618            (- a b)))
1619     (list (funcall #'target-fun 1 4) (funcall 'target-fun 1 4))))
1620 (test-target-fun-called #'caller-fun-3 (list -3 5))
1621
1622 ;;; Reported by NIIMI Satoshi
1623 ;;; Subject: [Sbcl-devel] compilation error with optimization
1624 ;;; Date: Sun, 09 Apr 2006 17:36:05 +0900
1625 (defun test-minimal-debug-info-for-unstored-but-used-parameter (n a)
1626   (declare (optimize (speed 3)
1627                      (debug 1)))
1628   (if (= n 0)
1629       0
1630       (test-minimal-debug-info-for-unstored-but-used-parameter (1- n) a)))
1631
1632 ;;; &KEY arguments with non-constant defaults.
1633 (declaim (notinline opaque-identity))
1634 (defun opaque-identity (x) x)
1635 (defstruct tricky-defaults
1636   (fun #'identity :type function)
1637   (num (opaque-identity 3) :type fixnum))
1638 (macrolet ((frob (form expected-expected-type)
1639              `(handler-case ,form
1640                (type-error (c) (assert (eq (type-error-expected-type c)
1641                                            ',expected-expected-type)))
1642                (:no-error (&rest vals) (error "~S returned values: ~S" ',form vals)))))
1643   (frob (make-tricky-defaults :fun 3) function)
1644   (frob (make-tricky-defaults :num #'identity) fixnum))
1645
1646 (let ((fun (compile nil '(lambda (&key (key (opaque-identity 3)))
1647                           (declare (optimize safety) (type integer key))
1648                           key))))
1649   (assert (= (funcall fun) 3))
1650   (assert (= (funcall fun :key 17) 17))
1651   (handler-case (funcall fun :key t)
1652     (type-error (c) (assert (eq (type-error-expected-type c) 'integer)))
1653     (:no-error (&rest vals) (error "no error"))))
1654
1655 ;;; Basic compiler-macro expansion
1656 (define-compiler-macro test-cmacro-0 () ''expanded)
1657
1658 (assert (eq 'expanded (funcall (lambda () (test-cmacro-0)))))
1659
1660 ;;; FUNCALL forms in compiler macros, lambda-list parsing
1661 (define-compiler-macro test-cmacro-1
1662     (&whole whole a (a2) &optional b &rest c &key d)
1663   (list whole a a2 b c d))
1664
1665 (macrolet ((test (form a a2 b c d)
1666              `(let ((form ',form))
1667                 (destructuring-bind (whole a a2 b c d)
1668                     (funcall (compiler-macro-function 'test-cmacro-1) form nil)
1669                   (assert (equal whole form))
1670                   (assert (eql a ,a))
1671                   (assert (eql a2 ,a2))
1672                   (assert (eql b ,b))
1673                   (assert (equal c ,c))
1674                   (assert (eql d ,d))))) )
1675   (test (funcall 'test-cmacro-1 1 (x) 2 :d 3) 1 'x 2 '(:d 3) 3)
1676   (test (test-cmacro-1 11 (y) 12 :d 13) 11 'y 12 '(:d 13) 13))
1677
1678 ;;; FUNCALL forms in compiler macros, expansions
1679 (define-compiler-macro test-cmacro-2 () ''ok)
1680
1681 (assert (eq 'ok (funcall (lambda () (funcall 'test-cmacro-2)))))
1682 (assert (eq 'ok (funcall (lambda () (funcall #'test-cmacro-2)))))
1683
1684 ;;; Shadowing of compiler-macros by local functions
1685 (define-compiler-macro test-cmacro-3 () ''global)
1686
1687 (defmacro find-cmacro-3 (&environment env)
1688   (compiler-macro-function 'test-cmacro-3 env))
1689
1690 (assert (funcall (lambda () (find-cmacro-3))))
1691 (assert (not (funcall (lambda () (flet ((test-cmacro-3 ()))
1692                                    (find-cmacro-3))))))
1693 (assert (eq 'local (funcall (lambda () (flet ((test-cmacro-3 () 'local))
1694                                          (test-cmacro-3))))))
1695 (assert (eq 'local (funcall (lambda () (flet ((test-cmacro-3 () 'local))
1696                                          (funcall #'test-cmacro-3))))))
1697 (assert (eq 'global (funcall (lambda () (flet ((test-cmacro-3 () 'local))
1698                                           (funcall 'test-cmacro-3))))))
1699
1700 ;;; Local NOTINLINE & INLINE
1701 (defun test-cmacro-4 () 'fun)
1702 (define-compiler-macro test-cmacro-4 () ''macro)
1703
1704 (assert (eq 'fun (funcall (lambda ()
1705                             (declare (notinline test-cmacro-4))
1706                             (test-cmacro-4)))))
1707
1708 (assert (eq 'macro (funcall (lambda ()
1709                               (declare (inline test-cmacro-4))
1710                               (test-cmacro-4)))))
1711
1712 ;;; SETF function compiler macros
1713 (define-compiler-macro (setf test-cmacro-4) (&whole form value) ''ok)
1714
1715 (assert (eq 'ok (funcall (lambda () (setf (test-cmacro-4) 'zot)))))
1716 (assert (eq 'ok (funcall (lambda () (funcall #'(setf test-cmacro-4) 'zot)))))
1717
1718 ;;; Step instrumentation breaking type-inference
1719 (handler-bind ((warning #'error))
1720   (assert (= 42 (funcall (compile nil '(lambda (v x)
1721                                         (declare (optimize sb-c:insert-step-conditions))
1722                                         (if (typep (the function x) 'fixnum)
1723                                             (svref v (the function x))
1724                                             (funcall x))))
1725                          nil (constantly 42)))))
1726
1727 ;;; bug 368: array type intersections in the compiler
1728 (defstruct e368)
1729 (defstruct i368)
1730 (defstruct g368
1731   (i368s (make-array 0 :fill-pointer t) :type (or (vector i368) null)))
1732 (defstruct s368
1733   (g368 (error "missing :G368") :type g368 :read-only t))
1734 (declaim (ftype (function (fixnum (vector i368) e368) t) r368))
1735 (declaim (ftype (function (fixnum (vector e368)) t) h368))
1736 (defparameter *h368-was-called-p* nil)
1737 (defun nsu (vertices e368)
1738   (let ((i368s (g368-i368s (make-g368))))
1739     (let ((fuis (r368 0 i368s e368)))
1740       (format t "~&FUIS=~S~%" fuis)
1741       (or fuis (h368 0 i368s)))))
1742 (defun r368 (w x y)
1743   (declare (ignore w x y))
1744   nil)
1745 (defun h368 (w x)
1746   (declare (ignore w x))
1747   (setf *h368-was-called-p* t)
1748   (make-s368 :g368 (make-g368)))
1749 (let ((nsu (nsu #() (make-e368))))
1750   (format t "~&NSU returned ~S~%" nsu)
1751   (format t "~&*H368-WAS-CALLED-P*=~S~%" *h368-was-called-p*)
1752   (assert (s368-p nsu))
1753   (assert *h368-was-called-p*))
1754
1755 ;;; bug 367: array type intersections in the compiler
1756 (defstruct e367)
1757 (defstruct i367)
1758 (defstruct g367
1759   (i367s (make-array 0 :fill-pointer t) :type (or (vector i367) null)))
1760 (defstruct s367
1761   (g367 (error "missing :G367") :type g367 :read-only t))
1762 (declaim (ftype (function ((vector i367) e367) (or s367 null)) r367))
1763 (declaim (ftype (function ((vector e367)) (values)) h367))
1764 (defun frob-367 (v w)
1765   (let ((x (g367-i367s (make-g367))))
1766     (let* ((y (or (r367 x w)
1767                   (h367 x)))
1768            (z (s367-g367 y)))
1769       (format t "~&Y=~S Z=~S~%" y z)
1770       (g367-i367s z))))
1771 (defun r367 (x y) (declare (ignore x y)) nil)
1772 (defun h367 (x) (declare (ignore x)) (values))
1773 (multiple-value-bind (res err) (ignore-errors (frob-367 0 (make-e367)))
1774   (assert (not res))
1775   (assert (typep err 'type-error)))
1776
1777 (handler-case
1778     (delete-file (compile-file "circ-tree-test.lisp"))
1779   (storage-condition (e)
1780     (error e)))
1781
1782 ;;; warnings due to step-insturmentation
1783 (defclass debug-test-class () ())
1784 (handler-case
1785     (compile nil '(lambda ()
1786                    (declare (optimize (debug 3)))
1787                    (defmethod print-object ((x debug-test-class) s)
1788                      (call-next-method))))
1789   ((and (not style-warning) warning) (e)
1790     (error e)))
1791
1792 ;;; program-error from bad lambda-list keyword
1793 (assert (eq :ok
1794             (handler-case
1795                 (funcall (lambda (&whole x)
1796                            (list &whole x)))
1797               (program-error ()
1798                 :ok))))
1799 #+sb-eval
1800 (assert (eq :ok
1801             (handler-case
1802                 (let ((*evaluator-mode* :interpret))
1803                   (funcall (eval '(lambda (&whole x)
1804                                    (list &whole x)))))
1805               (program-error ()
1806                 :ok))))
1807
1808 ;;; ignore &environment
1809 (handler-bind ((style-warning #'error))
1810   (compile nil '(lambda ()
1811                  (defmacro macro-ignore-env (&environment env)
1812                    (declare (ignore env))
1813                    :foo)))
1814   (compile nil '(lambda ()
1815                  (defmacro macro-no-env ()
1816                    :foo))))
1817
1818 (dolist (*evaluator-mode* '(#+sb-eval :interpret :compile))
1819   (disassemble (eval '(defun disassemble-source-form-bug (x y z)
1820                        (declare (optimize debug))
1821                        (list x y z)))))
1822
1823 ;;; long-standing bug in defaulting unknown values on the x86-64,
1824 ;;; since changing the calling convention (test case by Christopher
1825 ;;; Laux sbcl-help 30-06-2007)
1826
1827 (defun default-values-bug-demo-sub ()
1828   (format t "test")
1829   nil)
1830 (compile 'default-values-bug-demo-sub)
1831
1832 (defun default-values-bug-demo-main ()
1833   (multiple-value-bind (a b c d e f g h)
1834       (default-values-bug-demo-sub)
1835     (if a (+ a b c d e f g h) t)))
1836 (compile 'default-values-bug-demo-main)
1837
1838 (assert (default-values-bug-demo-main))
1839
1840 ;;; copy propagation bug reported by Paul Khuong
1841
1842 (defun local-copy-prop-bug-with-move-arg (x)
1843   (labels ((inner ()
1844              (values 1 0)))
1845     (if x
1846         (inner)
1847         (multiple-value-bind (a b)
1848             (inner)
1849           (values b a)))))
1850
1851 (assert (equal '(0 1) (multiple-value-list (local-copy-prop-bug-with-move-arg nil))))
1852 (assert (equal '(1 0) (multiple-value-list (local-copy-prop-bug-with-move-arg t))))
1853
1854 ;;;; with-pinned-objects & unwind-protect, using all non-tail conventions
1855
1856 (defun wpo-quux () (list 1 2 3))
1857 (defvar *wpo-quux* #'wpo-quux)
1858
1859 (defun wpo-call ()
1860   (unwind-protect
1861        (sb-sys:with-pinned-objects (*wpo-quux*)
1862          (values (funcall *wpo-quux*)))))
1863 (assert (equal '(1 2 3) (wpo-call)))
1864
1865 (defun wpo-multiple-call ()
1866   (unwind-protect
1867        (sb-sys:with-pinned-objects (*wpo-quux*)
1868          (funcall *wpo-quux*))))
1869 (assert (equal '(1 2 3) (wpo-multiple-call)))
1870
1871 (defun wpo-call-named ()
1872   (unwind-protect
1873        (sb-sys:with-pinned-objects (*wpo-quux*)
1874          (values (wpo-quux)))))
1875 (assert (equal '(1 2 3) (wpo-call-named)))
1876
1877 (defun wpo-multiple-call-named ()
1878   (unwind-protect
1879        (sb-sys:with-pinned-objects (*wpo-quux*)
1880          (wpo-quux))))
1881 (assert (equal '(1 2 3) (wpo-multiple-call-named)))
1882
1883 (defun wpo-call-variable (&rest args)
1884   (unwind-protect
1885        (sb-sys:with-pinned-objects (*wpo-quux*)
1886          (values (apply *wpo-quux* args)))))
1887 (assert (equal '(1 2 3) (wpo-call-variable)))
1888
1889 (defun wpo-multiple-call-variable (&rest args)
1890   (unwind-protect
1891        (sb-sys:with-pinned-objects (*wpo-quux*)
1892          (apply #'wpo-quux args))))
1893 (assert (equal '(1 2 3) (wpo-multiple-call-named)))
1894
1895 (defun wpo-multiple-call-local ()
1896   (flet ((quux ()
1897            (wpo-quux)))
1898     (unwind-protect
1899          (sb-sys:with-pinned-objects (*wpo-quux*)
1900            (quux)))))
1901 (assert (equal '(1 2 3) (wpo-multiple-call-local)))
1902
1903 ;;; bug 417: toplevel NIL confusing source path logic
1904 (handler-case
1905     (delete-file (compile-file "bug-417.lisp"))
1906   (sb-ext:code-deletion-note (e)
1907     (error e)))
1908
1909 ;;; unknown values return convention getting disproportionate
1910 ;;; amounts of values.
1911 (declaim (notinline one-value two-values))
1912 (defun one-value (x)
1913   (not x))
1914 (defun two-values (x y)
1915   (values y x))
1916 (defun wants-many-values (x y)
1917   (multiple-value-bind (a b c d e f)
1918       (one-value y)
1919     (assert (and (eql (not y) a)
1920                  (not (or b c d e f)))))
1921   (multiple-value-bind (a b c d e f)
1922       (two-values y x)
1923     (assert (and (eql a x) (eql b y)
1924                  (not (or c d e f)))))
1925   (multiple-value-bind (a b c d e f g h i)
1926       (one-value y)
1927     (assert (and (eql (not y) a)
1928                  (not (or b c d e f g h i)))))
1929   (multiple-value-bind (a b c d e f g h i)
1930       (two-values y x)
1931     (assert (and (eql a x) (eql b y)
1932                  (not (or c d e f g h i)))))
1933   (multiple-value-bind (a b c d e f g h i j k l m n o p q r s)
1934       (one-value y)
1935     (assert (and (eql (not y) a)
1936                  (not (or b c d e f g h i j k l m n o p q r s)))))
1937   (multiple-value-bind (a b c d e f g h i j k l m n o p q r s)
1938       (two-values y x)
1939     (assert (and (eql a x) (eql b y)
1940                  (not (or c d e f g h i j k l m n o p q r s))))))
1941 (wants-many-values 1 42)
1942
1943 ;;; constant coalescing
1944
1945 (defun count-code-constants (x f)
1946   (let ((code (sb-kernel:fun-code-header f))
1947         (n 0))
1948     (loop for i from sb-vm::code-constants-offset below (sb-kernel:get-header-data code)
1949           do (when (equal x (sb-kernel:code-header-ref code i))
1950                (incf n)))
1951     n))
1952
1953 (defvar *lambda*)
1954
1955 (defun compile2 (lambda)
1956   (let* ((lisp "compiler-impure-tmp.lisp")
1957          (fasl (compile-file-pathname lisp)))
1958     (unwind-protect
1959          (progn
1960            (with-open-file (f lisp :direction :output)
1961              (prin1 `(setf *lambda* ,lambda) f))
1962            (multiple-value-bind (fasl warn fail) (compile-file lisp)
1963              (declare (ignore warn))
1964              (when fail
1965                (error "File-compiling ~S failed." lambda))
1966              (let ((*lambda* nil))
1967                (load fasl)
1968                (values *lambda* (compile nil lambda)))))
1969       (ignore-errors (delete-file lisp))
1970       (ignore-errors (delete-file fasl)))))
1971
1972 ;; named and unnamed
1973 (defconstant +born-to-coalesce+ '.born-to-coalesce.)
1974 (multiple-value-bind (file-fun core-fun)
1975     (compile2 '(lambda ()
1976                 (let ((x (cons +born-to-coalesce+ nil))
1977                       (y (cons '.born-to-coalesce. nil)))
1978                   (list x y))))
1979   (assert (= 1 (count-code-constants '.born-to-coalesce. file-fun)))
1980   (assert (= 1 (count-code-constants '.born-to-coalesce. core-fun))))
1981
1982 ;; some things must retain identity under COMPILE, but we want to coalesce them under COMPILE-FILE
1983 (defun assert-coalescing (constant)
1984   (let ((value (copy-seq (symbol-value constant))))
1985     (multiple-value-bind (file-fun core-fun)
1986         (compile2 `(lambda ()
1987                      (let ((x (cons ,constant nil))
1988                            (y (cons ',value nil)))
1989                        (list x y))))
1990       (assert (= 1 (count-code-constants value file-fun)))
1991       (assert (= 2 (count-code-constants value core-fun)))
1992       (let* ((l (funcall file-fun))
1993              (a (car (first l)))
1994              (b (car (second l))))
1995         (assert (and (equal value a)
1996                      (equal a b)
1997                      (eq a b))))
1998       (let* ((l (funcall core-fun))
1999              (a (car (first l)))
2000              (b (car (second l))))
2001         (assert (and (equal value a)
2002                      (equal a b)
2003                      (not (eq a b))))))))
2004
2005 (defconstant +born-to-coalesce2+ "maybe coalesce me!")
2006 (assert-coalescing '+born-to-coalesce2+)
2007
2008 (defconstant +born-to-coalesce3+ #*01101001011101110100011)
2009 (assert-coalescing '+born-to-coalesce3+)
2010
2011 (defconstant +born-to-coalesce4+ '(foo bar "zot" 123 (nested "quux") #*0101110010))
2012 (assert-coalescing '+born-to-coalesce4+)
2013
2014 (defclass some-constant-thing () ())
2015
2016 ;;; correct handling of nested things loaded via SYMBOL-VALUE
2017 (defvar *sneaky-nested-thing* (list (make-instance 'some-constant-thing)))
2018 (defconstant +sneaky-nested-thing+ *sneaky-nested-thing*)
2019 (multiple-value-bind (file-fun core-fun) (compile2 '(lambda () +sneaky-nested-thing+))
2020   (assert (equal *sneaky-nested-thing* (funcall file-fun)))
2021   (assert (equal *sneaky-nested-thing* (funcall core-fun))))
2022
2023 ;;; catch constant modifications thru undefined variables
2024 (defun sneak-set-dont-set-me (x)
2025   (ignore-errors (setq dont-set-me x)))
2026 (defconstant dont-set-me 42)
2027 (assert (not (sneak-set-dont-set-me 13)))
2028 (assert (= 42 dont-set-me))
2029 (defun sneak-set-dont-set-me2 (x)
2030   (ignore-errors (setq dont-set-me2 x)))
2031 (defconstant dont-set-me2 (make-instance 'some-constant-thing))
2032 (assert (not (sneak-set-dont-set-me2 13)))
2033 (assert (typep dont-set-me2 'some-constant-thing))
2034
2035 ;;; check that non-trivial constants are EQ across different files: this is
2036 ;;; not something ANSI either guarantees or requires, but we want to do it
2037 ;;; anyways.
2038 (defconstant +share-me-1+ #-inline-constants 123.456d0 #+inline-constants nil)
2039 (defconstant +share-me-2+ "a string to share")
2040 (defconstant +share-me-3+ (vector 1 2 3))
2041 (defconstant +share-me-4+ (* 2 most-positive-fixnum))
2042 (multiple-value-bind (f1 c1) (compile2 '(lambda () (values +share-me-1+
2043                                                            +share-me-2+
2044                                                            +share-me-3+
2045                                                            +share-me-4+
2046                                                            #-inline-constants pi)))
2047   (multiple-value-bind (f2 c2) (compile2 '(lambda () (values +share-me-1+
2048                                                              +share-me-2+
2049                                                              +share-me-3+
2050                                                              +share-me-4+
2051                                                              #-inline-constants pi)))
2052     (flet ((test (fa fb)
2053              (mapc (lambda (a b)
2054                      (assert (eq a b)))
2055                    (multiple-value-list (funcall fa))
2056                    (multiple-value-list (funcall fb)))))
2057       (test f1 c1)
2058       (test f1 f2)
2059       (test f1 c2))))
2060
2061 ;;; user-defined satisfies-types cannot be folded
2062 (deftype mystery () '(satisfies mysteryp))
2063 (defvar *mystery* nil)
2064 (defun mysteryp (x) (eq x *mystery*))
2065 (defstruct thing (slot (error "missing") :type mystery))
2066 (defun test-mystery (m) (when (eq :mystery (thing-slot m)) :ok))
2067 (setf *mystery* :mystery)
2068 (assert (eq :ok (test-mystery (make-thing :slot :mystery))))
2069
2070 ;;; Singleton types can also be constant.
2071 (test-util:with-test (:name :propagate-singleton-types-to-eql)
2072   (macrolet ((test (type value &aux (fun (gensym "FUN")))
2073                `(progn
2074                   (declaim (ftype (function () (values ,type &optional)) ,fun))
2075                   (defun ,fun ()
2076                     ',value)
2077                   (lambda (x)
2078                     (if (eql x (,fun))
2079                         nil
2080                         (eql x (,fun)))))))
2081     (values
2082       (test (eql foo) foo)
2083       (test (integer 0 0) 0)
2084       (test (double-float 0d0 0d0) 0d0)
2085       (test (eql #\c) #\c))))
2086
2087 (declaim (ftype (function () (integer 42 42)) bug-655581))
2088 (defun bug-655581 ()
2089   42)
2090 (declaim (notinline bug-655581))
2091 (test-util:with-test (:name :bug-655581)
2092   (multiple-value-bind (type derived)
2093       (funcall (compile nil `(lambda ()
2094                                (ctu:compiler-derived-type (bug-655581)))))
2095     (assert derived)
2096     (assert (equal '(integer 42 42) type))))
2097
2098 (test-util:with-test (:name :clear-derived-types-on-set-fdefn)
2099   (let ((*evaluator-mode* :compile)
2100         (*derive-function-types* t))
2101     (eval `(progn
2102              (defun clear-derived-types-on-set-fdefn-1 ()
2103                "foo")
2104              (setf (symbol-function 'clear-derived-types-on-set-fdefn-1)
2105                    (constantly "foobar"))
2106              (defun clear-derived-types-on-set-fdefn-2 ()
2107                (length (clear-derived-types-on-set-fdefn-1)))))
2108     (assert (= 6 (clear-derived-types-on-set-fdefn-2)))))
2109
2110 (test-util:with-test (:name (:bug-655126 :derive-function-types t))
2111   (let ((*evaluator-mode* :compile)
2112         (*derive-function-types* t))
2113     (eval `(defun bug-655126 (x) x))
2114     ;; Full warnings are ok due to *derive-function-types* = T.
2115     (assert (eq :full-warning
2116                 (handler-case
2117                     (eval `(defun bug-655126-2 ()
2118                              (bug-655126)))
2119                   ((and warning (not style-warning)) ()
2120                     :full-warning))))
2121     (assert (eq 'bug-655126
2122                 (handler-case
2123                     (eval `(defun bug-655126 (x y)
2124                              (cons x y)))
2125                   ((and warning (not sb-kernel:redefinition-warning)) ()
2126                     :oops))))
2127     (assert (eq :full-warning
2128                 (handler-case
2129                     (eval `(defun bug-655126 (x)
2130                              (bug-655126 x y)))
2131                   ((and warning
2132                     (not style-warning)
2133                     (not sb-kernel:redefinition-warning)) ()
2134                     :full-warning))))))
2135
2136 (test-util:with-test (:name (:bug-655126 :derive-function-types nil))
2137   (let ((*evaluator-mode* :compile))
2138     (eval `(defun bug-655126/b (x) x))
2139     ;; Just style-warning here.
2140     (assert (eq :style-warning
2141                 (handler-case
2142                     (eval `(defun bug-655126-2/b ()
2143                              (bug-655126/b)))
2144                   (style-warning ()
2145                     :style-warning))))
2146     (assert (eq 'bug-655126/b
2147                 (handler-case
2148                     (eval `(defun bug-655126/b (x y)
2149                              (cons x y)))
2150                   ((and warning (not sb-kernel:redefinition-warning)) ()
2151                     :oops))))
2152     ;; Bogus self-call is always worth a full one.
2153     (assert (eq :full-warning
2154                 (handler-case
2155                     (eval `(defun bug-655126/b (x)
2156                              (bug-655126/b x y)))
2157                   ((and warning
2158                     (not style-warning)
2159                     (not sb-kernel:redefinition-warning)) ()
2160                     :full-warning))))))
2161
2162 (test-util:with-test (:name :bug-657499)
2163   ;; Don't trust derived types within the compilation unit.
2164   (ctu:file-compile
2165    `((declaim (optimize safety))
2166      (defun bug-657499-foo ()
2167        (cons t t))
2168      (defun bug-657499-bar ()
2169        (let ((cons (bug-657499-foo)))
2170          (setf (car cons) 3)
2171          cons)))
2172    :load t)
2173   (locally (declare (optimize safety))
2174     (setf (symbol-function 'bug-657499-foo) (constantly "foobar"))
2175     (assert (eq :type-error
2176                 (handler-case
2177                     (funcall 'bug-657499-bar)
2178                   (type-error (e)
2179                     (assert (eq 'cons (type-error-expected-type e)))
2180                     (assert (equal "foobar" (type-error-datum e)))
2181                     :type-error))))))
2182
2183 (declaim (unsigned-byte *symbol-value-test-var*))
2184 (defvar *symbol-value-test-var*)
2185
2186 (declaim (unsigned-byte **global-symbol-value-test-var**))
2187 (defglobal **global-symbol-value-test-var** 0)
2188
2189 (test-util:with-test (:name :symbol-value-type-derivation)
2190   (let ((fun (compile
2191               nil
2192               `(lambda ()
2193                  *symbol-value-test-var*))))
2194     (assert (equal '(function () (values unsigned-byte &optional))
2195                    (%simple-fun-type fun))))
2196   (let ((fun (compile
2197               nil
2198               `(lambda ()
2199                  **global-symbol-value-test-var**))))
2200     (assert (equal '(function () (values unsigned-byte &optional))
2201                    (%simple-fun-type fun))))
2202   (let ((fun (compile
2203               nil
2204               `(lambda (*symbol-value-test-var*)
2205                  (declare (fixnum *symbol-value-test-var*))
2206                  (symbol-value '*symbol-value-test-var*))))
2207         (ufix (type-specifier (specifier-type `(and unsigned-byte fixnum)))))
2208     (assert (equal `(function (,ufix) (values ,ufix &optional))
2209                    (%simple-fun-type fun))))
2210   (let ((fun (compile
2211               nil
2212               `(lambda ()
2213                  (declare (fixnum **global-symbol-value-test-var**))
2214                  (symbol-global-value '**global-symbol-value-test-var**))))
2215         (ufix (type-specifier (specifier-type `(and unsigned-byte fixnum)))))
2216     (assert (equal `(function () (values ,ufix &optional))
2217                    (%simple-fun-type fun)))))
2218
2219 (test-util:with-test (:name :mv-bind-to-let-type-propagation)
2220   (let ((f (compile nil `(lambda (x)
2221                            (declare (optimize speed)
2222                                     (type (integer 20 50) x))
2223                            (< (truncate x 10) 1))))
2224         (g (compile nil `(lambda (x)
2225                            (declare (optimize speed)
2226                                     (type (integer 20 50) x))
2227                            (< (nth-value 1 (truncate x 10)) 10))))
2228         (h (compile nil `(lambda (x)
2229                            (declare (optimize speed)
2230                                     (type (integer 20 50) x))
2231                            (multiple-value-bind (q r)
2232                                (truncate x 10)
2233                              (declare (ignore r))
2234                              (< q 1)))))
2235         (type0 '(function ((integer 20 50)) (values null &optional)))
2236         (type1 '(function ((integer 20 50)) (values (member t) &optional))))
2237     (assert (equal type0 (sb-kernel:%simple-fun-type f)))
2238     (assert (equal type1 (sb-kernel:%simple-fun-type g)))
2239     (assert (equal type0 (sb-kernel:%simple-fun-type h)))))
2240
2241 (test-util:with-test (:name :bug-308921)
2242   (let ((*check-consistency* t))
2243     (ctu:file-compile
2244      `((let ((exported-symbols-alist
2245                (loop for symbol being the external-symbols of :cl
2246                      collect (cons symbol
2247                                    (concatenate 'string
2248                                                 "#"
2249                                                 (string-downcase symbol))))))
2250          (defun hyperdoc-lookup (symbol)
2251            (cdr (assoc symbol exported-symbols-alist)))))
2252      :load nil)))
2253
2254 (test-util:with-test (:name :bug-308941)
2255   (multiple-value-bind (warn fail)
2256       (let ((*check-consistency* t))
2257         (ctu:file-compile
2258          "(eval-when (:compile-toplevel :load-toplevel :execute)
2259             (defstruct foo3))
2260           (defstruct bar
2261             (foo #.(make-foo3)))"
2262          :load nil))
2263     ;; ...but the compiler should not break.
2264     (assert (and warn fail))))
2265
2266 (test-util:with-test (:name :bug-903821)
2267   (let* ((fun (compile nil '(lambda (x n)
2268                              (declare (sb-ext:word x)
2269                               (type (integer 0 #.(1- sb-vm:n-word-bits)) n)
2270                               (optimize speed))
2271                              (logandc2 x (ash -1 n)))))
2272          (trace-output
2273           (with-output-to-string (*trace-output*)
2274             (eval `(trace ,(intern (format nil "ASH-LEFT-MOD~D" sb-vm::n-word-bits) "SB-VM")))
2275             (assert (= 7 (funcall fun 15 3))))))
2276     (assert (string= "" trace-output))))
2277
2278 ;;; success