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