Workaround for lp# 1370836
[sbcl.git] / tests / interface.impure.lisp
blobe59213f0eeb95a26b8ee0935d6aee683a5526978
1 ;;;; tests for problems in the interface presented to the user/programmer
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
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
8 ;;;; from CMU CL.
9 ;;;;
10 ;;;; This software is in the public domain and is provided with
11 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
14 (load "assertoid.lisp")
15 (load "test-util.lisp")
16 (use-package "ASSERTOID")
17 (use-package "TEST-UTIL")
20 (with-test (:name :disassemble)
21 ;;; DISASSEMBLE shouldn't fail on closures or unpurified functions
22 (defun disassemble-fun (x) x)
23 (disassemble 'disassemble-fun))
25 (with-test (:name :disassemble-closure)
26 (let ((x 1)) (defun disassemble-closure (y) (if y (setq x y) x)))
27 (disassemble 'disassemble-closure))
29 #+sb-eval
30 (with-test (:name :disassemble-interpreted)
31 ;; Nor should it fail on interpreted functions
32 (let ((sb-ext:*evaluator-mode* :interpret))
33 (eval `(defun disassemble-eval (x) x))
34 (disassemble 'disassemble-eval))
36 ;; disassemble-eval should still be an interpreted function.
37 ;; clhs disassemble: "(If that function is an interpreted function,
38 ;; it is first compiled but the result of this implicit compilation
39 ;; is not installed.)"
40 (assert (sb-eval:interpreted-function-p #'disassemble-eval)))
42 (with-test (:name :disassemble-generic)
43 ;; nor should it fail on generic functions or other funcallable instances
44 (defgeneric disassemble-generic (x))
45 (disassemble 'disassemble-generic)
46 (let ((fin (make-instance 'sb-mop:funcallable-standard-object)))
47 (disassemble fin)))
49 ;;; while we're at it, much the same applies to
50 ;;; FUNCTION-LAMBDA-EXPRESSION:
51 (defun fle-fun (x) x)
53 (let ((x 1)) (defun fle-closure (y) (if y (setq x y) x)))
55 (with-test (:name :function-lambda-expression)
56 (flet ((fle-name (x)
57 (nth-value 2 (function-lambda-expression x))))
58 (assert (eql (fle-name #'fle-fun) 'fle-fun))
59 (assert (eql (fle-name #'fle-closure) 'fle-closure))
60 (assert (eql (fle-name #'disassemble-generic) 'disassemble-generic))
61 (function-lambda-expression
62 (make-instance 'sb-mop:funcallable-standard-object))
63 (function-lambda-expression
64 (make-instance 'generic-function))
65 (function-lambda-expression
66 (make-instance 'standard-generic-function))
67 #+sb-eval
68 (progn
69 (let ((sb-ext:*evaluator-mode* :interpret))
70 (eval `(defun fle-eval (x) x))
71 (assert (eql (fle-name #'fle-eval) 'fle-eval)))
73 ;; fle-eval should still be an interpreted function.
74 (assert (sb-eval:interpreted-function-p #'fle-eval)))))
77 ;;; support for DESCRIBE tests
78 (defstruct to-be-described a b)
79 (defclass forward-describe-class (forward-describe-ref) (a))
80 (let ((sb-ext:*evaluator-mode* :compile))
81 (eval `(let (x) (defun closure-to-describe () (incf x)))))
83 (with-test (:name :describe-empty-gf)
84 (describe (make-instance 'generic-function))
85 (describe (make-instance 'standard-generic-function)))
87 ;;; DESCRIBE should run without signalling an error.
88 (with-test (:name (describe :no-error))
89 (describe (make-to-be-described))
90 (describe 12)
91 (describe "a string")
92 (describe 'symbolism)
93 (describe (find-package :cl))
94 (describe '(a list))
95 (describe #(a vector))
96 ;; bug 824974
97 (describe 'closure-to-describe))
99 ;;; The DESCRIBE-OBJECT methods for built-in CL stuff should do
100 ;;; FRESH-LINE and TERPRI neatly.
101 (dolist (i (list (make-to-be-described :a 14) 12 "a string"
102 #0a0 #(1 2 3) #2a((1 2) (3 4)) 'sym :keyword
103 (find-package :keyword) (list 1 2 3)
104 nil (cons 1 2) (make-hash-table)
105 (let ((h (make-hash-table)))
106 (setf (gethash 10 h) 100
107 (gethash 11 h) 121)
109 (make-condition 'simple-error)
110 (make-condition 'simple-error :format-control "fc")
111 #'car #'make-to-be-described (lambda (x) (+ x 11))
112 (constantly 'foo) #'(setf to-be-described-a)
113 #'describe-object (find-class 'to-be-described)
114 (find-class 'forward-describe-class)
115 (find-class 'forward-describe-ref) (find-class 'cons)))
116 (let ((s (with-output-to-string (s)
117 (write-char #\x s)
118 (describe i s))))
119 (macrolet ((check (form)
120 `(or ,form
121 (error "misbehavior in DESCRIBE of ~S:~% ~S" i ',form))))
122 (check (char= #\x (char s 0)))
123 ;; one leading #\NEWLINE from FRESH-LINE or the like, no more
124 (check (char= #\newline (char s 1)))
125 (check (char/= #\newline (char s 2)))
126 ;; one trailing #\NEWLINE from TERPRI or the like, no more
127 (let ((n (length s)))
128 (check (char= #\newline (char s (- n 1))))
129 (check (char/= #\newline (char s (- n 2))))))))
132 ;;; Tests of documentation on types and classes
134 (defun assert-documentation (thing doc-type expected)
135 ;; This helper function makes ASSERT errors print THING, DOC-TYPE,
136 ;; the return value of DOCUMENTATION and EXPECTED.
137 (flet ((assert-documentation-helper (thing doc-type documentation expected)
138 (declare (ignore thing doc-type))
139 (equal documentation expected)))
140 (assert (assert-documentation-helper
141 thing doc-type (documentation thing doc-type) expected))))
143 (defpackage #:documentation.package
144 (:documentation "PACKAGE"))
146 (with-test (:name (documentation package))
147 (assert-documentation (find-package '#:documentation.package) t "PACKAGE")
148 (setf (documentation (find-package '#:documentation.package) t) "PACKAGE2")
149 (assert-documentation (find-package '#:documentation.package) t "PACKAGE2"))
151 (defclass foo ()
153 (:documentation "FOO"))
155 (defclass documentation.funcallable-instance ()
157 (:metaclass sb-mop:funcallable-standard-class)
158 (:documentation "FEZ"))
160 (defstruct bar "BAR")
162 (define-condition baz ()
164 (:documentation "BAZ"))
166 (macrolet
167 ((do-class (name expected &optional structurep)
168 `(progn
169 (assert-documentation ',name 'type ,expected)
170 (assert-documentation (find-class ',name) 'type ,expected)
171 (assert-documentation (find-class ',name) 't ,expected)
172 ,@(when structurep
173 `((assert-documentation ',name 'structure ,expected)))
175 (let ((new1 (symbol-name (gensym "NEW1")))
176 (new2 (symbol-name (gensym "NEW2")))
177 (new3 (symbol-name (gensym "NEW3")))
178 (new4 (symbol-name (gensym "NEW4"))))
179 (declare (ignorable new4))
180 (setf (documentation ',name 'type) new1)
181 (assert-documentation (find-class ',name) 'type new1)
182 (setf (documentation (find-class ',name) 'type) new2)
183 (assert-documentation (find-class ',name) 't new2)
184 (setf (documentation (find-class ',name) 't) new3)
185 (assert-documentation ',name 'type new3)
186 ,@(when structurep
187 `((assert-documentation ',name 'structure new3)
188 (setf (documentation ',name 'structure) new4)
189 (assert-documentation ',name 'structure new4)))))))
191 (with-test (:name (documentation class standard-class))
192 (do-class foo "FOO"))
194 (with-test (:name (documentation class sb-mop:funcallable-standard-class))
195 (do-class documentation.funcallable-instance "FEZ"))
197 (with-test (:name (documentation struct 1))
198 (do-class bar "BAR" t))
200 (with-test (:name (documentation condition))
201 (do-class baz "BAZ")))
203 (defstruct (frob (:type vector)) "FROB")
205 (with-test (:name (documentation struct 2))
206 (assert-documentation 'frob 'structure "FROB")
207 (setf (documentation 'frob 'structure) "NEW5")
208 (assert-documentation 'frob 'structure "NEW5"))
210 (deftype quux ()
211 "QUUX"
214 (with-test (:name (documentation type))
215 (assert-documentation 'quux 'type "QUUX")
216 (setf (documentation 'quux 'type) "NEW4")
217 (assert-documentation 'quux 'type "NEW4"))
219 (define-compiler-macro cmacro (x)
220 "compiler macro"
223 (define-compiler-macro (setf cmacro) (y x)
224 "setf compiler macro"
225 (declare (ignore x))
228 (with-test (:name (documentation compiler-macro))
229 (assert-documentation 'cmacro 'compiler-macro "compiler macro")
230 (assert-documentation '(setf cmacro) 'compiler-macro "setf compiler macro"))
232 (defun (setf documentation.setf) (x)
233 "(setf foo) documentation"
236 (with-test (:name (documentation function setf))
237 (flet ((expect (documentation)
238 (assert-documentation
239 '(setf documentation.setf) 'function documentation)
240 (assert-documentation
241 #'(setf documentation.setf) 'function documentation)
242 (assert-documentation
243 #'(setf documentation.setf) t documentation)))
244 (expect "(setf foo) documentation")
245 ;; The original test checked this twice. No idea why.
246 (expect "(setf foo) documentation")
248 ;; Modification
249 (setf (documentation '(setf documentation.setf) 'function)
250 "(setf bar) documentation")
251 (expect "(setf bar) documentation")
253 (setf (documentation #'(setf documentation.setf) 'function)
254 "(setf baz) documentation")
255 (expect "(setf baz) documentation")
257 (setf (documentation #'(setf documentation.setf) t)
258 "(setf fez) documentation")
259 (expect "(setf fez) documentation")))
261 (with-test (:name (documentation lambda))
262 (let ((f (lambda () "aos the zos" t))
263 (g (sb-int:named-lambda fii () "zoot the fruit" t)))
264 (dolist (doc-type '(t function))
265 (assert-documentation f doc-type "aos the zos")
266 (assert-documentation g doc-type "zoot the fruit"))
267 (setf (documentation f t) "fire")
268 (assert-documentation f t "fire")
269 (assert-documentation g t "zoot the fruit")))
271 (with-test (:name (documentation flet))
272 (assert
273 (string= (documentation
274 (flet ((quux (x)
275 "this is FLET quux"
276 (/ x 2)))
277 #'quux)
279 "this is FLET quux")))
281 (with-test (:name (documentation labels))
282 (assert
283 (string= (documentation
284 (labels ((rec (x)
285 "this is LABELS rec"
286 (if (plusp x)
287 (* x (rec (1- x)))
288 1)))
289 #'rec)
291 "this is LABELS rec")))
293 (let ((x 1))
294 (defun docfoo (y)
295 "bar"
296 (incf x y)))
298 (with-test (:name (documentation :closure))
299 (assert-documentation 'docfoo 'function "bar")
300 (assert (string= (setf (documentation 'docfoo 'function) "baz") "baz"))
301 (assert-documentation 'docfoo 'function "baz")
302 (assert-documentation #'docfoo t "baz")
303 (assert (string= (setf (documentation #'docfoo t) "zot") "zot"))
304 (assert-documentation #'docfoo t "zot")
305 (assert-documentation 'docfoo 'function "zot")
306 (assert (not (setf (documentation 'docfoo 'function) nil)))
307 (assert-documentation 'docfoo 'function nil))
309 (with-test (:name (documentation :built-in-macro) :skipped-on '(not :sb-doc))
310 (assert (documentation 'trace 'function)))
312 (with-test (:name (documentation :built-in-function) :skipped-on '(not :sb-doc))
313 (assert (documentation 'cons 'function)))
315 (defvar documentation.variable nil
316 "foo variable documentation")
318 (with-test (:name (documentation variable))
319 (assert-documentation 'documentation.variable 'variable
320 "foo variable documentation")
321 (setf (documentation 'documentation.variable 'variable)
322 "baz variable documentation")
323 (assert-documentation 'documentation.variable 'variable
324 "baz variable documentation"))
326 (with-test (:name (documentation :mismatch-for-function))
327 (defun test ()
329 nil)
330 (setf (symbol-function 'test2) #'test)
331 (setf (documentation 'test 'function) "Y")
332 (assert (equal (documentation #'test t)
333 (documentation 'test 'function)))
334 (setf (documentation 'test2 'function) "Z")
335 (assert (not
336 (equal (documentation 'test 'function)
337 (documentation 'test2 'function)))))
339 (with-test (:name (documentation setf :on nil))
340 (assert
341 (handler-case
342 (assert (equal (setf (documentation nil 'function) "foo") "foo"))
343 (style-warning () t)
344 (:no-error (x)
345 (declare (ignore x))
346 nil))))
348 (with-test (:name :describe-generic-function-with-assumed-type)
349 ;; Signalled an error at one point
350 (flet ((zoo () (gogo)))
351 (defmethod gogo () nil)
352 (describe 'gogo)))
354 (defmacro bug-643958-test ()
355 "foo"
356 :ding!)
358 (with-test (:name :bug-643958)
359 (assert (equal "foo" (documentation 'bug-643958-test 'function)))
360 (setf (documentation 'bug-643958-test 'function) "bar")
361 (assert (equal "bar" (documentation 'bug-643958-test 'function))))
363 (defclass cannot-print-this ()
365 (defmethod print-object ((oops cannot-print-this) stream)
366 (error "No go!"))
367 (with-test (:name :describe-suppresses-print-errors)
368 (handler-bind ((error #'continue))
369 (with-output-to-string (s)
370 (describe (make-instance 'cannot-print-this) s))))
371 (with-test (:name :backtrace-suppresses-print-errors)
372 (handler-bind ((error #'continue))
373 (with-output-to-string (s)
374 (labels ((foo (n x)
375 (when (plusp n)
376 (foo (1- n) x))
377 (when (zerop n)
378 (sb-debug:backtrace 100 s))))
379 (foo 100 (make-instance 'cannot-print-this))))))
380 (with-test (:name :backtrace-and-circles)
381 (handler-bind ((error #'continue))
382 (with-output-to-string (s)
383 (labels ((foo (n x)
384 (when (plusp n)
385 (foo (1- n) x))
386 (when (zerop n)
387 (sb-debug:backtrace 100 s))))
388 (foo 100 (let ((list (list t)))
389 (nconc list list)))))))
391 (with-test (:name :endianness-in-features)
392 (assert
393 (or (member :big-endian *features*)
394 (member :little-endian *features*))))
396 (with-test (:name (trace generic-function))
397 (defgeneric traced-gf (x))
398 (defmethod traced-gf (x) (1+ x))
399 (assert (= (traced-gf 3) 4))
400 (trace traced-gf)
401 (let ((output (with-output-to-string (*trace-output*)
402 (assert (= (traced-gf 3) 4)))))
403 (assert (> (length output) 0)))
404 (assert (typep #'traced-gf 'standard-generic-function))
405 (untrace traced-gf)
406 (let ((output (with-output-to-string (*trace-output*)
407 (assert (= (traced-gf 3) 4)))))
408 (assert (= (length output) 0))))
410 ;;;; success