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