d710d17d04a35cc96eb80ddc33dd72c1921ec76a
[sbcl.git] / contrib / sb-cltl2 / tests.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; The software is in the public domain and is provided with
5 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
6 ;;;; more information.
7
8 (defpackage :sb-cltl2-tests
9   (:use :sb-cltl2 :cl :sb-rt :sb-ext :sb-kernel :sb-int))
10
11 (in-package :sb-cltl2-tests)
12
13 (rem-all-tests)
14
15 (defmacro *x*-value ()
16   (declare (special *x*))
17   *x*)
18
19 (deftest compiler-let.1
20     (let ((*x* :outer))
21       (compiler-let ((*x* :inner))
22         (list *x* (*x*-value))))
23   (:outer :inner))
24
25 (defvar *expansions* nil)
26 (defmacro macroexpand-macro (arg)
27   (push arg *expansions*)
28   arg)
29
30 (deftest macroexpand-all.1
31     (progn
32       (macroexpand-all '(defmethod foo ((x fixnum)) (1+ x)))
33       t)
34   t)
35
36 (deftest macroexpand-all.2
37     (let ((*expansions* nil))
38       (macroexpand-all '(list (macroexpand-macro 1)
39                          (let (macroexpand-macro :no)
40                            (macroexpand-macro 2))))
41       (remove-duplicates (sort *expansions* #'<)))
42   (1 2))
43
44 (deftest macroexpand-all.3
45     (let ((*expansions* nil))
46       (compile nil '(lambda ()
47                      (macrolet ((foo (key &environment env)
48                                   (macroexpand-all `(bar ,key) env)))
49                        (foo
50                         (macrolet ((bar (key)
51                                      (push key *expansions*)
52                                      key))
53                           (foo 1))))))
54       (remove-duplicates *expansions*))
55   (1))
56
57 (defun smv (env)
58   (multiple-value-bind (expansion macro-p)
59       (macroexpand 'srlt env)
60     (when macro-p (eval expansion))))
61 (defmacro testr (&environment env)
62   `',(getf (smv env) nil))
63
64 (deftest macroexpand-all.4
65     (macroexpand-all '(symbol-macrolet ((srlt '(nil zool))) (testr)))
66   (symbol-macrolet ((srlt '(nil zool))) 'zool))
67
68 (defmacro dinfo (thing &environment env)
69   `',(declaration-information thing env))
70
71 (macrolet ((def (x)
72                `(macrolet ((frob (suffix answer &optional declaration)
73                             `(deftest ,(intern (concatenate 'string
74                                                             "DECLARATION-INFORMATION."
75                                                             (symbol-name ',x)
76                                                             suffix))
77                                (locally (declare ,@(when declaration
78                                                          (list declaration)))
79                                  (cadr (assoc ',',x (dinfo optimize))))
80                               ,answer)))
81                  (frob ".DEFAULT" 1)
82                  (frob ".0" 0 (optimize (,x 0)))
83                  (frob ".1" 1 (optimize (,x 1)))
84                  (frob ".2" 2 (optimize (,x 2)))
85                  (frob ".3" 3 (optimize (,x 3)))
86                  (frob ".IMPLICIT" 3 (optimize ,x)))))
87   (def speed)
88   (def safety)
89   (def debug)
90   (def compilation-speed)
91   (def space))
92
93 (deftest declaration-information.muffle-conditions.default
94   (dinfo sb-ext:muffle-conditions)
95   nil)
96 (deftest declaration-information.muffle-conditions.1
97   (locally (declare (sb-ext:muffle-conditions warning))
98     (dinfo sb-ext:muffle-conditions))
99   warning)
100 (deftest declaration-information.muffle-conditions.2
101   (let ((junk (dinfo sb-ext:muffle-conditions)))
102     (declare (sb-ext:muffle-conditions warning))
103     (locally (declare (sb-ext:unmuffle-conditions style-warning))
104       (let ((dinfo (dinfo sb-ext:muffle-conditions)))
105         (not
106          (not
107           (and (subtypep dinfo `(or (and warning (not style-warning))
108                                     (and ,junk (not style-warning))))
109                (subtypep '(and warning (not style-warning)) dinfo)))))))
110   t)
111
112
113 (declaim (declaration fubar))
114
115 (deftest declaration-information.declaration
116     (if (member 'fubar (declaration-information 'declaration)) 'yay)
117   yay)
118
119 ;;;; VARIABLE-INFORMATION
120
121 (defvar *foo*)
122
123 (defmacro var-info (var &environment env)
124   (list 'quote (multiple-value-list (variable-information var env))))
125
126 (deftest variable-info.global-special/unbound
127     (var-info *foo*)
128   (:special nil nil))
129
130 (deftest variable-info.global-special/unbound/extra-decl
131     (locally (declare (special *foo*))
132       (var-info *foo*))
133   (:special nil nil))
134
135 (deftest variable-info.global-special/bound
136     (let ((*foo* t))
137       (var-info *foo*))
138   (:special nil nil))
139
140 (deftest variable-info.global-special/bound/extra-decl
141     (let ((*foo* t))
142       (declare (special *foo*))
143       (var-info *foo*))
144   (:special nil nil))
145
146 (deftest variable-info.local-special/unbound
147     (locally (declare (special x))
148       (var-info x))
149   (:special nil nil))
150
151 (deftest variable-info.local-special/bound
152     (let ((x 13))
153       (declare (special x))
154       (var-info x))
155   (:special nil nil))
156
157 (deftest variable-info.local-special/shadowed
158     (let ((x 3))
159       (declare (special x))
160       x
161       (let ((x 3))
162         x
163         (var-info x)))
164   (:lexical t nil))
165
166 (deftest variable-info.local-special/shadows-lexical
167     (let ((x 3))
168       (let ((x 3))
169         (declare (special x))
170         (var-info x)))
171   (:special nil nil))
172
173 (deftest variable-info.lexical
174     (let ((x 8))
175       (var-info x))
176   (:lexical t nil))
177
178 (deftest variable-info.lexical.type
179     (let ((x 42))
180       (declare (fixnum x))
181       (var-info x))
182   (:lexical t ((type . fixnum))))
183
184 (deftest variable-info.lexical.type.2
185     (let ((x 42))
186       (prog1
187           (var-info x)
188         (locally (declare (fixnum x))
189           (assert (plusp x)))))
190   (:lexical t nil))
191
192 (deftest variable-info.lexical.type.3
193     (let ((x 42))
194       (locally (declare (fixnum x))
195         (var-info x)))
196   (:lexical t ((type . fixnum))))
197
198 (deftest variable-info.ignore
199     (let ((x 8))
200       (declare (ignore x))
201       (var-info x))
202   (:lexical t ((ignore . t))))
203
204 (deftest variable-info.symbol-macro/local
205     (symbol-macrolet ((x 8))
206       (var-info x))
207   (:symbol-macro t nil))
208
209 (define-symbol-macro my-symbol-macro t)
210
211 (deftest variable-info.symbol-macro/global
212     (var-info my-symbol-macro)
213   (:symbol-macro nil nil))
214
215 (deftest variable-info.undefined
216     (var-info #:undefined)
217   (nil nil nil))
218
219 (declaim (global this-is-global))
220 (deftest global-variable
221     (var-info this-is-global)
222   (:global nil nil))
223
224 (defglobal this-is-global-too 42)
225 (deftest global-variable.2
226     (var-info this-is-global-too)
227   (:global nil ((always-bound . t))))
228
229 ;;;; FUNCTION-INFORMATION
230
231 (defmacro fun-info (var &environment env)
232   (list 'quote (multiple-value-list (function-information var env))))
233
234 (defun my-global-fun (x) x)
235
236 (deftest function-info.global/no-ftype
237     (fun-info my-global-fun)
238   (:function nil nil))
239
240 (declaim (ftype (function (cons) (values t &optional)) my-global-fun-2))
241
242 (defun my-global-fun-2 (x) x)
243
244 (deftest function-info.global/ftype
245     (fun-info my-global-fun-2)
246   (:function nil ((ftype function (cons) (values t &optional)))))
247
248 (defmacro my-macro (x) x)
249
250 (deftest function-info.macro
251     (fun-info my-macro)
252   (:macro nil nil))
253
254 (deftest function-info.macrolet
255     (macrolet ((thingy () nil))
256       (fun-info thingy))
257   (:macro t nil))
258
259 (deftest function-info.special-form
260     (fun-info progn)
261   (:special-form  nil nil))
262
263 (deftest function-info.notinline/local
264     (flet ((x (y) y))
265       (declare (notinline x))
266       (x 1)
267       (fun-info x))
268   (:function t ((inline . notinline))))
269
270 (declaim (notinline my-notinline))
271 (defun my-notinline (x) x)
272
273 (deftest function-info.notinline/global
274     (fun-info my-notinline)
275   (:function nil ((inline . notinline))))
276
277 (declaim (inline my-inline))
278 (defun my-inline (x) x)
279
280 (deftest function-info.inline/global
281     (fun-info my-inline)
282   (:function nil ((inline . inline))))
283
284 (deftest function-information.known-inline
285     (locally (declare (inline identity))
286       (fun-info identity))
287   (:function nil ((inline . inline)
288                   (ftype function (t) (values t &optional)))))
289
290 (deftest function-information.ftype
291     (flet ((foo (x) x))
292       (declare (ftype (sfunction (integer) integer) foo))
293       (fun-info foo))
294   (:function
295    t
296    ((ftype function (integer) (values integer &optional)))))
297
298 ;;;;; AUGMENT-ENVIRONMENT
299
300 (defmacro ct (form &environment env)
301   (let ((toeval `(let ((lexenv (quote ,env)))
302                    ,form)))
303     `(quote ,(eval toeval))))
304
305
306 (deftest augment-environment.variable1
307     (multiple-value-bind (kind local alist)
308         (variable-information
309          'x
310          (augment-environment nil :variable (list 'x) :declare '((type integer x))))
311       (list kind local (cdr (assoc 'type alist))))
312   (:lexical t integer))
313
314 (defvar *foo*)
315
316 (deftest augment-environment.variable2
317     (identity (variable-information '*foo* (augment-environment nil :variable '(*foo*))))
318   :lexical)
319
320 (deftest augment-environment.variable3
321     (identity (variable-information 'foo (augment-environment nil :variable '(foo))))
322   :lexical)
323
324 (deftest augment-environment.variable.special1
325     (identity (variable-information 'x (augment-environment nil :variable '(x) :declare '((special x)))))
326   :special)
327
328 (deftest augment-environment.variable.special12
329     (locally (declare (special x))
330       (ct
331        (variable-information
332         'x
333         (identity (augment-environment lexenv :variable '(x))))))
334   :lexical)
335
336 (deftest augment-environment.variable.special13
337     (let* ((e1 (augment-environment nil :variable '(x) :declare '((special x))))
338            (e2 (augment-environment e1  :variable '(x))))
339       (identity (variable-information 'x e2)))
340   :lexical)
341
342 (deftest augment-environment.variable.special.mask
343     (let* ((e1 (augment-environment nil :variable '(x) :declare '((ignore x))))
344            (e2 (augment-environment e1  :variable '(x))))
345       (assoc 'ignore
346              (nth 2 (multiple-value-list
347                      (variable-information 'x e2)))))
348   nil)
349
350 (deftest augment-environment.variable.ignore
351     (variable-information
352      'x
353      (augment-environment nil
354                           :variable '(x)
355                           :declare  '((ignore x))))
356   :lexical
357   t
358   ((ignore . t)))
359
360 (deftest augment-environment.function
361     (function-information
362      'foo
363      (augment-environment nil
364                           :function '(foo)
365                           :declare  '((ftype (sfunction (integer) integer) foo))))
366   :function
367   t
368   ((ftype function (integer) (values integer &optional))))
369
370
371 (deftest augment-environment.macro
372     (macroexpand '(mac feh)
373                  (augment-environment
374                   nil
375                   :macro (list (list 'mac #'(lambda (form benv)
376                                               (declare (ignore env))
377                                               `(quote ,form ,form ,form))))))
378   (quote (mac feh) (mac feh) (mac feh))
379   t)
380
381 (deftest augment-environment.symbol-macro
382     (macroexpand 'sym
383                  (augment-environment
384                   nil
385                   :symbol-macro (list (list 'sym '(foo bar baz)))))
386   (foo bar baz)
387   t)
388
389 (deftest augment-environment.macro2
390     (eval (macroexpand '(newcond
391                          ((= 1 2) 'foo)
392                          ((= 1 1) 'bar))
393                        (augment-environment nil :macro (list (list 'newcond (macro-function 'cond))))))
394   bar)
395
396
397 (deftest augment-environment.nest
398     (let ((x 1))
399       (ct
400        (let* ((e (augment-environment lexenv :variable '(y))))
401          (list
402           (variable-information 'x e)
403           (variable-information 'y e)))))
404   (:lexical :lexical))
405
406 (deftest augment-environment.nest2
407     (symbol-macrolet ((x "x"))
408       (ct
409        (let* ((e (augment-environment lexenv :variable '(y))))
410          (list
411           (macroexpand 'x e)
412           (variable-information 'y e)))))
413   ("x" :lexical))
414
415 (deftest augment-environment.symbol-macro-var
416     (let ((e (augment-environment
417               nil
418               :symbol-macro (list (list 'sym '(foo bar baz)))
419               :variable '(x))))
420       (list (macroexpand 'sym e)
421             (variable-information 'x e)))
422   ((foo bar baz)
423    :lexical))
424
425