Fix make-array transforms.
[sbcl.git] / tests / pprint.impure.lisp
1 ;;;; test of the pretty-printer
2
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.
13
14 (in-package :cl-user)
15
16 ;;;; tests for former BUG 99, where pretty-printing was pretty messed
17 ;;;; up, e.g. PPRINT-LOGICAL-BLOCK - because of CHECK-FOR-CIRCULARITY
18 ;;;; - didn't really work:
19 ;;;;   "DESCRIBE interacts poorly with *PRINT-CIRCLE*, e.g. the output from
20 ;;;;    (let ((*print-circle* t)) (describe (make-hash-table)))
21 ;;;;  is weird, [...] #<HASH-TABLE :TEST EQL :COUNT 0 {90BBFC5}> is an . (EQL)
22 ;;;; ..."
23 ;;;; So, this was mainly a pretty printing problem.
24
25 ;;; Create a circular list.
26 (eval-when (:compile-toplevel :load-toplevel :execute)
27   (defparameter *circ-list* '(1 1))
28   (prog1 nil
29     (setf (cdr *circ-list*) *circ-list*)))
30
31 ;;; I think this test is bogus. PPRINT-LOGICAL-BLOCK needs to print
32 ;;; the #1= and mark *CIRC-LIST* as having been printed for the first
33 ;;; time. After that any attempt to print *CIRC-LIST* must result in
34 ;;; in a #1# being printed. Thus the right output is (for once)
35 ;;; #1=#1#. -- JES, 2005-06-05
36 #+nil
37 ;;; circular lists are still being printed correctly?
38 (assert (equal
39          (with-output-to-string (*standard-output*)
40            (let ((*print-circle* t))
41              (pprint-logical-block (*standard-output* *circ-list*)
42                                  (format *standard-output* "~S" *circ-list*))))
43          "#1=(1 . #1#)"))
44
45 ;;; test from CLHS
46 (with-test (:name :pprint-clhs-example)
47   (assert (equal
48            (with-output-to-string (*standard-output*)
49              (let ((a (list 1 2 3)))
50                (setf (cdddr a) a)
51                (let ((*print-circle* t))
52                  (write a :stream *standard-output*))
53                :done))
54            "#1=(1 2 3 . #1#)")))
55
56 (with-test (:name (:pprint :bug-99))
57   (assert (equal
58            (with-output-to-string (*standard-output*)
59              (let* ((*print-circle* t))
60                (format *standard-output* "~@<~S ~_is ~S. This was not seen!~:>"
61                        'eql 'eql)))
62            "EQL is EQL. This was not seen!"))
63
64   (assert (equal
65            (with-output-to-string (*standard-output*)
66              (let* ((*print-circle* t))
67                (format *standard-output*
68                        "~@<~S ~_is ~S and ~S. This was not seen!~:>"
69                        'eql 'eql 'eql)))
70            "EQL is EQL and EQL. This was not seen!")))
71
72 ;;; the original test for BUG 99 (only interactive), no obvious
73 ;;; way to make an automated test:
74 ;;;  (LET ((*PRINT-CIRCLE* T)) (DESCRIBE (MAKE-HASH-TABLE)))
75
76 ;;; bug 263: :PREFIX, :PER-LINE-PREFIX and :SUFFIX arguments of
77 ;;; PPRINT-LOGICAL-BLOCK may be complex strings
78 (with-test (:name :pprint-logical-block-arguments-complex-strings)
79   (let ((list '(1 2 3))
80         (prefix (make-array 2
81                             :element-type 'character
82                             :displaced-to ";x"
83                             :fill-pointer 1))
84         (suffix (make-array 2
85                             :element-type 'character
86                             :displaced-to ">xy"
87                             :displaced-index-offset 1
88                             :fill-pointer 1)))
89     (assert (equal (with-output-to-string (s)
90                      (pprint-logical-block (s list
91                                               :per-line-prefix prefix
92                                               :suffix suffix)
93                        (format s "~{~W~^~:@_~}" list)))
94                    (format nil ";1~%~
95                               ;2~%~
96                               ;3x")))))
97
98 ;;; bug 141b: not enough care taken to disambiguate ,.FOO and ,@FOO
99 ;;; from , .FOO and , @FOO
100 (with-test (:name :pprint-backquote-magic)
101   (assert (equal
102            (with-output-to-string (s)
103              (write '`(,  .foo) :stream s :pretty t :readably t))
104            "`(, .FOO)"))
105   (assert (equal
106            (with-output-to-string (s)
107              (write '`(,  @foo) :stream s :pretty t :readably t))
108            "`(, @FOO)"))
109   (assert (equal
110            (with-output-to-string (s)
111              (write '`(,  ?foo) :stream s :pretty t :readably t))
112            "`(,?FOO)")))
113
114 ;;; bug reported by Paul Dietz on sbcl-devel: unquoted lambda lists
115 ;;; were leaking the SB-IMPL::BACKQ-COMMA implementation.
116 (with-test (:name :pprint-leaking-backq-comma)
117   (assert (equal
118            (with-output-to-string (s)
119              (write '`(foo ,x) :stream s :pretty t :readably t))
120            "`(FOO ,X)"))
121   (assert (equal
122            (with-output-to-string (s)
123              (write '`(foo ,@x) :stream s :pretty t :readably t))
124            "`(FOO ,@X)"))
125   #+nil                       ; '`(foo ,.x) => '`(foo ,@x) apparently.
126   (assert (equal
127            (with-output-to-string (s)
128              (write '`(foo ,.x) :stream s :pretty t :readably t))
129            "`(FOO ,.X)"))
130   (assert (equal
131            (with-output-to-string (s)
132              (write '`(lambda ,x) :stream s :pretty t :readably t))
133            "`(LAMBDA ,X)"))
134   (assert (equal
135            (with-output-to-string (s)
136              (write '`(lambda ,@x) :stream s :pretty t :readably t))
137            "`(LAMBDA ,@X)"))
138   #+nil                                 ; see above
139   (assert (equal
140            (with-output-to-string (s)
141              (write '`(lambda ,.x) :stream s :pretty t :readably t))
142            "`(LAMBDA ,.X)"))
143   (assert (equal
144            (with-output-to-string (s)
145              (write '`(lambda (,x)) :stream s :pretty t :readably t))
146            "`(LAMBDA (,X))")))
147
148 ;;; more backquote printing brokenness, fixed quasi-randomly by CSR.
149 ;;; NOTE KLUDGE FIXME: because our backquote optimizes at read-time,
150 ;;; these assertions, like the ones above, are fragile.  Likewise, it
151 ;;; is very possible that at some point READABLY printing backquote
152 ;;; expressions will have to change to printing the low-level conses,
153 ;;; since the magical symbols are accessible though (car '`(,foo)) and
154 ;;; friends.  HATE HATE HATE.  -- CSR, 2004-06-10
155 (with-test (:name :pprint-more-backquote-brokeness)
156   (assert (equal
157            (with-output-to-string (s)
158              (write '``(foo ,@',@bar) :stream s :pretty t))
159            "``(FOO ,@',@BAR)"))
160   (assert (equal
161            (with-output-to-string (s)
162              (write '``(,,foo ,',foo foo) :stream s :pretty t))
163            "``(,,FOO ,',FOO FOO)"))
164   (assert (equal
165            (with-output-to-string (s)
166              (write '``(((,,foo) ,',foo) foo) :stream s :pretty t))
167            "``(((,,FOO) ,',FOO) FOO)")))
168 \f
169 ;;; SET-PPRINT-DISPATCH should accept function name arguments, and not
170 ;;; rush to coerce them to functions.
171 (set-pprint-dispatch '(cons (eql frob)) 'ppd-function-name)
172 (defun ppd-function-name (s o)
173   (print (length o) s))
174
175 (with-test (:name (:set-pprint-dispatch :no-function-coerce)))
176 (let ((s (with-output-to-string (s)
177            (pprint '(frob a b) s))))
178   (assert (position #\3 s)))
179 \f
180 ;; Test that circularity detection works with pprint-logical-block
181 ;; (including when called through pprint-dispatch).
182 (with-test (:name :pprint-circular-detection)
183   (let ((*print-pretty* t)
184         (*print-circle* t)
185         (*print-pprint-dispatch* (copy-pprint-dispatch)))
186     (labels ((pprint-a (stream form &rest rest)
187                (declare (ignore rest))
188                (pprint-logical-block (stream form :prefix "<" :suffix ">")
189                  (pprint-exit-if-list-exhausted)
190                  (loop
191                    (write (pprint-pop) :stream stream)
192                    (pprint-exit-if-list-exhausted)
193                    (write-char #\space stream)))))
194       (set-pprint-dispatch '(cons (eql a)) #'pprint-a)
195       (assert (string= "<A 1 2 3>"
196                        (with-output-to-string (s)
197                          (write '(a 1 2 3) :stream s))))
198       (assert (string= "#1=<A 1 #1# #2=#(2) #2#>"
199                        (with-output-to-string (s)
200                          (write '#2=(a 1 #2# #5=#(2) #5#) :stream s))))
201       (assert (string= "#1=(B #2=<A 1 #1# 2 3> #2#)"
202                        (with-output-to-string (s)
203                          (write '#3=(b #4=(a 1 #3# 2 3) #4#) :stream s)))))))
204
205 ;; Test that a circular improper list inside a logical block works.
206 (with-test (:name :pprint-circular-improper-lists-inside-logical-blocks)
207   (let ((*print-circle* t)
208         (*print-pretty* t))
209     (assert (string= "#1=(#2=(#2# . #3=(#1# . #3#)))"
210                      (with-output-to-string (s)
211                        (write '#1=(#2=(#2# . #3=(#1# . #3#))) :stream s))))))
212
213 ;;; Printing malformed defpackage forms without errors.
214 (with-test (:name :pprint-defpackage)
215   (let ((*standard-output* (make-broadcast-stream)))
216     (pprint '(defpackage :foo nil))
217     (pprint '(defpackage :foo 42))))
218
219 (with-test (:name :standard-pprint-dispatch-modified)
220   (assert
221    (eq :error
222        (handler-case (with-standard-io-syntax
223                        (set-pprint-dispatch 'symbol (constantly nil))
224                        :no-error)
225          (sb-int:standard-pprint-dispatch-table-modified-error ()
226            :error)))))
227
228 (with-test (:name :pprint-defmethod-lambda-list-function)
229   (flet ((to-string (form)
230            (let ((string (with-output-to-string (s) (pprint form s))))
231              (assert (eql #\newline (char string 0)))
232              (subseq string 1))))
233     (assert (equal "(DEFMETHOD FOO ((FUNCTION CONS)) FUNCTION)"
234                    (to-string `(defmethod foo ((function cons)) function))))
235     (assert (equal "(DEFMETHOD FOO :AFTER (FUNCTION CONS) FUNCTION)"
236                    (to-string `(defmethod foo :after (function cons) function))))))
237
238 (defclass frob () ())
239
240 (defmethod print-object ((obj frob) stream)
241   (print-unreadable-object (obj stream :type nil :identity nil)
242     (format stream "FRABOTZICATOR")))
243
244 ;;; SBCL < 1.0.38 printed #<\nFRABOTIZICATOR>
245 (with-test (:name (:pprint-unreadable-object :no-ugliness-when-type=nil))
246   (assert (equal "#<FRABOTZICATOR>"
247                  (let ((*print-right-margin* 5)
248                        (*print-pretty* t))
249                    (format nil "~@<~S~:>" (make-instance 'frob))))))
250
251 (with-test (:name :pprint-logical-block-code-deletion-node)
252   (handler-case
253       (compile nil
254                `(lambda (words &key a b c)
255                   (pprint-logical-block (nil words :per-line-prefix (or a b c))
256                     (pprint-fill *standard-output* (sort (copy-seq words) #'string<) nil))))
257     ((or sb-ext:compiler-note warning) (c)
258       (error e))))
259
260 (with-test (:name :pprint-logical-block-multiple-per-line-prefix-eval)
261   (funcall (compile nil
262                     `(lambda ()
263                        (let ((n 0))
264                          (with-output-to-string (s)
265                            (pprint-logical-block (s nil :per-line-prefix (if (eql 1 (incf n))
266                                                                              "; "
267                                                                              (error "oops")))
268                              (pprint-newline :mandatory s)
269                              (pprint-newline :mandatory s)))
270                          n)))))
271
272 (with-test (:name :can-restore-orig-pprint-dispatch-table)
273   (let* ((orig (pprint-dispatch 'some-symbol))
274          (alt (lambda (&rest args) (apply orig args))))
275     (set-pprint-dispatch 'symbol alt)
276     (assert (eq alt (pprint-dispatch 'some-symbol)))
277     (setf *print-pprint-dispatch* (copy-pprint-dispatch nil))
278     (assert (eq orig (pprint-dispatch 'some-symbol)))
279     (assert (not (eq alt orig)))))
280
281 (with-test (:name :pprint-improper-list)
282   (let* ((max-length 10)
283          (stream (make-broadcast-stream))
284          (errors
285            (loop for symbol being the symbol in :cl
286                  nconc
287                  (loop for i from 1 below max-length
288                        for list = (cons symbol 10) then (cons symbol list)
289                        when (nth-value 1 (ignore-errors (pprint list stream)))
290                        collect (format nil "(~{~a ~}~a . 10)" (butlast list) symbol)))))
291     (when errors
292       (error "Can't PPRINT imporper lists: ~a" errors))))
293
294 (with-test (:name :pprint-circular-backq-comma)
295   ;; LP 1161218 reported by James M. Lawrence
296   (let ((string (write-to-string '(let ((#1=#:var '(99)))
297                                    `(progn ,@(identity #1#)))
298                                  :circle t :pretty t)))
299     (assert (not (search "#2#" string)))))
300
301 (with-test (:name :pprint-dotted-setf)
302   (let ((*print-pretty* t))
303     (equal (format nil "~a" '(setf . a))
304            "(SETF . A)")))
305
306 \f
307 ;;; success