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