0.9.2.43:
[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 (load "assertoid.lisp")
19 (use-package "ASSERTOID")
20
21 ;;; Old CMU CL code assumed that the names of "keyword" arguments are
22 ;;; necessarily self-evaluating symbols, but ANSI Common Lisp allows
23 ;;; them to be any symbols, not necessarily keywords, and thus not
24 ;;; necessarily self-evaluating. Make sure that this works.
25 (defun newfangled-cons (&key ((left-thing x)) ((right-thing y)))
26   (cons x y))
27 (assert (equal (cons 1 2) (newfangled-cons 'right-thing 2 'left-thing 1)))
28
29 ;;; ANSI specifically says that duplicate keys are OK in lambda lists,
30 ;;; with no special exception for macro lambda lists. (As reported by
31 ;;; Pierre Mai on cmucl-imp 2001-03-30, Python didn't think so. The
32 ;;; rest of the thread had some entertainment value, at least for me
33 ;;; (WHN). The unbelievers were besmote and now even CMU CL will
34 ;;; conform to the spec in this regard. Who needs diplomacy when you
35 ;;; have brimstone?:-)
36 (defmacro ayup-duplicate-keys-are-ok-i-see-the-lite (&key k)
37   k)
38 (assert (equal (ayup-duplicate-keys-are-ok-i-see-the-lite :k 112) 112))
39 (assert (equal (ayup-duplicate-keys-are-ok-i-see-the-lite :k 'x :k 'y) 'x))
40
41 ;;; As reported by Alexey Dejneka (sbcl-devel 2002-01-30), in
42 ;;; sbcl-0.7.1 plus his patch (i.e. essentially sbcl-0.7.1.2), the
43 ;;; compiler barfed on this, blowing up in FIND-IN-PHYSENV looking for
44 ;;; the LAMBDA-VAR named NUM. That was fixed in sbcl-0.7.1.3.
45 (defun parse-num (index)
46   (let (num x)
47     (flet ((digs ()
48              (setq num index))
49            (z ()
50              (let ()
51                (setq x nil))))
52       (when (and (digs) (digs)) x))))
53
54 ;;; Bug 132: The compiler used to fail to compile INTEGER-valued CATCH
55 ;;; tags. This was fixed by Alexey Dejneka in sbcl-0.7.1.14. (INTEGER
56 ;;; catch tags are still a bad idea because EQ is used to compare
57 ;;; tags, and EQ comparison on INTEGERs is unportable; but now it's a
58 ;;; compiler warning instead of a failure to compile.)
59 (defun foo ()
60   (catch 0 (print 1331)))
61
62 ;;; Bug 150: In sbcl-0.7.1.15, compiling this code caused a failure in
63 ;;; SB-C::ADD-TEST-CONSTRAINTS:
64 ;;;    The value NIL is not of type SB-C::CONTINUATION.
65 ;;; This bug was fixed by APD in sbcl-0.7.1.30.
66 (defun bug150-test1 ()
67   (let* ()
68     (flet ((wufn () (glorp table1 4.9)))
69       (gleep *uustk* #'wufn "#1" (list)))
70     (if (eql (lo foomax 3.2))
71         (values)
72         (error "not ~S" '(eql (lo foomax 3.2))))
73     (values)))
74 ;;; A simpler test case for bug 150: The compiler died with the
75 ;;; same type error when trying to compile this.
76 (defun bug150-test2 ()
77   (let ()
78     (<)))
79
80 ;;; bug 147, fixed by APD 2002-04-28
81 ;;;
82 ;;; This test case used to crash the compiler, e.g. with
83 ;;;   failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)"
84 (defun bug147 (string ind)
85   (flet ((digs ()
86            (let (old-index)
87              (if (and (< ind ind)
88                       (typep (char string ind) '(member #\1)))
89                  nil))))))
90
91 ;;; bug reported and fixed by Matthias Hoelzl sbcl-devel 2002-05-13
92 (defmacro foo-2002-05-13 () ''x)
93 (eval '(foo-2002-05-13))
94 (compile 'foo-2002-05-13)
95 (foo-2002-05-13) ; (The bug caused UNDEFINED-FUNCTION to be signalled here.)
96
97 ;;; floating point pain on the PPC.
98 ;;;
99 ;;; This test case used to fail to compile on most powerpcs prior to
100 ;;; sbcl-0.7.4.2x, as floating point traps were being incorrectly
101 ;;; masked.
102 (defun floating-point-pain (x)
103   (declare (single-float x))
104   (log x))
105
106 ;;; bug found and fixed ca. sbcl-0.7.5.12: The INTERSECTION-TYPE
107 ;;; here satisfies "is a subtype of ARRAY-TYPE", but can't be
108 ;;; accessed with ARRAY-TYPE accessors like
109 ;;; ARRAY-TYPE-SPECIALIZED-ELEMENT-TYPE, so ARRAY-related
110 ;;; DEFTRANSFORMs died with TYPE-ERROR at compile time when
111 ;;; compiling the DEFUN here.
112 (defun stupid-input-to-smart-array-deftransforms-0-7-5-12 (v)
113   (declare (type (and simple-vector fwd-type-ref) v))
114   (aref v 0))
115
116 ;;; Ca. sbcl-0.7.5.15 the compiler would fail an internal consistency
117 ;;; check on this code because it expected all calls to %INSTANCE-REF
118 ;;; to be transformed away, but its expectations were dashed by perverse
119 ;;; code containing app programmer errors like this.
120 (defstruct something-known-to-be-a-struct x y)
121 (multiple-value-bind (fun warnings-p failure-p)
122     (compile nil
123              '(lambda ()
124                 (labels ((a1 (a2 a3)
125                              (cond (t (a4 a2 a3))))
126                          (a4 (a2 a3 a5 a6)
127                              (declare (type (or simple-vector null) a5 a6))
128                              (something-known-to-be-a-struct-x a5))
129                          (a8 (a2 a3)
130                              (a9 #'a1 a10 a2 a3))
131                          (a11 (a2 a3)
132                               (cond ((and (funcall a12 a2)
133                                           (funcall a12 a3))
134                                      (funcall a13 a2 a3))
135                                     (t
136                                      (when a14
137                                      (let ((a15 (a1 a2 a3)))
138                                        ))
139                                      a16))))
140                   (values #'a17 #'a11))))
141   ;; Python sees the structure accessor on the known-not-to-be-a-struct
142   ;; A5 value and is very, very disappointed in you. (But it doesn't
143   ;; signal BUG any more.)
144   (assert failure-p))
145
146 ;;; On the SPARC, there was an erroneous definition of some VOPs used
147 ;;; to compile LOGANDs, which would lead to compilation of the
148 ;;; following function giving rise to a compile-time error (bug
149 ;;; spotted and fixed by Raymond Toy for CMUCL)
150 (defun logand-sparc-bogons (a0 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
151   (declare (type (unsigned-byte 32) a0)
152            (type (signed-byte 32) a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
153            ;; to ensure that the call is a candidate for
154            ;; transformation
155            (optimize (speed 3) (safety 0) (compilation-speed 0) (debug 0)))
156   (values
157    ;; the call that fails compilation
158    (logand a0 a10)
159    ;; a call to prevent the other arguments from being optimized away
160    (logand a1 a2 a3 a4 a5 a6 a7 a8 a9)))
161
162 ;;; bug 192, reported by Einar Floystad Dorum sbcl-devel 2002-08-14,
163 ;;; fixed in sbcl-0.7.6.26: Compiling this function in 0.7.6 caused
164 ;;; the compiler to try to constant-fold DATA-VECTOR-REF, which is OK,
165 ;;; except that there was no non-VOP definition of DATA-VECTOR-REF, so
166 ;;; it would fail.
167 (defun bug192 ()
168       (funcall
169        (LAMBDA (TEXT I L )
170          (LABELS ((G908 (I)
171                     (LET ((INDEX
172                            (OR
173                             (IF (= I L)
174                                 NIL
175                                 (LET ((S TEXT)
176                                       (E (ELT TEXT I)))
177                                   (DECLARE (IGNORABLE S E))
178                                   (WHEN (EQL #\a E)
179                                     (G909 (1+ I))))))))
180                       INDEX))
181                   (G909 (I)
182                     (OR
183                      (IF (= I L)
184                          NIL
185                          (LET ((S TEXT)
186                                (E (ELT TEXT I)))
187                            (DECLARE (IGNORABLE S E))
188                            (WHEN (EQL #\b E) (G910 (1+ I)))))))
189                   (G910 (I)
190                     (LET ((INDEX
191                            (OR
192                             (IF NIL
193                                 NIL
194                                 (LET ((S TEXT))
195                                   (DECLARE (IGNORABLE S))
196                                   (WHEN T I))))))
197                       INDEX)))
198            (G908 I))) "abcdefg" 0 (length "abcdefg")))
199
200 ;;; bugs #65, #70, and #109, closed by APD's patch sbcl-devel 2002-08-17
201 ;;;
202 ;;; This was "YA code deletion bug" whose symptom was the failure of
203 ;;; the assertion
204 ;;;   (EQ (C::LAMBDA-TAIL-SET C::CALLER)
205 ;;;       (C::LAMBDA-TAIL-SET (C::LAMBDA-HOME C::CALLEE)))
206 ;;; at compile time.
207 (defun bug65-1 (termx termy) ; from Carl Witty on submit bugs list, debian.org
208   (labels
209     ((alpha-equal-bound-term-lists (listx listy)
210        (or (and (null listx) (null listy))
211            (and listx listy
212                 (let ((bindings-x (bindings-of-bound-term (car listx)))
213                       (bindings-y (bindings-of-bound-term (car listy))))
214                   (if (and (null bindings-x) (null bindings-y))
215                       (alpha-equal-terms (term-of-bound-term (car listx))
216                                          (term-of-bound-term (car listy)))
217                       (and (= (length bindings-x) (length bindings-y))
218                            (prog2
219                                (enter-binding-pairs (bindings-of-bound-term (car listx))
220                                                     (bindings-of-bound-term (car listy)))
221                                (alpha-equal-terms (term-of-bound-term (car listx))
222                                                   (term-of-bound-term (car listy)))
223                              (exit-binding-pairs (bindings-of-bound-term (car listx))
224                                                  (bindings-of-bound-term (car listy)))))))
225                 (alpha-equal-bound-term-lists (cdr listx) (cdr listy)))))
226
227      (alpha-equal-terms (termx termy)
228        (if (and (variable-p termx)
229                 (variable-p termy))
230            (equal-bindings (id-of-variable-term termx)
231                            (id-of-variable-term termy))
232            (and (equal-operators-p (operator-of-term termx) (operator-of-term termy))
233                 (alpha-equal-bound-term-lists (bound-terms-of-term termx)
234                                               (bound-terms-of-term termy))))))
235
236     (or (eq termx termy)
237         (and termx termy
238              (with-variable-invocation (alpha-equal-terms termx termy))))))
239 (defun bug65-2 () ; from Bob Rogers cmucl-imp 1999-07-28
240   ;; Given an FSSP alignment file named by the argument . . .
241   (labels ((get-fssp-char ()
242              (get-fssp-char))
243            (read-fssp-char ()
244              (get-fssp-char)))
245     ;; Stub body, enough to tickle the bug.
246     (list (read-fssp-char)
247           (read-fssp-char))))
248 (defun bug70 ; from David Young cmucl-help 30 Nov 2000
249     (item sequence &key (test #'eql))
250   (labels ((find-item (obj seq test &optional (val nil))
251                       (let ((item (first seq)))
252                         (cond ((null seq)
253                                (values nil nil))
254                               ((funcall test obj item)
255                                (values val seq))
256                               (t
257                                (find-item obj
258                                           (rest seq)
259                                           test
260                                           (nconc val `(,item))))))))
261     (find-item item sequence test)))
262 (defun bug109 () ; originally from CMU CL bugs collection, reported as
263                  ; SBCL bug by MNA 2001-06-25
264   (labels
265       ((eff (&key trouble)
266             (eff)
267             ;; nil
268             ;; Uncomment and it works
269             ))
270     (eff)))
271
272 ;;; bug 192a, fixed by APD "more strict type checking" patch
273 ;;; (sbcl-devel 2002-08-07)
274 (defun bug192a (x)
275   (declare (optimize (speed 0) (safety 3)))
276   ;; Even with bug 192a, this declaration was checked as an assertion.
277   (declare (real x))
278   (+ x
279      (locally
280        ;; Because of bug 192a, this declaration was trusted without checking.
281        (declare (single-float x))
282        (sin x))))
283 (assert (null (ignore-errors (bug192a nil))))
284 (multiple-value-bind (result error) (ignore-errors (bug192a 100))
285   (assert (null result))
286   (assert (equal (type-error-expected-type error) 'single-float)))
287
288 ;;; bug 194, fixed in part by APD "more strict type checking" patch
289 ;;; (sbcl-devel 2002-08-07)
290 (progn
291   (multiple-value-bind (result error)
292       (ignore-errors (multiple-value-prog1 (progn (the real '(1 2 3)))))
293     (assert (null result))
294     (assert (typep error 'type-error)))
295   (multiple-value-bind (result error)
296       (ignore-errors (the real '(1 2 3)))
297     (assert (null result))
298     (assert (typep error 'type-error))))
299
300 (defun bug194d ()
301   (null (ignore-errors
302           (let ((arg1 1)
303                 (arg2 (identity (the real #(1 2 3)))))
304             (if (< arg1 arg2) arg1 arg2)))))
305 (assert (eq (bug194d) t))
306
307 \f
308 ;;; BUG 48a. and b. (symbol-macrolet handling), fixed by Eric Marsden
309 ;;; and Raymond Toy for CMUCL, fix ported for sbcl-0.7.6.18.
310 (multiple-value-bind (function warnings-p failure-p)
311     (compile nil '(lambda ()
312                    ;; not interested in the package lock violation here
313                    (declare (sb-ext:disable-package-locks t))
314                    (symbol-macrolet ((t nil)) t)))
315   (assert failure-p)
316   (assert (raises-error? (funcall function) program-error)))
317 (multiple-value-bind (function warnings-p failure-p)
318     (compile nil
319              '(lambda ()
320                ;; not interested in the package lock violation here
321                (declare (sb-ext:disable-package-locks *standard-input*))
322                 (symbol-macrolet ((*standard-input* nil))
323                   *standard-input*)))
324   (assert failure-p)
325   (assert (raises-error? (funcall function) program-error)))
326 (multiple-value-bind (function warnings-p failure-p)
327     (compile nil '(lambda () (symbol-macrolet ((s nil)) (declare (special s)) s)))
328   (assert failure-p)
329   (assert (raises-error? (funcall function) program-error)))
330 \f
331 ;;; bug 120a: Turned out to be constraining code looking like (if foo
332 ;;; <X> <X>) where <X> was optimized by the compiler to be the exact
333 ;;; same block in both cases, but not turned into (PROGN FOO <X>).
334 ;;; Fixed by APD in sbcl-0.7.7.2, who provided this test:
335 (declaim (inline dont-constrain-if-too-much))
336 (defun dont-constrain-if-too-much (frame up-frame)
337   (declare (optimize (speed 3) (safety 1) (debug 1)))
338   (if (or (not frame) t)
339       frame
340       "bar"))
341 (defun dont-constrain-if-too-much-aux (x y)
342   (declare (optimize (speed 3) (safety 1) (debug 1)))
343   (if x t (if y t (dont-constrain-if-too-much x y))))
344
345 (assert (null (dont-constrain-if-too-much-aux nil nil)))
346
347 ;;; TYPE-ERROR confusion ca. sbcl-0.7.7.24, reported and fixed by
348 ;;; APD sbcl-devel 2002-09-14
349 (defun exercise-0-7-7-24-bug (x)
350   (declare (integer x))
351   (let (y)
352     (setf y (the single-float (if (> x 0) x 3f0)))
353     (list y y)))
354 (multiple-value-bind (v e) (ignore-errors (exercise-0-7-7-24-bug 4))
355   (assert (null v))
356   (assert (typep e 'type-error)))
357 (assert (equal (exercise-0-7-7-24-bug -4) '(3f0 3f0)))
358
359 ;;; non-intersecting type declarations were DWIMing in a confusing
360 ;;; fashion until sbcl-0.7.7.28, when APD reported and fixed the
361 ;;; problem.
362 (defun non-intersecting-the (x)
363   (let (y)
364     (setf y (the single-float (the integer x)))
365     (list y y)))
366
367 (raises-error? (foo 3) type-error)
368 (raises-error? (foo 3f0) type-error)
369
370 ;;; until 0.8.2 SBCL did not check THEs in arguments
371 (defun the-in-arguments-aux (x)
372   x)
373 (defun the-in-arguments-1 (x)
374   (list x (the-in-arguments-aux (the (single-float 0s0) x))))
375 (defun the-in-arguments-2 (x)
376   (list x (the-in-arguments-aux (the single-float x))))
377
378 (multiple-value-bind (result condition)
379     (ignore-errors (the-in-arguments-1 1))
380   (assert (null result))
381   (assert (typep condition 'type-error)))
382 (multiple-value-bind (result condition)
383     (ignore-errors (the-in-arguments-2 1))
384   (assert (null result))
385   (assert (typep condition 'type-error)))
386
387 ;;; bug 153: a hole in a structure slot type checking
388 (declaim (optimize safety))
389 (defstruct foo153
390   (bla 0 :type fixnum))
391 (defun bug153-1 ()
392   (let ((foo (make-foo153)))
393     (setf (foo153-bla foo) '(1 . 1))
394     (format t "Is ~a of type ~a a cons? => ~a~%"
395             (foo153-bla foo)
396             (type-of (foo153-bla foo))
397             (consp (foo153-bla foo)))))
398 (defun bug153-2 (x)
399   (let ((foo (make-foo153)))
400     (setf (foo153-bla foo) x)
401     (format t "Is ~a of type ~a a cons? => ~a~%"
402             (foo153-bla foo)
403             (type-of (foo153-bla foo))
404             (consp (foo153-bla foo)))))
405
406 (multiple-value-bind (result condition)
407     (ignore-errors (bug153-1))
408   (declare (ignore result))
409   (assert (typep condition 'type-error)))
410 (multiple-value-bind (result condition)
411     (ignore-errors (bug153-2 '(1 . 1)))
412   (declare (ignore result))
413   (assert (typep condition 'type-error)))
414
415 ;;;; bug 110: the compiler flushed the argument type test and the default
416 ;;;; case in the cond.
417 ;
418 ;(locally (declare (optimize (safety 3) (speed 2)))
419 ;  (defun bug110 (x)
420 ;    (declare (optimize (safety 2) (speed 3)))
421 ;    (declare (type (or string stream) x))
422 ;    (cond ((typep x 'string) 'string)
423 ;          ((typep x 'stream) 'stream)
424 ;          (t
425 ;           'none))))
426 ;
427 ;(multiple-value-bind (result condition)
428 ;    (ignore-errors (bug110 0))
429 ;  (declare (ignore result))
430 ;  (assert (typep condition 'type-error)))
431
432 ;;; bug 202: the compiler failed to compile a function, which derived
433 ;;; type contradicted declared.
434 (declaim (ftype (function () null) bug202))
435 (defun bug202 ()
436   t)
437
438 ;;; bugs 178, 199: compiler failed to compile a call of a function
439 ;;; with a hairy type
440 (defun bug178 (x)
441       (funcall (the function (the standard-object x))))
442
443 (defun bug199-aux (f)
444   (eq nil (funcall f)))
445
446 (defun bug199 (f x)
447   (declare (type (and function (satisfies bug199-aux)) f))
448   (funcall f x))
449
450 ;;; check non-toplevel DEFMACRO
451 (defvar *defmacro-test-status* nil)
452
453 (defun defmacro-test ()
454   (fmakunbound 'defmacro-test-aux)
455   (let* ((src "defmacro-test.lisp")
456          (obj (compile-file-pathname src)))
457     (unwind-protect
458          (progn
459            (compile-file src)
460            (assert (equal *defmacro-test-status* '(function a)))
461            (setq *defmacro-test-status* nil)
462            (load obj)
463            (assert (equal *defmacro-test-status* nil))
464            (macroexpand '(defmacro-test-aux 'a))
465            (assert (equal *defmacro-test-status* '(macro 'a z-value)))
466            (eval '(defmacro-test-aux 'a))
467            (assert (equal *defmacro-test-status* '(expanded 'a z-value))))
468       (ignore-errors (delete-file obj)))))
469
470 (defmacro-test)
471
472 ;;; bug 204: EVAL-WHEN inside a local environment
473 (defvar *bug204-test-status*)
474
475 (defun bug204-test ()
476   (let* ((src "bug204-test.lisp")
477          (obj (compile-file-pathname src)))
478     (unwind-protect
479          (progn
480            (setq *bug204-test-status* nil)
481            (compile-file src)
482            (assert (equal *bug204-test-status* '((:expanded :load-toplevel)
483                                                  (:called :compile-toplevel)
484                                                  (:expanded :compile-toplevel))))
485            (setq *bug204-test-status* nil)
486            (load obj)
487            (assert (equal *bug204-test-status* '((:called :load-toplevel)))))
488       (ignore-errors (delete-file obj)))))
489
490 (bug204-test)
491
492 ;;; toplevel SYMBOL-MACROLET
493 (defvar *symbol-macrolet-test-status*)
494
495 (defun symbol-macrolet-test ()
496   (let* ((src "symbol-macrolet-test.lisp")
497          (obj (compile-file-pathname src)))
498     (unwind-protect
499          (progn
500            (setq *symbol-macrolet-test-status* nil)
501            (compile-file src)
502            (assert (equal *symbol-macrolet-test-status*
503                           '(2 1)))
504            (setq *symbol-macrolet-test-status* nil)
505            (load obj)
506            (assert (equal *symbol-macrolet-test-status* '(2))))
507       (ignore-errors (delete-file obj)))))
508
509 (symbol-macrolet-test)
510
511 ;;; On the x86, this code failed to compile until sbcl-0.7.8.37:
512 (defun x86-assembler-failure (x)
513   (declare (optimize (speed 3) (safety 0)))
514   (eq (setf (car x) 'a) nil))
515
516 ;;; bug 211: :ALLOW-OTHER-KEYS
517 (defun bug211d (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
518   (list x x-p y y-p))
519
520 (assert (equal (bug211d) '(:x nil :y nil)))
521 (assert (equal (bug211d :x 1) '(1 t :y nil)))
522 (assert (raises-error? (bug211d :y 2) program-error))
523 (assert (equal (bug211d :y 2 :allow-other-keys t :allow-other-keys nil)
524                '(:x nil t t)))
525 (assert (raises-error? (bug211d :y 2 :allow-other-keys nil) program-error))
526
527 (let ((failure-p
528        (nth-value
529         3
530         (compile 'bug211b
531                  '(lambda ()
532                    (flet ((test (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
533                             (list x x-p y y-p)))
534                      (assert (equal (test) '(:x nil :y nil)))
535                      (assert (equal (test :x 1) '(1 t :y nil)))
536                      (assert (equal (test :y 2 :allow-other-keys 11 :allow-other-keys nil)
537                                     '(:x nil 11 t)))))))))
538   (assert (not failure-p))
539   (bug211b))
540
541 (let ((failure-p
542        (nth-value
543         3
544         (compile 'bug211c
545                  '(lambda ()
546                    (flet ((test (&key (x :x x-p))
547                             (list x x-p)))
548                      (assert (equal (test) '(:x nil)))
549                      (assert (equal (test :x 1) '(1 t)))
550                      (assert (equal (test :y 2 :allow-other-keys 11 :allow-other-keys nil)
551                                     '(:x nil)))))))))
552   (assert (not failure-p))
553   (bug211c))
554
555 (dolist (form '((test :y 2)
556                 (test :y 2 :allow-other-keys nil)
557                 (test :y 2 :allow-other-keys nil :allow-other-keys t)))
558   (multiple-value-bind (result warnings-p failure-p)
559       (compile nil `(lambda ()
560                      (flet ((test (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
561                               (list x x-p y y-p)))
562                        ,form)))
563     (assert failure-p)
564     (assert (raises-error? (funcall result) program-error))))
565
566 ;;; bug 217: wrong type inference
567 (defun bug217-1 (x s)
568   (let ((f (etypecase x
569              (character #'write-char)
570              (integer #'write-byte))))
571     (funcall f x s)
572     (etypecase x
573       (character (write-char x s))
574       (integer (write-byte x s)))))
575 (bug217-1 #\1 *standard-output*)
576
577
578 ;;; bug 221: tried and died on CSUBTYPEP (not VALUES-SUBTYPEP) of the
579 ;;; function return types when inferring the type of the IF expression
580 (declaim (ftype (function (fixnum) (values package boolean)) bug221f1))
581 (declaim (ftype (function (t) (values package boolean)) bug221f2))
582 (defun bug221 (b x)
583   (funcall (if b #'bug221f1 #'bug221f2) x))
584 \f
585 ;;; bug 172: macro lambda lists were too permissive until 0.7.9.28
586 ;;; (fix provided by Matthew Danish) on sbcl-devel
587 (assert (null (ignore-errors
588                 (defmacro bug172 (&rest rest foo) `(list ,rest ,foo)))))
589
590 ;;; embedded THEs
591 (defun check-embedded-thes (policy1 policy2 x y)
592   (handler-case
593       (funcall (compile nil
594                         `(lambda (f)
595                            (declare (optimize (speed 2) (safety ,policy1)))
596                            (multiple-value-list
597                             (the (values (integer 2 3) t &optional)
598                               (locally (declare (optimize (safety ,policy2)))
599                                 (the (values t (single-float 2f0 3f0) &optional)
600                                   (funcall f)))))))
601                (lambda () (values x y)))
602     (type-error (error)
603       error)))
604
605 (assert (equal (check-embedded-thes 0 0  :a :b) '(:a :b)))
606
607 (assert (equal (check-embedded-thes 0 3  :a 2.5f0) '(:a 2.5f0)))
608 (assert (typep (check-embedded-thes 0 3  2 3.5f0) 'type-error))
609
610 (assert (equal (check-embedded-thes 0 1  :a 3.5f0) '(:a 3.5f0)))
611 (assert (typep (check-embedded-thes 0 1  2 2.5d0) 'type-error))
612
613 (assert (equal (check-embedded-thes 3 0  2 :a) '(2 :a)))
614 (assert (typep (check-embedded-thes 3 0  4 2.5f0) 'type-error))
615
616 (assert (equal (check-embedded-thes 1 0  4 :b) '(4 :b)))
617 (assert (typep (check-embedded-thes 1 0  1.0 2.5f0) 'type-error))
618
619
620 (assert (equal (check-embedded-thes 3 3  2 2.5f0) '(2 2.5f0)))
621 (assert (typep (check-embedded-thes 3 3  0 2.5f0) 'type-error))
622 (assert (typep (check-embedded-thes 3 3  2 3.5f0) 'type-error))
623 \f
624 ;;; INLINE inside MACROLET
625 (declaim (inline to-be-inlined))
626 (macrolet ((def (x) `(defun ,x (y) (+ y 1))))
627   (def to-be-inlined))
628 (defun call-inlined (z)
629   (to-be-inlined z))
630 (assert (= (call-inlined 3) 4))
631 (macrolet ((frob (x) `(+ ,x 3)))
632   (defun to-be-inlined (y)
633     (frob y)))
634 (assert (= (call-inlined 3)
635            ;; we should have inlined the previous definition, so the
636            ;; new one won't show up yet.
637            4))
638 (defun call-inlined (z)
639   (to-be-inlined z))
640 (assert (= (call-inlined 3) 6))
641 (defun to-be-inlined (y)
642   (+ y 5))
643 (assert (= (call-inlined 3) 6))
644 \f
645 ;;; DEFINE-COMPILER-MACRO to work as expected, not via weird magical
646 ;;; IR1 pseudo-:COMPILE-TOPLEVEL handling
647 (defvar *bug219-a-expanded-p* nil)
648 (defun bug219-a (x)
649   (+ x 1))
650 (define-compiler-macro bug219-a (&whole form y)
651   (setf *bug219-a-expanded-p* t)
652   (if (constantp y)
653       (+ (eval y) 2)
654       form))
655 (defun bug219-a-aux ()
656   (bug219-a 2))
657 (assert (= (bug219-a-aux)
658            (if *bug219-a-expanded-p* 4 3)))
659 (defvar *bug219-a-temp* 3)
660 (assert (= (bug219-a *bug219-a-temp*) 4))
661
662 (defvar *bug219-b-expanded-p* nil)
663 (defun bug219-b-aux1 (x)
664   (when x
665     (define-compiler-macro bug219-b (y)
666       (setf *bug219-b-expanded-p* t)
667       `(+ ,y 2))))
668 (defun bug219-b-aux2 (z)
669   (bug219-b z))
670 (assert (not *bug219-b-expanded-p*))
671 (assert (raises-error? (bug219-b-aux2 1) undefined-function))
672 (bug219-b-aux1 t)
673 (defun bug219-b-aux2 (z)
674   (bug219-b z))
675 (defun bug219-b (x)
676   x)
677 (assert (= (bug219-b-aux2 1)
678            (if *bug219-b-expanded-p* 3 1)))
679
680 ;;; bug 224: failure in unreachable code deletion
681 (defmacro do-optimizations (&body body)
682   `(dotimes (.speed. 4)
683      (dotimes (.space. 4)
684        (dotimes (.debug. 4)
685          (dotimes (.compilation-speed. 4)
686            (proclaim `(optimize (speed , .speed.) (space , .space.)
687                                 (debug , .debug.)
688                                 (compilation-speed , .compilation-speed.)))
689            ,@body)))))
690
691 (do-optimizations
692     (compile nil
693              (read-from-string
694               "(lambda () (#:localy (declare (optimize (safety 3)))
695                                     (ignore-errors (progn (values-list (car (list '(1 . 2)))) t))))")))
696
697 (do-optimizations
698     (compile nil '(lambda ()
699                    (labels ((ext ()
700                               (tagbody
701                                  (labels ((i1 () (list (i2) (i2)))
702                                           (i2 () (list (int) (i1)))
703                                           (int () (go :exit)))
704                                    (list (i1) (i1) (i1)))
705                                :exit (return-from ext)
706                                  )))
707                      (list (error "nih") (ext) (ext))))))
708
709 (do-optimizations
710   (compile nil '(lambda (x) (let ((y (error ""))) (list x y)))))
711
712 ;;; bug 223: invalid moving of global function name referencing
713 (defun bug223-int (n)
714   `(int ,n))
715
716 (defun bug223-wrap ()
717   (let ((old #'bug223-int))
718     (setf (fdefinition 'bug223-int)
719           (lambda (n)
720             (assert (> n 0))
721             `(ext ,@(funcall old (1- n)))))))
722 (compile 'bug223-wrap)
723
724 (assert (equal (bug223-int 4) '(int 4)))
725 (bug223-wrap)
726 (assert (equal (bug223-int 4) '(ext int 3)))
727 (bug223-wrap)
728 (assert (equal (bug223-int 4) '(ext ext int 2)))
729 \f
730 ;;; COERCE got its own DEFOPTIMIZER which has to reimplement most of
731 ;;; SPECIFIER-TYPE-NTH-ARG.  For a while, an illegal type would throw
732 ;;; you into the debugger on compilation.
733 (defun coerce-defopt1 (x)
734   ;; illegal, but should be compilable.
735   (coerce x '(values t)))
736 (defun coerce-defopt2 (x)
737   ;; illegal, but should be compilable.
738   (coerce x '(values t &optional)))
739 (assert (null (ignore-errors (coerce-defopt1 3))))
740 (assert (null (ignore-errors (coerce-defopt2 3))))
741 \f
742 ;;; Oops.  In part of the (CATCH ..) implementation of DEBUG-RETURN,
743 ;;; it was possible to confuse the type deriver of the compiler
744 ;;; sufficiently that compiler invariants were broken (explained by
745 ;;; APD sbcl-devel 2003-01-11).
746
747 ;;; WHN's original report
748 (defun debug-return-catch-break1 ()
749   (with-open-file (s "/tmp/foo"
750                      :direction :output
751                      :element-type (list
752                                     'signed-byte
753                                     (1+
754                                      (integer-length most-positive-fixnum))))
755     (read-byte s)
756     (read-byte s)
757     (read-byte s)
758     (read-byte s)))
759
760 ;;; APD's simplified test case
761 (defun debug-return-catch-break2 (x)
762   (declare (type (vector (unsigned-byte 8)) x))
763   (setq *y* (the (unsigned-byte 8) (aref x 4))))
764 \f
765 ;;; FUNCTION-LAMBDA-EXPRESSION should return something that's COMPILE
766 ;;; can understand.  Here's a simple test for that on a function
767 ;;; that's likely to return a hairier list than just a lambda:
768 (macrolet ((def (fn) `(progn
769                        (declaim (inline ,fn))
770                        (defun ,fn (x) (1+ x)))))
771   (def bug228))
772 (let ((x (function-lambda-expression #'bug228)))
773   (when x
774     (assert (= (funcall (compile nil x) 1) 2))))
775
776 ;;;
777 (defun bug192b (i)
778   (dotimes (j i)
779     (declare (type (mod 4) i))
780     (unless (< i 5)
781       (print j))))
782 (assert (raises-error? (bug192b 6) type-error))
783
784 (defun bug192c (x y)
785   (locally (declare (type fixnum x y))
786     (+ x (* 2 y))))
787 (assert (raises-error? (bug192c 1.1 2) type-error))
788
789 (assert (raises-error? (progn (the real (list 1)) t) type-error))
790
791 (defun bug236 (a f)
792   (declare (optimize (speed 2) (safety 0)))
793   (+ 1d0
794      (the double-float
795        (multiple-value-prog1
796            (svref a 0)
797          (unless f (return-from bug236 0))))))
798 (assert (eql (bug236 #(4) nil) 0))
799
800 ;;; Bug reported by reported by rif on c.l.l 2003-03-05
801 (defun test-type-of-special-1 (x)
802   (declare (special x)
803            (fixnum x)
804            (optimize (safety 3)))
805   (list x))
806 (defun test-type-of-special-2 (x)
807   (declare (special x)
808            (fixnum x)
809            (optimize (safety 3)))
810   (list x (setq x (/ x 2)) x))
811 (assert (raises-error? (test-type-of-special-1 3/2) type-error))
812 (assert (raises-error? (test-type-of-special-2 3) type-error))
813 (assert (equal (test-type-of-special-2 8) '(8 4 4)))
814
815 ;;; bug which existed in 0.8alpha.0.4 for several milliseconds before
816 ;;; APD fixed it in 0.8alpha.0.5
817 (defun frob8alpha04 (x y)
818   (+ x y))
819 (defun baz8alpha04 (this kids)
820   (flet ((n-i (&rest rest)
821            ;; Removing the #+NIL here makes the bug go away.
822            #+nil (format t "~&in N-I REST=~S~%" rest)
823            (apply #'frob8alpha04 this rest)))
824     (n-i kids)))
825 ;;; failed in 0.8alpha.0.4 with "The value 13 is not of type LIST."
826 (assert (= (baz8alpha04 12 13) 25))
827
828 ;;; evaluation order in structure slot writers
829 (defstruct sswo
830   a b)
831 (let* ((i 0)
832        (s (make-sswo :a (incf i) :b (incf i)))
833        (l (list s :v)))
834   (assert (= (sswo-a s) 1))
835   (assert (= (sswo-b s) 2))
836   (setf (sswo-a (pop l)) (pop l))
837   (assert (eq l nil))
838   (assert (eq (sswo-a s) :v)))
839
840 (defun bug249 (x)
841   (flet ((bar (y)
842            (declare (fixnum y))
843            (incf x)))
844     (list (bar x) (bar x) (bar x))))
845
846 (assert (raises-error? (bug249 1.0) type-error))
847
848 ;;; bug reported by ohler on #lisp 2003-07-10
849 (defun bug-ohler-2003-07-10 (a b)
850   (declare (optimize (speed 0) (safety 3) (space 0)
851                      (debug 1) (compilation-speed 0)))
852   (adjoin a b))
853
854 ;;; bug reported by Doug McNaught on sbcl-devel 2003-09-14:
855 ;;; COMPILE-FILE did not bind *READTABLE*
856 (let* ((source "bug-doug-mcnaught-20030914.lisp")
857        (fasl (compile-file-pathname source)))
858   (labels ((check ()
859              (assert (null (get-macro-character #\]))))
860            (full-check ()
861              (check)
862              (assert (typep *bug-doug-mcnaught-20030914*
863                             '(simple-array (unsigned-byte 4) (*))))
864              (assert (equalp *bug-doug-mcnaught-20030914* #(1 2 3)))
865              (makunbound '*bug-doug-mcnaught-20030914*)))
866     (compile-file source)
867     (check)
868     (load fasl)
869     (full-check)
870     (load source)
871     (full-check)
872     (delete-file fasl)))
873 \f
874 (defun expt-derive-type-bug (a b)
875   (unless (< a b)
876     (truncate (expt a b))))
877 (assert (equal (multiple-value-list (expt-derive-type-bug 1 1))
878                '(1 0)))
879
880 ;;; Problems with type checking in functions with EXPLICIT-CHECK
881 ;;; attribute (reported by Peter Graves)
882 (loop for (fun . args) in '((= a) (/= a)
883                             (< a) (<= a) (> a) (>= a))
884       do (assert (raises-error? (apply fun args) type-error)))
885
886 (defclass broken-input-stream (sb-gray:fundamental-input-stream) ())
887 (defmethod sb-gray:stream-read-char ((stream broken-input-stream))
888   (throw 'break :broken))
889 (assert (eql (block return
890                (handler-case
891                    (catch 'break
892                      (funcall (eval ''peek-char)
893                               1 (make-instance 'broken-input-stream))
894                      :test-broken)
895                  (type-error (c)
896                    (return-from return :good))))
897              :good))
898 \f
899 ;;;; MUFFLE-CONDITIONS test (corresponds to the test in the manual)
900 (defvar *compiler-note-count* 0)
901 #-(or alpha x86-64) ; FIXME: make a better test!
902 (handler-bind ((sb-ext:compiler-note (lambda (c)
903                                        (declare (ignore c))
904                                        (incf *compiler-note-count*))))
905   (let ((fun
906          (compile nil
907                   '(lambda (x)
908                     (declare (optimize speed) (fixnum x))
909                     (declare (sb-ext:muffle-conditions sb-ext:compiler-note))
910                     (values (* x 5) ; no compiler note from this
911                      (locally
912                        (declare (sb-ext:unmuffle-conditions sb-ext:compiler-note))
913                        ;; this one gives a compiler note
914                        (* x -5)))))))
915     (assert (= *compiler-note-count* 1))
916     (assert (equal (multiple-value-list (funcall fun 1)) '(5 -5)))))
917 \f
918 (handler-case
919     (eval '(flet ((%f (&key) nil)) (%f nil nil)))
920   (error (c) :good)
921   (:no-error (val) (error "no error: ~S" val)))
922 (handler-case
923     (eval '(labels ((%f (&key x) x)) (%f nil nil)))
924   (error (c) :good)
925   (:no-error (val) (error "no error: ~S" val)))
926 \f
927 ;;;; tests not in the problem domain, but of the consistency of the
928 ;;;; compiler machinery itself
929
930 (in-package "SB-C")
931
932 ;;; Hunt for wrong-looking things in fundamental compiler definitions,
933 ;;; and gripe about them.
934 ;;;
935 ;;; FIXME: It should be possible to (1) repair the things that this
936 ;;; code gripes about, and then (2) make the code signal errors
937 ;;; instead of just printing complaints to standard output, in order
938 ;;; to prevent the code from later falling back into disrepair.
939 (defun grovel-results (function)
940   (dolist (template (fun-info-templates (info :function :info function)))
941     (when (template-more-results-type template)
942       (format t "~&Template ~A has :MORE results, and translates ~A.~%"
943               (template-name template)
944               function)
945       (return nil))
946     (when (eq (template-result-types template) :conditional)
947       ;; dunno.
948       (return t))
949     (let ((types (template-result-types template))
950           (result-type (fun-type-returns (info :function :type function))))
951       (cond
952         ((values-type-p result-type)
953          (do ((ltypes (append (args-type-required result-type)
954                               (args-type-optional result-type))
955                       (rest ltypes))
956               (types types (rest types)))
957              ((null ltypes)
958               (unless (null types)
959                 (format t "~&More types than ltypes in ~A, translating ~A.~%"
960                         (template-name template)
961                         function)
962                 (return nil)))
963            (when (null types)
964              (unless (null ltypes)
965                (format t "~&More ltypes than types in ~A, translating ~A.~%"
966                        (template-name template)
967                        function)
968                (return nil)))))
969         ((eq result-type (specifier-type nil))
970          (unless (null types)
971            (format t "~&Template ~A returns values for function ~A with RESULT-TYPE NIL.~%"
972                    (template-name template)
973                    function)
974            (return nil)))
975         ((/= (length types) 1)
976          (format t "~&Template ~A isn't returning 1 value for ~A.~%"
977                  (template-name template)
978                  function)
979          (return nil))
980         (t t)))))
981 (defun identify-suspect-vops (&optional (env (first
982                                               (last *info-environment*))))
983   (do-info (env :class class :type type :name name :value value)
984     (when (and (eq class :function) (eq type :type))
985       ;; OK, so we have an entry in the INFO database. Now, if ...
986       (let* ((info (info :function :info name))
987              (templates (and info (fun-info-templates info))))
988         (when templates
989           ;; ... it has translators
990           (grovel-results name))))))
991 (identify-suspect-vops)
992 \f
993 ;;;; tests for compiler output
994 (let* ((*error-output* (make-broadcast-stream))
995        (output (with-output-to-string (*standard-output*)
996                  (compile-file "compiler-output-test.lisp"
997                                :print nil :verbose nil))))
998   (print output)
999   (assert (zerop (length output))))
1000
1001 ;;;; bug 305: INLINE/NOTINLINE causing local ftype to be lost
1002
1003 (define-condition optimization-error (error) ())
1004
1005 (labels ((compile-lambda (type sense)
1006            (handler-bind ((compiler-note (lambda (_)
1007                                            (declare (ignore _))
1008                                            (error 'optimization-error))))
1009              (values
1010               (compile
1011                nil
1012                `(lambda ()
1013                   (declare
1014                    ,@(when type '((ftype (function () (integer 0 10)) bug-305)))
1015                    (,sense bug-305)
1016                    (optimize speed))
1017                   (1+ (bug-305))))
1018               nil)))
1019          (expect-error (sense)
1020            (multiple-value-bind (f e)  (ignore-errors (compile-lambda nil sense))
1021              (assert (not f))
1022              (assert (typep e 'optimization-error))))
1023          (expect-pass (sense)
1024            (multiple-value-bind (f e)  (ignore-errors (compile-lambda t sense))
1025              (assert f)
1026              (assert (not e)))))
1027   (expect-error 'inline)
1028   (expect-error 'notinline)
1029   (expect-pass 'inline)
1030   (expect-pass 'notinline))
1031
1032 ;;; bug 211e: bogus style warning from duplicated keyword argument to
1033 ;;; a local function.
1034 (handler-bind ((style-warning #'error))
1035   (let ((f (compile nil '(lambda ()
1036                           (flet ((foo (&key y) (list y)))
1037                             (list (foo :y 1 :y 2)))))))
1038     (assert (equal '((1)) (funcall f)))))
1039
1040 ;;; check that EQL is optimized when other argument is (OR SYMBOL FIXNUM).
1041 (handler-bind ((compiler-note #'error))
1042   (let ((f1 (compile nil '(lambda (x1 y1)
1043                            (declare (type (or symbol fixnum) x1)
1044                                     (optimize speed))
1045                            (eql x1 y1))))
1046         (f2 (compile nil '(lambda (x2 y2)
1047                            (declare (type (or symbol fixnum) y2)
1048                                     (optimize speed))
1049                            (eql x2 y2)))))
1050     (let ((fix (random most-positive-fixnum))
1051           (sym (gensym))
1052           (e-count 0))
1053       (assert (funcall f1 fix fix))
1054       (assert (funcall f2 fix fix))
1055       (assert (funcall f1 sym sym))
1056       (assert (funcall f2 sym sym))
1057       (handler-bind ((type-error (lambda (c)
1058                                    (incf e-count)
1059                                    (continue c))))
1060         (flet ((test (f x y)
1061                  (with-simple-restart (continue "continue with next test")
1062                    (funcall f x y)
1063                    (error "fell through with (~S ~S ~S)" f x y))))
1064           (test f1 "oops" 42)
1065           (test f1 (1+ most-positive-fixnum) 42)
1066           (test f2 42 "oops")
1067           (test f2 42 (1+ most-positive-fixnum))))
1068       (assert (= e-count 4)))))
1069
1070 ;;; success
1071 (quit :unix-status 104)