3 # This software is part of the SBCL system. See the README file for
6 # While most of SBCL is derived from the CMU CL system, the test
7 # files (like this one) were written from scratch after the fork
10 # This software is in the public domain and is provided with
11 # absolutely no warranty. See the COPYING and CREDITS files for
16 base_tmpfilename
="compiler-test-$$-tmp"
17 tmpfilename
="$base_tmpfilename.lisp"
18 compiled_tmpfilename
="$base_tmpfilename.fasl"
20 # This should fail, as type inference should show that the call to FOO
21 # will return something of the wrong type.
22 cat > $tmpfilename <<EOF
24 (defun foo (x) (list x))
25 (defun bar (x) (1+ (foo x)))
27 expect_failed_compile
$tmpfilename
29 # This should fail, as we define a function multiply in the same file
31 cat > $tmpfilename <<EOF
33 (defun foo (x) (list x))
34 (defun foo (x) (cons x x))
36 expect_failed_compile
$tmpfilename
38 # This shouldn't fail, as the inner FLETs should not be treated as
39 # having the same name.
40 cat > $tmpfilename <<EOF
43 (flet ((baz (y) (load y)))
44 (declare (notinline baz))
47 (flet ((baz (y) (load y)))
48 (declare (notinline baz))
51 expect_clean_compile
$tmpfilename
53 # This shouldn't fail because it's not really a multiple definition
54 cat > $tmpfilename <<EOF
56 (eval-when (:compile-toplevel :load-toplevel :execute)
59 expect_clean_compile
$tmpfilename
62 cat > $tmpfilename <<EOF
64 (eval-when (:compile-toplevel)
68 expect_clean_compile
$tmpfilename
70 # This shouldn't fail despite the apparent type mismatch, because of
71 # the NOTINLINE declamation.
72 cat > $tmpfilename <<EOF
74 (defun foo (x) (list x))
75 (declaim (notinline foo))
76 (defun bar (x) (1+ (foo x)))
78 expect_clean_compile
$tmpfilename
80 # This shouldn't fail, but did until sbcl-0.8.10.4x
81 cat > $tmpfilename <<EOF
83 (declaim (inline foo))
87 (list (foo y) (if (> y 1) (funcall (if (> y 0) #'foo #'identity) y))))
89 expect_clean_compile
$tmpfilename
91 # This shouldn't fail despite the apparent type mismatch, because of
92 # the NOTINLINE declaration.
93 cat > $tmpfilename <<EOF
95 (defun foo (x) (list x))
97 (declare (notinline foo))
100 expect_clean_compile
$tmpfilename
102 # This in an ideal world would fail (that is, return with FAILURE-P
103 # set), but at present it doesn't.
104 cat > $tmpfilename <<EOF
105 (in-package :cl-user)
106 (defun foo (x) (list x))
108 (declare (notinline foo))
110 (declare (inline foo))
113 # expect_failed_compile $tmpfilename
115 # This used to not warn, because the VALUES derive-type optimizer was
116 # insufficiently precise.
117 cat > $tmpfilename <<EOF
118 (in-package :cl-user)
119 (defun foo (x) (declare (ignore x)) (values))
120 (defun bar (x) (1+ (foo x)))
122 expect_failed_compile
$tmpfilename
124 # Even after making the VALUES derive-type optimizer more precise, the
125 # following should still be clean.
126 cat > $tmpfilename <<EOF
127 (in-package :cl-user)
128 (defun foo (x) (declare (ignore x)) (values))
129 (defun bar (x) (car x))
131 expect_clean_compile
$tmpfilename
133 # NOTINLINE on known functions shouldn't inhibit type inference
134 # (spotted by APD sbcl-devel 2003-06-14)
135 cat > $tmpfilename <<EOF
136 (in-package :cl-user)
138 (declare (notinline list))
141 expect_failed_compile
$tmpfilename
143 # ERROR wants to check its format string for sanity...
144 cat > $tmpfilename <<EOF
145 (in-package :cl-user)
150 expect_failed_compile
$tmpfilename
152 # ... but it (ERROR) shouldn't complain about being unable to optimize
153 # when it's uncertain about its argument's type
154 cat > $tmpfilename <<EOF
155 (in-package :cl-user)
159 fail_on_compiler_note
$tmpfilename
161 # test case from Rudi for some CLOS WARNINGness that shouldn't have
163 cat > $tmpfilename <<EOF
164 #+sb-eval (eval-when (:compile-toplevel)
165 (setf sb-ext:*evaluator-mode* :compile))
167 (eval-when (:compile-toplevel :load-toplevel :execute)
168 (defstruct buffer-state
171 (defclass buffered-stream-mixin ()
172 ((buffer-state :initform (make-buffer-state))))
174 (defgeneric frob (stream))
175 (defmethod frob ((stream t))
177 (defmethod frob ((stream buffered-stream-mixin))
179 ((index (buffer-state-output-index (slot-value stream 'buffer-state))))
183 expect_clean_compile
$tmpfilename
185 # undeclared unbound variables should cause a full warning, as they
186 # invoke undefined behaviour
187 cat > $tmpfilename <<EOF
190 expect_failed_compile
$tmpfilename
192 cat > $tmpfilename <<EOF
193 (declaim (special *x*))
196 expect_clean_compile
$tmpfilename
198 cat > $tmpfilename <<EOF
199 (defun foo () (declare (special x)) x)
201 expect_clean_compile
$tmpfilename
203 # MUFFLE-CONDITIONS tests
204 cat > $tmpfilename <<EOF
206 (declare (muffle-conditions style-warning))
209 expect_clean_compile
$tmpfilename
211 cat > $tmpfilename <<EOF
213 (declare (muffle-conditions code-deletion-note))
216 fail_on_compiler_note
$tmpfilename
218 cat > $tmpfilename <<EOF
220 (declare (muffle-conditions compiler-note))
221 (declare (optimize speed))
224 fail_on_compiler_note
$tmpfilename
226 cat > $tmpfilename <<EOF
227 (declaim (muffle-conditions compiler-note))
229 (declare (optimize speed))
232 fail_on_compiler_note
$tmpfilename
234 cat > $tmpfilename <<EOF
235 (declaim (muffle-conditions compiler-note))
237 (declare (unmuffle-conditions compiler-note))
238 (declare (optimize speed))
241 expect_compiler_note
$tmpfilename
243 # undefined variable causes a WARNING
244 cat > $tmpfilename <<EOF
245 (declaim (muffle-conditions warning))
246 (declaim (unmuffle-conditions style-warning))
249 expect_clean_compile
$tmpfilename
251 # top level LOCALLY behaves nicely
252 cat > $tmpfilename <<EOF
254 (declare (muffle-conditions warning))
257 expect_clean_compile
$tmpfilename
259 cat > $tmpfilename <<EOF
261 (declare (muffle-conditions warning))
265 expect_failed_compile
$tmpfilename
267 # This should fail, and fail nicely -- not eg. loop trying to dump
268 # references to the unbound variable.
269 cat > $tmpfilename <<EOF
270 (defmacro macro-with-unbound-variables (foo)
273 (macro-with-unbound-variables 'xxx)
275 expect_failed_compile
$tmpfilename
277 # This should fail, as the MAKE-LOAD-FORM must be used for
278 # externalizing conditions, and the method for CONDITION must signal
280 cat > $tmpfilename <<EOF
281 (defvar *oops* #.(make-condition 'condition))
283 expect_failed_compile
$tmpfilename
285 # This should fail, as the MAKE-LOAD-FORM must be used for objects,
286 # and the method for STANDARD.OBJECT is required to signal an error.
287 cat > $tmpfilename <<EOF
288 (defvar *oops* #.(make-instance 'standard-object))
290 expect_failed_compile
$tmpfilename
292 # This should be clean
293 cat > $tmpfilename <<EOF
294 (defvar *string* (make-string 10 :element-type 'base-char))
296 expect_clean_compile
$tmpfilename
298 # This should style-warn (but not warn or otherwise fail) as the call
299 # to FORMAT has too many arguments, which is bad style but not
301 cat > $tmpfilename <<EOF
303 (format nil "abc~~def" a b))
305 expect_warned_compile
$tmpfilename
307 # Tests that destructive-functions on known-constant data cause
308 # compile-time warnings.
309 cat > $tmpfilename <<EOF
310 (let ((string "foo"))
312 (setf string "bar")))
314 expect_clean_compile
$tmpfilename
316 cat > $tmpfilename <<EOF
321 expect_clean_compile
$tmpfilename
323 cat > $tmpfilename <<EOF
328 expect_clean_compile
$tmpfilename
330 cat > $tmpfilename <<EOF
331 (let ((string "foo"))
333 (replace string "bar")))
335 expect_failed_compile
$tmpfilename
337 cat > $tmpfilename <<EOF
339 (setf (char "bar" 0) #\1))
341 expect_failed_compile
$tmpfilename
343 cat > $tmpfilename <<EOF
344 (let ((foo '(1 2 3)))
348 expect_failed_compile
$tmpfilename
350 cat > $tmpfilename <<EOF
351 (declaim (optimize (speed 3) (space 0) (safety 0)))
356 expect_clean_compile
$tmpfilename
358 cat > $tmpfilename <<EOF
362 expect_clean_compile
$tmpfilename
364 cat > $tmpfilename <<EOF
365 (eval-when (:compile-toplevel :load-toplevel :execute)
367 (defmethod make-load-form ((foo foox) &optional env)
368 (declare (ignore env))
373 expect_clean_compile
$tmpfilename
375 cat > $tmpfilename <<EOF
376 (defun something (x) x)
378 (defun something-more (x) x)
380 expect_aborted_compile
$tmpfilename