0.7.10.10:
[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 (cl:in-package :cl-user)
19
20 (load "assertoid.lisp")
21
22 ;;; Old CMU CL code assumed that the names of "keyword" arguments are
23 ;;; necessarily self-evaluating symbols, but ANSI Common Lisp allows
24 ;;; them to be any symbols, not necessarily keywords, and thus not
25 ;;; necessarily self-evaluating. Make sure that this works.
26 (defun newfangled-cons (&key ((left-thing x)) ((right-thing y)))
27   (cons x y))
28 (assert (equal (cons 1 2) (newfangled-cons 'right-thing 2 'left-thing 1)))
29
30 ;;; ANSI specifically says that duplicate keys are OK in lambda lists,
31 ;;; with no special exception for macro lambda lists. (As reported by
32 ;;; Pierre Mai on cmucl-imp 2001-03-30, Python didn't think so. The
33 ;;; rest of the thread had some entertainment value, at least for me
34 ;;; (WHN). The unbelievers were besmote and now even CMU CL will
35 ;;; conform to the spec in this regard. Who needs diplomacy when you
36 ;;; have brimstone?:-)
37 (defmacro ayup-duplicate-keys-are-ok-i-see-the-lite (&key k)
38   k)
39 (assert (equal (ayup-duplicate-keys-are-ok-i-see-the-lite :k 112) 112))
40 (assert (equal (ayup-duplicate-keys-are-ok-i-see-the-lite :k 'x :k 'y) 'x))
41
42 ;;; As reported by Alexey Dejneka (sbcl-devel 2002-01-30), in
43 ;;; sbcl-0.7.1 plus his patch (i.e. essentially sbcl-0.7.1.2), the
44 ;;; compiler barfed on this, blowing up in FIND-IN-PHYSENV looking for
45 ;;; the LAMBDA-VAR named NUM. That was fixed in sbcl-0.7.1.3.
46 (defun parse-num (index)
47   (let (num x)
48     (flet ((digs ()
49              (setq num index))
50            (z ()
51              (let ()
52                (setq x nil))))
53       (when (and (digs) (digs)) x))))
54
55 ;;; Bug 132: The compiler used to fail to compile INTEGER-valued CATCH
56 ;;; tags. This was fixed by Alexey Dejneka in sbcl-0.7.1.14. (INTEGER
57 ;;; catch tags are still a bad idea because EQ is used to compare
58 ;;; tags, and EQ comparison on INTEGERs is unportable; but now it's a
59 ;;; compiler warning instead of a failure to compile.)
60 (defun foo ()
61   (catch 0 (print 1331)))
62
63 ;;; Bug 150: In sbcl-0.7.1.15, compiling this code caused a failure in
64 ;;; SB-C::ADD-TEST-CONSTRAINTS:
65 ;;;    The value NIL is not of type SB-C::CONTINUATION.
66 ;;; This bug was fixed by APD in sbcl-0.7.1.30.
67 (defun bug150-test1 ()
68   (let* ()
69     (flet ((wufn () (glorp table1 4.9)))
70       (gleep *uustk* #'wufn "#1" (list)))
71     (if (eql (lo foomax 3.2))
72         (values)
73         (error "not ~S" '(eql (lo foomax 3.2))))
74     (values)))
75 ;;; A simpler test case for bug 150: The compiler died with the
76 ;;; same type error when trying to compile this.
77 (defun bug150-test2 ()
78   (let ()
79     (<)))
80
81 ;;; bug 147, fixed by APD 2002-04-28
82 ;;;
83 ;;; This test case used to crash the compiler, e.g. with
84 ;;;   failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)"
85 (defun bug147 (string ind)
86   (flet ((digs ()
87            (let (old-index)
88              (if (and (< ind ind)
89                       (typep (char string ind) '(member #\1)))
90                  nil))))))
91
92 ;;; bug reported and fixed by Matthias Hoelzl sbcl-devel 2002-05-13
93 (defmacro foo-2002-05-13 () ''x)
94 (eval '(foo-2002-05-13))
95 (compile 'foo-2002-05-13)
96 (foo-2002-05-13) ; (The bug caused UNDEFINED-FUNCTION to be signalled here.)
97
98 ;;; floating point pain on the PPC.
99 ;;;
100 ;;; This test case used to fail to compile on most powerpcs prior to
101 ;;; sbcl-0.7.4.2x, as floating point traps were being incorrectly
102 ;;; masked.
103 (defun floating-point-pain (x)
104   (declare (single-float x))
105   (log x))
106
107 ;;; bug found and fixed ca. sbcl-0.7.5.12: The INTERSECTION-TYPE
108 ;;; here satisfies "is a subtype of ARRAY-TYPE", but can't be
109 ;;; accessed with ARRAY-TYPE accessors like
110 ;;; ARRAY-TYPE-SPECIALIZED-ELEMENT-TYPE, so ARRAY-related
111 ;;; DEFTRANSFORMs died with TYPE-ERROR at compile time when
112 ;;; compiling the DEFUN here.
113 (defun stupid-input-to-smart-array-deftransforms-0-7-5-12 (v)
114   (declare (type (and simple-vector fwd-type-ref) v))
115   (aref v 0))
116
117 ;;; Ca. sbcl-0.7.5.15 the compiler would fail an internal consistency
118 ;;; check on this code because it expected all calls to %INSTANCE-REF
119 ;;; to be transformed away, but its expectations were dashed by perverse
120 ;;; code containing app programmer errors like this.
121 (defstruct something-known-to-be-a-struct x y)
122 (multiple-value-bind (fun warnings-p failure-p)
123     (compile nil
124              '(lambda ()
125                 (labels ((a1 (a2 a3)
126                              (cond (t (a4 a2 a3))))
127                          (a4 (a2 a3 a5 a6)
128                              (declare (type (or simple-vector null) a5 a6))
129                              (something-known-to-be-a-struct-x a5))
130                          (a8 (a2 a3)
131                              (a9 #'a1 a10 a2 a3))
132                          (a11 (a2 a3)
133                               (cond ((and (funcall a12 a2)
134                                           (funcall a12 a3))
135                                      (funcall a13 a2 a3))
136                                     (t
137                                      (when a14
138                                      (let ((a15 (a1 a2 a3)))
139                                        ))
140                                      a16))))
141                   (values #'a17 #'a11))))
142   ;; Python sees the structure accessor on the known-not-to-be-a-struct
143   ;; A5 value and is very, very disappointed in you. (But it doesn't
144   ;; signal BUG any more.)
145   (assert failure-p))
146
147 ;;; On the SPARC, there was an erroneous definition of some VOPs used
148 ;;; to compile LOGANDs, which would lead to compilation of the
149 ;;; following function giving rise to a compile-time error (bug
150 ;;; spotted and fixed by Raymond Toy for CMUCL)
151 (defun logand-sparc-bogons (a0 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
152   (declare (type (unsigned-byte 32) a0)
153            (type (signed-byte 32) a1 a2 a3 a4 a5 a6 a7 a8 a9 a10)
154            ;; to ensure that the call is a candidate for
155            ;; transformation
156            (optimize (speed 3) (safety 0) (compilation-speed 0) (debug 0)))
157   (values
158    ;; the call that fails compilation
159    (logand a0 a10)
160    ;; a call to prevent the other arguments from being optimized away
161    (logand a1 a2 a3 a4 a5 a6 a7 a8 a9)))
162
163 ;;; bug 192, reported by Einar Floystad Dorum sbcl-devel 2002-08-14,
164 ;;; fixed in sbcl-0.7.6.26: Compiling this function in 0.7.6 caused
165 ;;; the compiler to try to constant-fold DATA-VECTOR-REF, which is OK,
166 ;;; except that there was no non-VOP definition of DATA-VECTOR-REF, so
167 ;;; it would fail.
168 (defun bug192 ()
169       (funcall 
170        (LAMBDA (TEXT I L )
171          (LABELS ((G908 (I)
172                     (LET ((INDEX
173                            (OR
174                             (IF (= I L)
175                                 NIL
176                                 (LET ((S TEXT)
177                                       (E (ELT TEXT I)))
178                                   (DECLARE (IGNORABLE S E))
179                                   (WHEN (EQL #\a E)
180                                     (G909 (1+ I))))))))
181                       INDEX))
182                   (G909 (I)
183                     (OR
184                      (IF (= I L)
185                          NIL
186                          (LET ((S TEXT)
187                                (E (ELT TEXT I)))
188                            (DECLARE (IGNORABLE S E))
189                            (WHEN (EQL #\b E) (G910 (1+ I)))))))
190                   (G910 (I)
191                     (LET ((INDEX
192                            (OR
193                             (IF NIL
194                                 NIL
195                                 (LET ((S TEXT))
196                                   (DECLARE (IGNORABLE S))
197                                   (WHEN T I))))))
198                       INDEX)))
199            (G908 I))) "abcdefg" 0 (length "abcdefg")))
200
201 ;;; bugs #65, #70, and #109, closed by APD's patch sbcl-devel 2002-08-17
202 ;;;
203 ;;; This was "YA code deletion bug" whose symptom was the failure of
204 ;;; the assertion
205 ;;;   (EQ (C::LAMBDA-TAIL-SET C::CALLER)
206 ;;;       (C::LAMBDA-TAIL-SET (C::LAMBDA-HOME C::CALLEE)))
207 ;;; at compile time.
208 (defun bug65-1 (termx termy) ; from Carl Witty on submit bugs list, debian.org
209   (labels
210     ((alpha-equal-bound-term-lists (listx listy)
211        (or (and (null listx) (null listy))
212            (and listx listy
213                 (let ((bindings-x (bindings-of-bound-term (car listx)))
214                       (bindings-y (bindings-of-bound-term (car listy))))
215                   (if (and (null bindings-x) (null bindings-y))
216                       (alpha-equal-terms (term-of-bound-term (car listx))
217                                          (term-of-bound-term (car listy)))
218                       (and (= (length bindings-x) (length bindings-y))
219                            (prog2
220                                (enter-binding-pairs (bindings-of-bound-term (car listx))
221                                                     (bindings-of-bound-term (car listy)))
222                                (alpha-equal-terms (term-of-bound-term (car listx))
223                                                   (term-of-bound-term (car listy)))
224                              (exit-binding-pairs (bindings-of-bound-term (car listx))
225                                                  (bindings-of-bound-term (car listy)))))))
226                 (alpha-equal-bound-term-lists (cdr listx) (cdr listy)))))
227
228      (alpha-equal-terms (termx termy)
229        (if (and (variable-p termx)
230                 (variable-p termy))
231            (equal-bindings (id-of-variable-term termx)
232                            (id-of-variable-term termy))
233            (and (equal-operators-p (operator-of-term termx) (operator-of-term termy))
234                 (alpha-equal-bound-term-lists (bound-terms-of-term termx)
235                                               (bound-terms-of-term termy))))))
236
237     (or (eq termx termy)
238         (and termx termy
239              (with-variable-invocation (alpha-equal-terms termx termy))))))
240 (defun bug65-2 () ; from Bob Rogers cmucl-imp 1999-07-28
241   ;; Given an FSSP alignment file named by the argument . . .
242   (labels ((get-fssp-char ()
243              (get-fssp-char))
244            (read-fssp-char ()
245              (get-fssp-char)))
246     ;; Stub body, enough to tickle the bug.
247     (list (read-fssp-char)
248           (read-fssp-char))))
249 (defun bug70 ; from David Young cmucl-help 30 Nov 2000
250     (item sequence &key (test #'eql))
251   (labels ((find-item (obj seq test &optional (val nil))
252                       (let ((item (first seq)))
253                         (cond ((null seq)
254                                (values nil nil))
255                               ((funcall test obj item)
256                                (values val seq))
257                               (t        
258                                (find-item obj
259                                           (rest seq)
260                                           test
261                                           (nconc val `(,item))))))))
262     (find-item item sequence test)))
263 (defun bug109 () ; originally from CMU CL bugs collection, reported as
264                  ; SBCL bug by MNA 2001-06-25
265   (labels 
266       ((eff (&key trouble)
267             (eff)
268             ;; nil
269             ;; Uncomment and it works
270             ))
271     (eff)))
272
273 ;;; bug 192a, fixed by APD "more strict type checking" patch
274 ;;; (sbcl-devel 2002-08-07)
275 (defun bug192a (x)
276   (declare (optimize (speed 0) (safety 3)))
277   ;; Even with bug 192a, this declaration was checked as an assertion.
278   (declare (real x))
279   (+ x
280      (locally
281        ;; Because of bug 192a, this declaration was trusted without checking.
282        (declare (single-float x))
283        (sin x))))
284 (assert (null (ignore-errors (bug192a nil))))
285 (multiple-value-bind (result error) (ignore-errors (bug192a 100))
286   (assert (null result))
287   (assert (equal (type-error-expected-type error) 'single-float)))
288
289 ;;; bug 194, fixed in part by APD "more strict type checking" patch
290 ;;; (sbcl-devel 2002-08-07)
291 (progn
292   #+nil ; FIXME: still broken in 0.7.7.19 (after patch)
293   (multiple-value-bind (result error)
294       (ignore-errors (multiple-value-prog1 (progn (the real '(1 2 3)))))
295     (assert (null result))
296     (assert (typep error 'type-error)))
297   #+nil ; FIXME: still broken in 0.7.7.19 (after patch)
298   (multiple-value-bind (result error)
299       (ignore-errors (the real '(1 2 3)))
300     (assert (null result))
301     (assert (typep error 'type-error))))
302 \f
303 ;;; BUG 48a. and b. (symbol-macrolet handling), fixed by Eric Marsden
304 ;;; and Raymond Toy for CMUCL, fix ported for sbcl-0.7.6.18.
305 (multiple-value-bind (function warnings-p failure-p)
306     (compile nil '(lambda () (symbol-macrolet ((t nil)) t)))
307   (assert failure-p)
308   (assert (raises-error? (funcall function) program-error)))
309 (multiple-value-bind (function warnings-p failure-p)
310     (compile nil
311              '(lambda ()
312                 (symbol-macrolet ((*standard-input* nil))
313                   *standard-input*)))
314   (assert failure-p)
315   (assert (raises-error? (funcall function) program-error)))
316 #||
317 BUG 48c, not yet fixed:
318 (multiple-value-bind (function warnings-p failure-p)
319     (compile nil '(lambda () (symbol-macrolet ((s nil)) (declare (special s)) s)))
320   (assert failure-p)
321   (assert (raises-error? (funcall function) program-error)))
322 ||#
323 \f
324 ;;; bug 120a: Turned out to be constraining code looking like (if foo
325 ;;; <X> <X>) where <X> was optimized by the compiler to be the exact
326 ;;; same block in both cases, but not turned into (PROGN FOO <X>).
327 ;;; Fixed by APD in sbcl-0.7.7.2, who provided this test:
328 (declaim (inline dont-constrain-if-too-much))
329 (defun dont-constrain-if-too-much (frame up-frame)
330   (declare (optimize (speed 3) (safety 1) (debug 1)))
331   (if (or (not frame) t)
332       frame
333       "bar"))
334 (defun dont-constrain-if-too-much-aux (x y)
335   (declare (optimize (speed 3) (safety 1) (debug 1)))
336   (if x t (if y t (dont-constrain-if-too-much x y))))
337
338 (assert (null (dont-constrain-if-too-much-aux nil nil)))  
339
340 ;;; TYPE-ERROR confusion ca. sbcl-0.7.7.24, reported and fixed by
341 ;;; APD sbcl-devel 2002-09-14
342 (defun exercise-0-7-7-24-bug (x)
343   (declare (integer x))
344   (let (y)
345     (setf y (the single-float (if (> x 0) x 3f0)))
346     (list y y)))
347 (multiple-value-bind (v e) (ignore-errors (exercise-0-7-7-24-bug 4))
348   (assert (null v))
349   (assert (typep e 'type-error)))
350 (assert (equal (exercise-0-7-7-24-bug -4) '(3f0 3f0)))
351
352 ;;; non-intersecting type declarations were DWIMing in a confusing
353 ;;; fashion until sbcl-0.7.7.28, when APD reported and fixed the
354 ;;; problem.
355 (defun non-intersecting-the (x)
356   (let (y)
357     (setf y (the single-float (the integer x)))
358     (list y y)))
359
360 (raises-error? (foo 3) type-error)
361 (raises-error? (foo 3f0) type-error)
362
363 ;;; until 0.8.2 SBCL did not check THEs in arguments
364 (defun the-in-arguments-aux (x)
365   x)
366 (defun the-in-arguments-1 (x)
367   (list x (the-in-arguments-aux (the (single-float 0s0) x))))
368 (defun the-in-arguments-2 (x)
369   (list x (the-in-arguments-aux (the single-float x))))
370
371 (multiple-value-bind (result condition)
372     (ignore-errors (the-in-arguments-1 1))
373   (assert (null result))
374   (assert (typep condition 'type-error)))
375 (multiple-value-bind (result condition)
376     (ignore-errors (the-in-arguments-2 1))
377   (assert (null result))
378   (assert (typep condition 'type-error)))
379
380 ;;; bug 153: a hole in a structure slot type checking
381 (declaim (optimize safety))
382 (defstruct foo153
383   (bla 0 :type fixnum))
384 (defun bug153-1 ()
385   (let ((foo (make-foo153)))
386     (setf (foo153-bla foo) '(1 . 1))
387     (format t "Is ~a of type ~a a cons? => ~a~%"
388             (foo153-bla foo)
389             (type-of (foo153-bla foo))
390             (consp (foo153-bla foo)))))
391 (defun bug153-2 (x)
392   (let ((foo (make-foo153)))
393     (setf (foo153-bla foo) x)
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
399 (multiple-value-bind (result condition)
400     (ignore-errors (bug153-1))
401   (declare (ignore result))
402   (assert (typep condition 'type-error)))
403 (multiple-value-bind (result condition)
404     (ignore-errors (bug153-2 '(1 . 1)))
405   (declare (ignore result))
406   (assert (typep condition 'type-error)))
407
408 ;;; bug 110: the compiler flushed the argument type test and the default
409 ;;; case in the cond.
410
411 (defun bug110 (x)
412   (declare (optimize (safety 2) (speed 3)))
413   (declare (type (or string stream) x))
414   (cond ((typep x 'string) 'string)
415         ((typep x 'stream) 'stream)
416         (t
417          'none)))
418
419 (multiple-value-bind (result condition)
420     (ignore-errors (bug110 0))
421   (declare (ignore result))
422   (assert (typep condition 'type-error)))
423
424 ;;; bug 202: the compiler failed to compile a function, which derived
425 ;;; type contradicted declared.
426 (declaim (ftype (function () null) bug202))
427 (defun bug202 ()
428   t)
429
430 ;;; bugs 178, 199: compiler failed to compile a call of a function
431 ;;; with a hairy type
432 (defun bug178 (x)
433       (funcall (the function (the standard-object x))))
434
435 (defun bug199-aux (f)
436   (eq nil (funcall f)))
437
438 (defun bug199 (f x)
439   (declare (type (and function (satisfies bug199-aux)) f))
440   (funcall f x))
441
442 ;;; check non-toplevel DEFMACRO
443 (defvar *defmacro-test-status* nil)
444
445 (defun defmacro-test ()
446   (fmakunbound 'defmacro-test-aux)
447   (let* ((src "defmacro-test.lisp")
448          (obj (compile-file-pathname src)))
449     (unwind-protect
450          (progn
451            (compile-file src)
452            (assert (equal *defmacro-test-status* '(function a)))
453            (setq *defmacro-test-status* nil)
454            (load obj)
455            (assert (equal *defmacro-test-status* nil))
456            (macroexpand '(defmacro-test-aux 'a))
457            (assert (equal *defmacro-test-status* '(macro 'a z-value)))
458            (eval '(defmacro-test-aux 'a))
459            (assert (equal *defmacro-test-status* '(expanded 'a z-value))))
460       (ignore-errors (delete-file obj)))))
461
462 (defmacro-test)
463
464 ;;; bug 204: EVAL-WHEN inside a local environment
465 (defvar *bug204-test-status*)
466
467 (defun bug204-test ()
468   (let* ((src "bug204-test.lisp")
469          (obj (compile-file-pathname src)))
470     (unwind-protect
471          (progn
472            (setq *bug204-test-status* nil)
473            (compile-file src)
474            (assert (equal *bug204-test-status* '((:expanded :load-toplevel)
475                                                  (:called :compile-toplevel)
476                                                  (:expanded :compile-toplevel))))
477            (setq *bug204-test-status* nil)
478            (load obj)
479            (assert (equal *bug204-test-status* '((:called :load-toplevel)))))
480       (ignore-errors (delete-file obj)))))
481
482 (bug204-test)
483
484 ;;; toplevel SYMBOL-MACROLET
485 (defvar *symbol-macrolet-test-status*)
486
487 (defun symbol-macrolet-test ()
488   (let* ((src "symbol-macrolet-test.lisp")
489          (obj (compile-file-pathname src)))
490     (unwind-protect
491          (progn
492            (setq *symbol-macrolet-test-status* nil)
493            (compile-file src)
494            (assert (equal *symbol-macrolet-test-status*
495                           '(2 1)))
496            (setq *symbol-macrolet-test-status* nil)
497            (load obj)
498            (assert (equal *symbol-macrolet-test-status* '(2))))
499       (ignore-errors (delete-file obj)))))
500
501 (symbol-macrolet-test)
502
503 ;;; On the x86, this code failed to compile until sbcl-0.7.8.37:
504 (defun x86-assembler-failure (x)
505   (declare (optimize (speed 3) (safety 0)))
506   (eq (setf (car x) 'a) nil))
507
508 ;;; bug 211: :ALLOW-OTHER-KEYS
509 (defun bug211d (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
510   (list x x-p y y-p))
511
512 (assert (equal (bug211d) '(:x nil :y nil)))
513 (assert (equal (bug211d :x 1) '(1 t :y nil)))
514 (assert (raises-error? (bug211d :y 2) program-error))
515 (assert (equal (bug211d :y 2 :allow-other-keys t :allow-other-keys nil)
516                '(:x nil t t)))
517 (assert (raises-error? (bug211d :y 2 :allow-other-keys nil) program-error))
518
519 (let ((failure-p
520        (nth-value
521         3
522         (compile 'bug211b
523                  '(lambda ()
524                    (flet ((test (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
525                             (list x x-p y y-p)))
526                      (assert (equal (test) '(:x nil :y nil)))
527                      (assert (equal (test :x 1) '(1 t :y nil)))
528                      (assert (equal (test :y 2 :allow-other-keys 11 :allow-other-keys nil)
529                                     '(:x nil 11 t)))))))))
530   (assert (not failure-p))
531   (bug211b))
532
533 (let ((failure-p
534        (nth-value
535         3
536         (compile 'bug211c
537                  '(lambda ()
538                    (flet ((test (&key (x :x x-p))
539                             (list x x-p)))
540                      (assert (equal (test) '(:x nil)))
541                      (assert (equal (test :x 1) '(1 t)))
542                      (assert (equal (test :y 2 :allow-other-keys 11 :allow-other-keys nil)
543                                     '(:x nil)))))))))
544   (assert (not failure-p))
545   (bug211c))
546
547 (dolist (form '((test :y 2)
548                 (test :y 2 :allow-other-keys nil)
549                 (test :y 2 :allow-other-keys nil :allow-other-keys t)))
550   (multiple-value-bind (result warnings-p failure-p)
551       (compile nil `(lambda ()
552                      (flet ((test (&key (x :x x-p) ((:allow-other-keys y) :y y-p))
553                               (list x x-p y y-p)))
554                        ,form)))
555     (assert failure-p)
556     (assert (raises-error? (funcall result) program-error))))
557
558 ;;; bug 217: wrong type inference
559 (defun bug217-1 (x s)
560   (let ((f (etypecase x
561              (character #'write-char)
562              (integer #'write-byte))))
563     (funcall f x s)
564     (etypecase x
565       (character (write-char x s))
566       (integer (write-byte x s)))))
567 (bug217-1 #\1 *standard-output*)
568
569
570 ;;; bug 221: tried and died on CSUBTYPEP (not VALUES-SUBTYPEP) of the
571 ;;; function return types when inferring the type of the IF expression
572 (declaim (ftype (function (fixnum) (values package boolean)) bug221f1))
573 (declaim (ftype (function (t) (values package boolean)) bug221f2))
574 (defun bug221 (b x)
575   (funcall (if b #'bug221f1 #'bug221f2) x))
576 \f
577 ;;; bug 172: macro lambda lists were too permissive until 0.7.9.28
578 ;;; (fix provided by Matthew Danish) on sbcl-devel
579 (assert (null (ignore-errors
580                 (defmacro bug172 (&rest rest foo) `(list ,rest ,foo)))))
581
582 ;;; embedded THEs
583 (defun check-embedded-thes (policy1 policy2 x y)
584   (handler-case
585       (funcall (compile nil
586                         `(lambda (f)
587                            (declare (optimize (speed 2) (safety ,policy1)))
588                            (multiple-value-list
589                             (the (values (integer 2 3) t)
590                               (locally (declare (optimize (safety ,policy2)))
591                                 (the (values t (single-float 2f0 3f0))
592                                   (funcall f)))))))
593                (lambda () (values x y)))
594     (type-error (error)
595       error)))
596
597 (assert (equal (check-embedded-thes 0 0  :a :b) '(:a :b)))
598
599 (assert (equal (check-embedded-thes 0 3  :a 2.5f0) '(:a 2.5f0)))
600 (assert (typep (check-embedded-thes 0 3  2 3.5f0) 'type-error))
601
602 (assert (equal (check-embedded-thes 0 1  :a 3.5f0) '(:a 3.5f0)))
603 (assert (typep (check-embedded-thes 0 1  2 2.5d0) 'type-error))
604
605 #+nil
606 (assert (equal (check-embedded-thes 3 0  2 :a) '(2 :a)))
607 (assert (typep (check-embedded-thes 3 0  4 2.5f0) 'type-error))
608
609 (assert (equal (check-embedded-thes 1 0  4 :b) '(4 :b)))
610 (assert (typep (check-embedded-thes 1 0  1.0 2.5f0) 'type-error))
611
612
613 (assert (equal (check-embedded-thes 3 3  2 2.5f0) '(2 2.5f0)))
614 (assert (typep (check-embedded-thes 3 3  0 2.5f0) 'type-error))
615 (assert (typep (check-embedded-thes 3 3  2 3.5f0) 'type-error))
616
617 \f
618 ;;; INLINE inside MACROLET
619 (declaim (inline to-be-inlined))
620 (macrolet ((def (x) `(defun ,x (y) (+ y 1))))
621   (def to-be-inlined))
622 (defun call-inlined (z)
623   (to-be-inlined z))
624 (assert (= (call-inlined 3) 4))
625 (macrolet ((frob (x) `(+ ,x 3)))
626   (defun to-be-inlined (y)
627     (frob y)))
628 (assert (= (call-inlined 3)
629            ;; we should have inlined the previous definition, so the
630            ;; new one won't show up yet.
631            4))
632 (defun call-inlined (z)
633   (to-be-inlined z))
634 (assert (= (call-inlined 3) 6))
635 (defun to-be-inlined (y)
636   (+ y 5))
637 (assert (= (call-inlined 3) 6))
638 \f
639 ;;;; tests not in the problem domain, but of the consistency of the
640 ;;;; compiler machinery itself
641
642 (in-package "SB-C")
643
644 ;;; Hunt for wrong-looking things in fundamental compiler definitions,
645 ;;; and gripe about them.
646 ;;;
647 ;;; FIXME: It should be possible to (1) repair the things that this
648 ;;; code gripes about, and then (2) make the code signal errors
649 ;;; instead of just printing complaints to standard output, in order
650 ;;; to prevent the code from later falling back into disrepair.
651 (defun grovel-results (function)
652   (dolist (template (fun-info-templates (info :function :info function)))
653     (when (template-more-results-type template)
654       (format t "~&Template ~A has :MORE results, and translates ~A.~%"
655               (template-name template)
656               function)
657       (return nil))
658     (when (eq (template-result-types template) :conditional)
659       ;; dunno.
660       (return t))
661     (let ((types (template-result-types template))
662           (result-type (fun-type-returns (info :function :type function))))
663       (cond
664         ((values-type-p result-type)
665          (do ((ltypes (append (args-type-required result-type)
666                               (args-type-optional result-type))
667                       (rest ltypes))
668               (types types (rest types)))
669              ((null ltypes)
670               (unless (null types)
671                 (format t "~&More types than ltypes in ~A, translating ~A.~%"
672                         (template-name template)
673                         function)
674                 (return nil)))
675            (when (null types)
676              (unless (null ltypes)
677                (format t "~&More ltypes than types in ~A, translating ~A.~%"
678                        (template-name template)
679                        function)
680                (return nil)))))
681         ((eq result-type (specifier-type nil))
682          (unless (null types)
683            (format t "~&Template ~A returns values for function ~A with RESULT-TYPE NIL.~%"
684                    (template-name template)
685                    function)
686            (return nil)))
687         ((/= (length types) 1)
688          (format t "~&Template ~A isn't returning 1 value for ~A.~%"
689                  (template-name template)
690                  function)
691          (return nil))
692         (t t)))))
693 (defun identify-suspect-vops (&optional (env (first
694                                               (last *info-environment*))))
695   (do-info (env :class class :type type :name name :value value)
696     (when (and (eq class :function) (eq type :type))
697       ;; OK, so we have an entry in the INFO database. Now, if ...
698       (let* ((info (info :function :info name))
699              (templates (and info (fun-info-templates info))))
700         (when templates
701           ;; ... it has translators
702           (grovel-results name))))))
703 (identify-suspect-vops)
704 \f
705 ;;; success
706 (quit :unix-status 104)