1 ;;;; test of the pretty-printer
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
12 ;;;; more information.
16 ;;;; Assert that entries inserted into a dispatch table with equal priority
17 ;;;; are order-preserving - unless they are of the form (CONS (EQL x)).
18 ;;;; This is not a requirement in general, but is quite reasonable.
19 (with-test (:name
:pprint-dispatch-order-preserving
)
20 (let ((tbl (sb-pretty::make-pprint-dispatch-table
)))
21 (handler-bind ((style-warning #'muffle-warning
)) ; nonexistent types
22 (set-pprint-dispatch 'foo1
#'pprint-fill
5 tbl
)
23 (set-pprint-dispatch 'fool
#'pprint-fill
0 tbl
)
24 (set-pprint-dispatch 'foo2
#'pprint-fill
5 tbl
))
25 (let ((entries (sb-pretty::pprint-dispatch-table-entries tbl
)))
26 (assert (equal (mapcar #'sb-pretty
::pprint-dispatch-entry-type entries
)
27 '(foo1 foo2 fool
))))))
29 ;;;; tests for former BUG 99, where pretty-printing was pretty messed
30 ;;;; up, e.g. PPRINT-LOGICAL-BLOCK - because of CHECK-FOR-CIRCULARITY
31 ;;;; - didn't really work:
32 ;;;; "DESCRIBE interacts poorly with *PRINT-CIRCLE*, e.g. the output from
33 ;;;; (let ((*print-circle* t)) (describe (make-hash-table)))
34 ;;;; is weird, [...] #<HASH-TABLE :TEST EQL :COUNT 0 {90BBFC5}> is an . (EQL)
36 ;;;; So, this was mainly a pretty printing problem.
38 ;;; Create a circular list.
39 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
40 (defparameter *circ-list
* '(1 1))
42 (setf (cdr *circ-list
*) *circ-list
*)))
44 ;;; I think this test is bogus. PPRINT-LOGICAL-BLOCK needs to print
45 ;;; the #1= and mark *CIRC-LIST* as having been printed for the first
46 ;;; time. After that any attempt to print *CIRC-LIST* must result in
47 ;;; in a #1# being printed. Thus the right output is (for once)
48 ;;; #1=#1#. -- JES, 2005-06-05
50 ;;; circular lists are still being printed correctly?
52 (with-output-to-string (*standard-output
*)
53 (let ((*print-circle
* t
))
54 (pprint-logical-block (*standard-output
* *circ-list
*)
55 (format *standard-output
* "~S" *circ-list
*))))
59 (with-test (:name
:pprint-clhs-example
)
61 (with-output-to-string (*standard-output
*)
62 (let ((a (list 1 2 3)))
64 (let ((*print-circle
* t
))
65 (write a
:stream
*standard-output
*))
69 (with-test (:name
(:pprint
:bug-99
))
71 (with-output-to-string (*standard-output
*)
72 (let* ((*print-circle
* t
))
73 (format *standard-output
* "~@<~S ~_is ~S. This was not seen!~:>"
75 "EQL is EQL. This was not seen!"))
78 (with-output-to-string (*standard-output
*)
79 (let* ((*print-circle
* t
))
80 (format *standard-output
*
81 "~@<~S ~_is ~S and ~S. This was not seen!~:>"
83 "EQL is EQL and EQL. This was not seen!")))
85 ;;; the original test for BUG 99 (only interactive), no obvious
86 ;;; way to make an automated test:
87 ;;; (LET ((*PRINT-CIRCLE* T)) (DESCRIBE (MAKE-HASH-TABLE)))
89 ;;; bug 263: :PREFIX, :PER-LINE-PREFIX and :SUFFIX arguments of
90 ;;; PPRINT-LOGICAL-BLOCK may be complex strings
91 (with-test (:name
:pprint-logical-block-arguments-complex-strings
)
94 :element-type
'character
98 :element-type
'character
100 :displaced-index-offset
1
102 (assert (equal (with-output-to-string (s)
103 (pprint-logical-block (s list
104 :per-line-prefix prefix
106 (format s
"~{~W~^~:@_~}" list
)))
111 ;;; bug 141b: not enough care taken to disambiguate ,.FOO and ,@FOO
112 ;;; from , .FOO and , @FOO
113 (with-test (:name
:pprint-backquote-magic
)
115 (with-output-to-string (s)
116 (write '`(, .foo
) :stream s
:pretty t
:readably t
))
119 (with-output-to-string (s)
120 (write '`(, @foo
) :stream s
:pretty t
:readably t
))
123 (with-output-to-string (s)
124 (write '`(, ?foo
) :stream s
:pretty t
:readably t
))
127 ;;; bug reported by Paul Dietz on sbcl-devel: unquoted lambda lists
128 ;;; were leaking the SB-IMPL::BACKQ-COMMA implementation.
129 (with-test (:name
:pprint-leaking-backq-comma
)
131 (with-output-to-string (s)
132 (write '`(foo ,x
) :stream s
:pretty t
:readably t
))
135 (with-output-to-string (s)
136 (write '`(foo ,@x
) :stream s
:pretty t
:readably t
))
139 (with-output-to-string (s)
140 (write '`(foo ,.x
) :stream s
:pretty t
:readably t
))
143 (with-output-to-string (s)
144 (write '`(lambda ,x
) :stream s
:pretty t
:readably t
))
147 (with-output-to-string (s)
148 (write '`(lambda ,@x
) :stream s
:pretty t
:readably t
))
151 (with-output-to-string (s)
152 (write '`(lambda ,.x
) :stream s
:pretty t
:readably t
))
155 (with-output-to-string (s)
156 (write '`(lambda (,x
)) :stream s
:pretty t
:readably t
))
159 ;;; more backquote printing brokenness, fixed quasi-randomly by CSR.
160 ;;; and fixed a little more by DPK.
161 (with-test (:name
:pprint-more-backquote-brokeness
)
162 (flet ((try (input expect
)
163 (assert (equalp (read-from-string expect
) input
))
164 (let ((actual (write-to-string input
:pretty t
)))
165 (unless (equal actual expect
)
166 (error "Failed test for ~S. Got ~S~%"
168 (try '``(foo ,@',@bar
) "``(FOO ,@',@BAR)")
169 (try '``(,,foo
,',foo foo
) "``(,,FOO ,',FOO FOO)")
170 (try '``(((,,foo
) ,',foo
) foo
) "``(((,,FOO) ,',FOO) FOO)")
172 (try '`#(,bar
) "`#(,BAR)")
173 (try '`#(,(bar)) "`#(,(BAR))")
174 (try '`#(,@bar
) "`#(,@BAR)")
175 (try '`#(,@(bar)) "`#(,@(BAR))")
176 (try '`#(a ,b c
) "`#(A ,B C)")
177 (try '`#(,@A
,b c
) "`#(,@A ,B C)")
178 (try '`(,a .
#(foo #() #(,bar
) ,bar
)) "`(,A . #(FOO #() #(,BAR) ,BAR))")
179 (try '(let ((foo (x))) `(let (,foo
) (setq ,foo
(y)) (baz ,foo
)))
180 ;; PPRINT-LET emits a mandatory newline after the bindings,
181 ;; otherwise this'd fit on one line given an adequate right margin.
188 ;;; SET-PPRINT-DISPATCH should accept function name arguments, and not
189 ;;; rush to coerce them to functions.
190 (set-pprint-dispatch '(cons (eql frob
)) 'ppd-function-name
)
191 (defun ppd-function-name (s o
)
192 (print (length o
) s
))
194 (with-test (:name
(:set-pprint-dispatch
:no-function-coerce
)))
195 (let ((s (with-output-to-string (s)
196 (pprint '(frob a b
) s
))))
197 (assert (position #\
3 s
)))
199 ;; Test that circularity detection works with pprint-logical-block
200 ;; (including when called through pprint-dispatch).
201 (with-test (:name
:pprint-circular-detection
)
202 (let ((*print-pretty
* t
)
204 (*print-pprint-dispatch
* (copy-pprint-dispatch)))
205 (labels ((pprint-a (stream form
&rest rest
)
206 (declare (ignore rest
))
207 (pprint-logical-block (stream form
:prefix
"<" :suffix
">")
208 (pprint-exit-if-list-exhausted)
210 (write (pprint-pop) :stream stream
)
211 (pprint-exit-if-list-exhausted)
212 (write-char #\space stream
)))))
213 (set-pprint-dispatch '(cons (eql a
)) #'pprint-a
)
214 (assert (string= "<A 1 2 3>"
215 (with-output-to-string (s)
216 (write '(a 1 2 3) :stream s
))))
217 (assert (string= "#1=<A 1 #1# #2=#(2) #2#>"
218 (with-output-to-string (s)
219 (write '#2=(a 1 #2# #5=#(2) #5#) :stream s
))))
220 (assert (string= "#1=(B #2=<A 1 #1# 2 3> #2#)"
221 (with-output-to-string (s)
222 (write '#3=(b #4=(a 1 #3# 2 3) #4#) :stream s
)))))))
224 ;; Test that a circular improper list inside a logical block works.
225 (with-test (:name
:pprint-circular-improper-lists-inside-logical-blocks
)
226 (let ((*print-circle
* t
)
228 (assert (string= "#1=(#2=(#2# . #3=(#1# . #3#)))"
229 (with-output-to-string (s)
230 (write '#1=(#2=(#2# .
#3=(#1# .
#3#))) :stream s
))))))
232 ;;; Printing malformed defpackage forms without errors.
233 (with-test (:name
:pprint-defpackage
)
234 (let ((*standard-output
* (make-broadcast-stream)))
235 (pprint '(defpackage :foo nil
))
236 (pprint '(defpackage :foo
42))))
238 (with-test (:name
:standard-pprint-dispatch-modified
)
241 (handler-case (with-standard-io-syntax
242 (set-pprint-dispatch 'symbol
(constantly nil
))
244 (sb-int:standard-pprint-dispatch-table-modified-error
()
247 (with-test (:name
:pprint-defmethod-lambda-list-function
)
248 (flet ((to-string (form)
249 (let ((string (with-output-to-string (s) (pprint form s
))))
250 (assert (eql #\newline
(char string
0)))
252 (assert (equal "(DEFMETHOD FOO ((FUNCTION CONS)) FUNCTION)"
253 (to-string `(defmethod foo ((function cons
)) function
))))
254 (assert (equal "(DEFMETHOD FOO :AFTER (FUNCTION CONS) FUNCTION)"
255 (to-string `(defmethod foo :after
(function cons
) function
))))))
257 (defclass frob
() ())
259 (defmethod print-object ((obj frob
) stream
)
260 (print-unreadable-object (obj stream
:type nil
:identity nil
)
261 (format stream
"FRABOTZICATOR")))
263 ;;; SBCL < 1.0.38 printed #<\nFRABOTIZICATOR>
264 (with-test (:name
(:pprint-unreadable-object
:no-ugliness-when-type
=nil
))
265 (assert (equal "#<FRABOTZICATOR>"
266 (let ((*print-right-margin
* 5)
268 (format nil
"~@<~S~:>" (make-instance 'frob
))))))
270 (with-test (:name
:pprint-logical-block-code-deletion-node
)
273 `(lambda (words &key a b c
)
274 (pprint-logical-block (nil words
:per-line-prefix
(or a b c
))
275 (pprint-fill *standard-output
* (sort (copy-seq words
) #'string
<) nil
))))
276 ((or sb-ext
:compiler-note warning
) (c)
279 (with-test (:name
:pprint-logical-block-multiple-per-line-prefix-eval
)
280 (funcall (compile nil
283 (with-output-to-string (s)
284 (pprint-logical-block (s nil
:per-line-prefix
(if (eql 1 (incf n
))
287 (pprint-newline :mandatory s
)
288 (pprint-newline :mandatory s
)))
291 (with-test (:name
:can-restore-orig-pprint-dispatch-table
)
292 (let* ((orig (pprint-dispatch 'some-symbol
))
293 (alt (lambda (&rest args
) (apply orig args
))))
294 (set-pprint-dispatch 'symbol alt
)
295 (assert (eq alt
(pprint-dispatch 'some-symbol
)))
296 (setf *print-pprint-dispatch
* (copy-pprint-dispatch nil
))
297 (assert (eq orig
(pprint-dispatch 'some-symbol
)))
298 (assert (not (eq alt orig
)))))
300 (with-test (:name
:pprint-improper-list
)
301 (let* ((max-length 10)
302 (stream (make-broadcast-stream))
304 (loop for symbol being the symbol in
:cl
306 (loop for i from
1 below max-length
307 for list
= (cons symbol
10) then
(cons symbol list
)
308 when
(nth-value 1 (ignore-errors (pprint list stream
)))
309 collect
(format nil
"(~{~a ~}~a . 10)" (butlast list
) symbol
)))))
311 (error "Can't PPRINT improper lists: ~a" errors
))))
313 (with-test (:name
:pprint-circular-backq-comma
)
314 ;; LP 1161218 reported by James M. Lawrence
315 (let ((string (write-to-string '(let ((#1=#:var
'(99)))
316 `(progn ,@(identity #1#)))
317 :circle t
:pretty t
)))
318 (assert (not (search "#2#" string
)))))
320 (with-test (:name
:pprint-dotted-setf
)
321 (let ((*print-pretty
* t
))
322 (equal (format nil
"~a" '(setf . a
))
325 (with-test (:name
:literal-fun-nested-lists
)
326 (assert (search "EQUALP" (format nil
"~:w" `((((((,#'equalp
)))))))
327 :test
#'char-equal
)))