Fix make-array transforms.
[sbcl.git] / tests / print.impure.lisp
1 ;;;; miscellaneous tests of printing stuff
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 (load "assertoid.lisp")
15 (use-package "ASSERTOID")
16
17 ;;; We should be able to output X readably (at least when *READ-EVAL*).
18 (defun assert-readable-output (x)
19   (assert (eql x
20                (let ((*read-eval* t))
21                  (read-from-string (with-output-to-string (s)
22                                      (write x :stream s :readably t)))))))
23
24 ;;; Even when *READ-EVAL* is NIL, we should be able to output some
25 ;;; (not necessarily readable) representation without signalling an
26 ;;; error.
27 (defun assert-unreadable-output (x)
28   (let ((*read-eval* nil))
29     (with-output-to-string (s) (write x :stream s :readably nil))))
30
31 (defun assert-output (x)
32   (assert-readable-output x)
33   (assert-unreadable-output x))
34
35 ;;; Nathan Froyd reported that sbcl-0.6.11.34 screwed up output of
36 ;;; floating point infinities.
37 (dolist (x (list short-float-positive-infinity short-float-negative-infinity
38                  single-float-positive-infinity single-float-negative-infinity
39                  double-float-positive-infinity double-float-negative-infinity
40                  long-float-positive-infinity long-float-negative-infinity))
41   (assert-output x))
42
43 ;;; Eric Marsden reported that this would blow up in CMU CL (even
44 ;;; though ANSI says that the mismatch between ~F expected type and
45 ;;; provided string type is supposed to be handled without signalling
46 ;;; an error) and provided a fix which was ported to sbcl-0.6.12.35.
47 (assert (null (format t "~F" "foo")))
48
49 ;;; This was a bug in SBCL until 0.6.12.40 (originally reported as a
50 ;;; CMU CL bug by Erik Naggum on comp.lang.lisp).
51 (loop for base from 2 to 36
52       with *print-radix* = t
53       do (let ((*print-base* base))
54            (assert (string= "#*101" (format nil "~S" #*101)))))
55
56 ;;; bug in sbcl-0.7.1.25, reported by DB sbcl-devel 2002-02-25
57 (assert (string= "0.5" (format nil "~2D" 0.5)))
58
59 ;;; we want malformed format strings to cause errors rather than have
60 ;;; some DWIM "functionality".
61 (assert (raises-error? (format nil "~:2T")))
62
63 ;;; bug reported, with fix, by Robert Strandh, sbcl-devel 2002-03-09,
64 ;;; fixed in sbcl-0.7.1.36:
65 (assert (string= (format nil "~2,3,8,'0$" 1234567.3d0) "1234567.30"))
66
67 ;;; checks that other FORMAT-DOLLAR output remains sane after the
68 ;;; 0.7.1.36 change
69 (assert (string= (format nil "~$" 0) "0.00"))
70 (assert (string= (format nil "~$" 4) "4.00"))
71 (assert (string= (format nil "~$" -4.0) "-4.00"))
72 (assert (string= (format nil "~2,7,11$" -4.0) "-0000004.00"))
73 (assert (string= (format nil "~2,7,11,' $" 1.1) " 0000001.10"))
74 (assert (string= (format nil "~1,7,11,' $" 1.1) "  0000001.1"))
75 (assert (string= (format nil "~1,3,8,' $" 7.3) "   007.3"))
76 (assert (string= (format nil "~2,3,8,'0$" 7.3) "00007.30"))
77
78 ;;; Check for symbol lookup in ~/ / directive -- double-colon was
79 ;;; broken in 0.7.1.36 and earlier
80 (defun print-foo (stream arg colonp atsignp &rest params)
81   (declare (ignore colonp atsignp params))
82   (format stream "~d" arg))
83
84 (assert (string= (format nil "~/print-foo/" 2) "2"))
85 (assert (string= (format nil "~/cl-user:print-foo/" 2) "2"))
86 (assert (string= (format nil "~/cl-user::print-foo/" 2) "2"))
87 (assert (raises-error? (format nil "~/cl-user:::print-foo/" 2)))
88 (assert (raises-error? (format nil "~/cl-user:a:print-foo/" 2)))
89 (assert (raises-error? (format nil "~/a:cl-user:print-foo/" 2)))
90 (assert (raises-error? (format nil "~/cl-user:print-foo:print-foo/" 2)))
91
92 ;;; better make sure that we get this one right, too
93 (defun print-foo\:print-foo (stream arg colonp atsignp &rest params)
94   (declare (ignore colonp atsignp params))
95   (format stream "~d" arg))
96
97 (assert (string= (format nil "~/cl-user:print-foo:print-foo/" 2) "2"))
98 (assert (string= (format nil "~/cl-user::print-foo:print-foo/" 2) "2"))
99
100 ;;; Check for error detection of illegal directives in a~<..~> justify
101 ;;; block (see ANSI section 22.3.5.2)
102 (assert (raises-error? (format nil "~<~W~>" 'foo)))
103 (assert (raises-error? (format nil "~<~<~A~:>~>" '(foo))))
104 (assert (string= (format nil "~<~<~A~>~>" 'foo) "FOO"))
105
106 (with-test (:name (:format :justification-atsign-check))
107   (assert (raises-error? (format nil "~<~@>")))
108   (assert (raises-error? (eval '(format nil "~<~@>")))))
109
110 ;;; Check that arrays that we print while *PRINT-READABLY* is true are
111 ;;; in fact generating similar objects.
112 (assert (equal (array-dimensions
113                 (read-from-string
114                  (with-output-to-string (s)
115                    (let ((*print-readably* t))
116                      (print (make-array '(1 2 0)) s)))))
117                '(1 2 0)))
118
119 (dolist (array (list (make-array '(1 0 1))
120                      (make-array 0 :element-type nil)
121                      (make-array 1 :element-type 'base-char)
122                      (make-array 1 :element-type 'character)))
123   (assert (multiple-value-bind (result error)
124               (ignore-errors (read-from-string
125                               (with-output-to-string (s)
126                                 (let ((*print-readably* t))
127                                   (print array s)))))
128             ;; it might not be readably-printable
129             (or (typep error 'print-not-readable)
130                 (and
131                  ;; or else it had better have the same dimensions
132                  (equal (array-dimensions result) (array-dimensions array))
133                  ;; and the same element-type
134                  (equal (array-element-type result) (array-element-type array)))))))
135
136 ;;; before 0.8.0.66 it signalled UNBOUND-VARIABLE
137 (write #(1 2 3) :pretty nil :readably t)
138
139 ;;; another UNBOUND-VARIABLE, this time due to a bug in FORMATTER
140 ;;; expanders.
141 (funcall (formatter "~@<~A~:*~A~:>") nil 3)
142
143 ;;; the PPC floating point backend was at one point sufficiently
144 ;;; broken that this looped infinitely or caused segmentation
145 ;;; violations through stack corruption.
146 (print 0.0001)
147
148 ;;; In sbcl-0.8.7, the ~W format directive interpreter implemented the
149 ;;; sense of the colon and at-sign modifiers exactly backwards.
150 ;;;
151 ;;; (Yes, the test for this *is* substantially hairier than the fix;
152 ;;; wanna make something of it?)
153 (cl:in-package :cl-user)
154 (defstruct wexerciser-0-8-7)
155 (defun wexercise-0-8-7-interpreted (wformat)
156   (format t wformat (make-wexerciser-0-8-7)))
157 (defmacro define-compiled-wexercise-0-8-7 (wexercise wformat)
158   `(defun ,wexercise ()
159     (declare (optimize (speed 3) (space 1)))
160     (format t ,wformat (make-wexerciser-0-8-7))
161     (values)))
162 (define-compiled-wexercise-0-8-7 wexercise-0-8-7-compiled-without-atsign "~W")
163 (define-compiled-wexercise-0-8-7 wexercise-0-8-7-compiled-with-atsign "~@W")
164 (defmethod print-object :before ((wexerciser-0-8-7 wexerciser-0-8-7) stream)
165   (unless (and *print-level* *print-length*)
166     (error "gotcha coming")))
167 (let ((*print-level* 11)
168       (*print-length* 12))
169   (wexercise-0-8-7-interpreted "~W")
170   (wexercise-0-8-7-compiled-without-atsign))
171 (remove-method #'print-object
172                (find-method #'print-object
173                             '(:before)
174                             (mapcar #'find-class '(wexerciser-0-8-7 t))))
175 (defmethod print-object :before ((wexerciser-0-8-7 wexerciser-0-8-7) stream)
176   (when (or *print-level* *print-length*)
177     (error "gotcha going")))
178 (let ((*print-level* 11)
179       (*print-length* 12))
180   (wexercise-0-8-7-interpreted "~@W")
181   (wexercise-0-8-7-compiled-with-atsign))
182 \f
183 ;;; WRITE-TO-STRING was erroneously DEFKNOWNed as FOLDABLE
184 ;;;
185 ;;; This bug from PFD
186 (defpackage "SCRATCH-WRITE-TO-STRING" (:use))
187 (with-standard-io-syntax
188   (let* ((*package* (find-package "SCRATCH-WRITE-TO-STRING"))
189          (answer (write-to-string 'scratch-write-to-string::x :readably nil)))
190     (assert (string= answer "X"))))
191 ;;; and a couple from Bruno Haible
192 (defun my-pprint-reverse (out list)
193   (write-char #\( out)
194   (when (setq list (reverse list))
195     (loop
196      (write (pop list) :stream out)
197      (when (endp list) (return))
198      (write-char #\Space out)))
199   (write-char #\) out))
200 (with-standard-io-syntax
201   (let ((*print-pprint-dispatch* (copy-pprint-dispatch)))
202     (set-pprint-dispatch '(cons (member foo)) 'my-pprint-reverse 0)
203     (let ((answer (write-to-string '(foo bar :boo 1) :pretty t :escape t)))
204       (assert (string= answer "(1 :BOO BAR FOO)")))))
205 (defun my-pprint-logical (out list)
206   (pprint-logical-block (out list :prefix "(" :suffix ")")
207     (when list
208       (loop
209        (write-char #\? out)
210        (write (pprint-pop) :stream out)
211        (write-char #\? out)
212        (pprint-exit-if-list-exhausted)
213        (write-char #\Space out)))))
214 (with-standard-io-syntax
215   (let ((*print-pprint-dispatch* (copy-pprint-dispatch)))
216     (set-pprint-dispatch '(cons (member bar)) 'my-pprint-logical 0)
217     (let ((answer (write-to-string '(bar foo :boo 1) :pretty t :escape t)))
218       (assert (string= answer "(?BAR? ?FOO? ?:BOO? ?1?)")))))
219
220 ;;; FORMAT string compile-time checker failure, reported by Thomas
221 ;;; F. Burdick
222 (multiple-value-bind (f w-p f-p)
223     (compile nil '(lambda () (format nil "~{")))
224   (assert (and w-p f-p))
225   (assert (nth-value 1 (ignore-errors (funcall f)))))
226
227 ;;; floating point print/read consistency
228 (let ((x (/ -9.349640046247849d-21 -9.381494249123696d-11)))
229   (let ((y (read-from-string (write-to-string x :readably t))))
230     (assert (eql x y))))
231
232 (let ((x1 (float -5496527/100000000000000000))
233       (x2 (float -54965272/1000000000000000000)))
234   (assert (or (equal (multiple-value-list (integer-decode-float x1))
235                      (multiple-value-list (integer-decode-float x2)))
236               (string/= (prin1-to-string x1) (prin1-to-string x2)))))
237
238 ;;; readable printing of arrays with *print-radix* t
239 (let ((*print-radix* t)
240       (*print-readably* t)
241       (*print-pretty* nil))
242   (let ((output (with-output-to-string (s)
243                   (write #2a((t t) (nil nil)) :stream s))))
244     (assert (equalp (read-from-string output) #2a((t t) (nil nil))))))
245
246 ;;; NIL parameters to "interpreted" FORMAT directives
247 (assert (string= (format nil "~v%" nil) (string #\Newline)))
248
249 ;;; PRINC-TO-STRING should bind print-readably
250 (let ((*print-readably* t))
251   (assert (string= (princ-to-string #\7)
252                    (write-to-string #\7 :escape nil :readably nil))))
253
254 ;;; in FORMAT, ~^ inside ~:{ should go to the next case, not break
255 ;;; iteration, even if one argument is just a one-element list.
256 (assert (string= (format nil "~:{~A~^~}" '((A) (C D))) "AC"))
257
258 ;;; errors should be raised if pprint and justification are mixed
259 ;;; injudiciously...
260 (dolist (x (list "~<~:;~>~_" "~<~:;~>~I" "~<~:;~>~W"
261                  "~<~:;~>~:T" "~<~:;~>~<~:>" "~_~<~:;~>"
262                  "~I~<~:;~>" "~W~<~:;~>" "~:T~<~:;~>" "~<~:>~<~:;~>"))
263   (assert (raises-error? (format nil x nil)))
264   (assert (raises-error? (format nil (eval `(formatter ,x)) nil))))
265 ;;; ...but not in judicious cases.
266 (dolist (x (list "~<~;~>~_" "~<~;~>~I" "~<~;~>~W"
267                  "~<~;~>~:T" "~<~;~>~<~>" "~_~<~;~>"
268                  "~I~<~;~>" "~W~<~;~>" "~:T~<~;~>" "~<~>~<~;~>"
269                  "~<~:;~>~T" "~T~<~:;~>"))
270   (assert (format nil x nil))
271   (assert (format nil (eval `(formatter ,x)) nil)))
272
273 ;;; bug 350: bignum printing so memory-hungry that heap runs out
274 ;;; -- just don't stall here forever on a slow box
275 (with-test (:name :bug-350)
276   (handler-case
277       (with-timeout 10
278         (print (ash 1 1000000)))
279     (timeout ()
280       (print 'timeout!))))
281
282 ;;; bug 371: bignum print/read inconsistency
283 (defvar *bug-371* -7043009959286724629649270926654940933664689003233793014518979272497911394287216967075767325693021717277238746020477538876750544587281879084559996466844417586093291189295867052594478662802691926547232838591510540917276694295393715934079679531035912244103731582711556740654671309980075069010778644542022/670550434139267031632063192770201289106737062379324644110801846820471752716238484923370056920388400273070254958650831435834503195629325418985020030706879602898158806736813101434594805676212779217311897830937606064579213895527844045511878668289820732425014254579493444623868748969110751636786165152601)
284 (let ((*print-base* 5)
285       (*read-base* 5)
286       (*print-radix* nil))
287   (assert (= *bug-371* (read-from-string (prin1-to-string *bug-371*)))))
288
289 ;;; a spot of random-testing for rational printing
290 (defvar *seed-state* (make-random-state))
291 (print *seed-state*) ; so that we can reproduce errors
292 (let ((seed (make-random-state *seed-state*)))
293   (loop repeat 42
294      do (let ((n (random (ash 1 1000) seed))
295               (d (random (ash 1 1000) seed)))
296           (when (zerop (random 2 seed))
297             (setf n (- n)))
298           (let ((r (/ n d)))
299             (loop for base from 2 to 36
300                do (let ((*print-base* base)
301                         (*read-base* base)
302                         (*print-radix* nil))
303                     (assert (= r (read-from-string (prin1-to-string r))))
304                     (if (= 36 base)
305                         (decf *read-base*)
306                         (incf *read-base*))
307                     (assert (not (eql r (read-from-string (prin1-to-string r)))))
308                     (let ((*print-radix* t))
309                       (assert (= r (read-from-string
310                                     (princ-to-string r)))))))))
311        (write-char #\.)
312        (finish-output)))
313
314 ;;;; Bugs, found by PFD
315 ;;; NIL parameter for ~^ means `not supplied'
316 (loop for (format arg result) in
317       '(("~:{~D~v^~D~}" ((3 1 4) (1 0 2) (7 nil) (5 nil 6)) "341756")
318         ("~:{~1,2,v^~A~}" ((nil 0) (3 1) (0 2)) "02"))
319       do (assert (string= (funcall #'format nil format arg) result))
320       do (assert (string= (with-output-to-string (s)
321                             (funcall (eval `(formatter ,format)) s arg))
322                           result)))
323
324 ;;; NIL first parameter for ~R is equivalent to no parameter.
325 (assert (string= (format nil "~VR" nil 5) "five"))
326 (assert (string= (format nil (formatter "~VR") nil 6) "six"))
327
328 ;;; CSR inserted a bug into Burger & Dybvig's float printer.  Caught
329 ;;; by Raymond Toy
330 (assert (string= (format nil "~E" 1d23) "1.d+23"))
331
332 ;;; Fixed-format bugs from CLISP's test suite (reported by Bruno
333 ;;; Haible, bug 317)
334 (assert (string= (format nil "~1F" 10) "10."))
335 (assert (string= (format nil "~0F" 10) "10."))
336 (assert (string= (format nil "~2F" 1234567.1) "1234567."))
337
338 ;;; here's one that seems to fail most places.  I think this is right,
339 ;;; and most of the other answers I've seen are definitely wrong.
340 (assert (string= (format nil "~G" 1d23) "100000000000000000000000.    "))
341
342 ;;; Adam Warner's test case
343 (assert (string= (format nil "~@F" 1.23) "+1.23"))
344
345
346 ;;; New (2005-11-08, also known as CSR House day) float format test
347 ;;; cases.  Simon Alexander, Raymond Toy, and others
348 (assert (string= (format nil "~9,4,,-7E" pi) ".00000003d+8"))
349 (assert (string= (format nil "~9,4,,-5E" pi) ".000003d+6"))
350 (assert (string= (format nil "~5,4,,7E" pi) "3141600.d-6"))
351 (assert (string= (format nil "~11,4,,3E" pi) "  314.16d-2"))
352 (assert (string= (format nil "~11,4,,5E" pi) "  31416.d-4"))
353 (assert (string= (format nil "~11,4,,0E" pi) "  0.3142d+1"))
354 (assert (string= (format nil "~9,,,-1E" pi) ".03142d+2"))
355 (assert (string= (format nil "~,,,-2E" pi) "0.003141592653589793d+3"))
356 (assert (string= (format nil "~,,,2E" pi) "31.41592653589793d-1"))
357 (assert (string= (format nil "~E" pi) "3.141592653589793d+0"))
358 (assert (string= (format nil "~9,5,,-1E" pi) ".03142d+2"))
359 (assert (string= (format nil "~11,5,,-1E" pi) " 0.03142d+2"))
360 (assert (string= (format nil "~G" pi) "3.141592653589793    "))
361 (assert (string= (format nil "~9,5G" pi) "3.1416    "))
362 (assert (string= (format nil "|~13,6,2,7E|" pi) "| 3141593.d-06|"))
363 (assert (string= (format nil "~9,3,2,0,'%E" pi) "0.314d+01"))
364 (assert (string= (format nil "~9,0,6f" pi) " 3141593."))
365 (assert (string= (format nil "~6,2,1,'*F" pi) " 31.42"))
366 (assert (string= (format nil "~6,2,1,'*F" (* 100 pi)) "******"))
367 (assert (string= (format nil "~9,3,2,-2,'%@E" pi) "+.003d+03"))
368 (assert (string= (format nil "~10,3,2,-2,'%@E" pi) "+0.003d+03"))
369 (assert (string= (format nil "~15,3,2,-2,'%,'=@E" pi) "=====+0.003d+03"))
370 (assert (string= (format nil "~9,3,2,-2,'%E" pi) "0.003d+03"))
371 (assert (string= (format nil "~8,3,2,-2,'%@E" pi) "%%%%%%%%"))
372
373 (assert (string= (format nil "~g" 1e0) "1.    "))
374 (assert (string= (format nil "~g" 1.2d40) "12000000000000000000000000000000000000000.    "))
375
376 (assert (string= (format nil "~e" 0) "0.0e+0"))
377 (assert (string= (format nil "~e" 0d0) "0.0d+0"))
378 (assert (string= (format nil "~9,,4e" 0d0) "0.0d+0000"))
379
380 (let ((table (make-hash-table)))
381   (setf (gethash 1 table) t)
382   (assert
383    (raises-error? (with-standard-io-syntax
384                     (let ((*read-eval* nil)
385                           (*print-readably* t))
386                       (with-output-to-string (*standard-output*)
387                         (prin1 table))))
388                   print-not-readable)))
389
390 ;; Test that we can print characters readably regardless of the external format
391 ;; of the stream.
392
393 (defun test-readable-character (character external-format)
394   (let ((file "print.impure.tmp"))
395     (unwind-protect
396          (progn
397            (with-open-file (stream file
398                                    :direction :output
399                                    :external-format external-format
400                                    :if-exists :supersede)
401              (write character :stream stream :readably t))
402            (with-open-file (stream file
403                                    :direction :input
404                                    :external-format external-format
405                                    :if-does-not-exist :error)
406              (assert (char= (read stream) character))))
407       (ignore-errors
408         (delete-file file)))))
409
410 (with-test (:name (:print-readable :character :utf-8) :skipped-on '(not :sb-unicode))
411   (test-readable-character (code-char #xfffe) :utf-8))
412
413 (with-test (:name (:print-readable :character :iso-8859-1) :skipped-on '(not :sb-unicode))
414   (test-readable-character (code-char #xfffe) :iso-8859-1))
415
416 (assert (string= (eval '(format nil "~:C" #\a)) "a"))
417 (assert (string= (format nil (formatter "~:C") #\a) "a"))
418
419 ;;; This used to trigger an AVER instead.
420 (assert (raises-error? (eval '(formatter "~>")) sb-format:format-error))
421 (assert (raises-error? (eval '(format t "~>")) sb-format:format-error))
422
423 ;;; readably printing hash-tables, check for circularity
424 (let ((x (cons 1 2))
425       (h (make-hash-table))
426       (*print-readably* t)
427       (*print-circle* t)
428       (*read-eval* t))
429   (setf (gethash x h) h)
430   (destructuring-bind (x2 . h2) (read-from-string (write-to-string (cons x h)))
431     (assert (equal x x2))
432     (assert (eq h2 (gethash x2 h2)))))
433
434 ;;; an off-by-one error in the ~R format directive until 1.0.15.20
435 ;;; prevented printing cardinals and ordinals between (expt 10 63) and
436 ;;; (1- (expt 10 66))
437 (assert (string= (format nil "~R" (expt 10 63)) "one vigintillion"))
438 (assert (string= (format nil "~:R" (expt 10 63)) "one vigintillionth"))
439
440 ;;; too-clever cacheing for PRINT-OBJECT resulted in a bogus method
441 ;;; for printing RESTART objects.  Check also CONTROL-STACK-EXHAUSTED
442 ;;; and HEAP-EXHAUSTED-ERROR.
443 (let ((result (with-output-to-string (*standard-output*)
444                 (princ (find-restart 'abort)))))
445   (assert (string/= result "#<" :end1 2)))
446 (let ((result (with-output-to-string (*standard-output*)
447                 (princ (make-condition 'sb-kernel::control-stack-exhausted)))))
448   (assert (string/= result "#<" :end1 2)))
449 (let ((result (with-output-to-string (*standard-output*)
450                 (princ (make-condition 'sb-kernel::heap-exhausted-error)))))
451   (assert (string/= result "#<" :end1 2)))
452
453 (with-test (:name (:with-standard-io-syntax :bind-print-pprint-dispatch))
454   (let ((*print-pprint-dispatch* (copy-pprint-dispatch nil)))
455     (set-pprint-dispatch 'symbol #'(lambda (stream obj)
456                                      (declare (ignore obj))
457                                      (write-string "FOO" stream)))
458     (with-standard-io-syntax
459       (let ((*print-pretty* t))
460         (assert (string= (princ-to-string 'bar) "BAR"))))))
461
462 ;;; bug-lp#488979
463
464 (defclass a-class-name () ())
465
466 (assert (find #\Newline
467               (let ((*print-pretty* t)
468                     (*print-right-margin* 10))
469                 (format nil "~A" (make-instance 'a-class-name)))
470               :test #'char=))
471
472 (assert (not (find #\Newline
473                    (let ((*print-pretty* nil)
474                          (*print-right-margin* 10))
475                      (format nil "~A" (make-instance 'a-class-name)))
476                    :test #'char=)))
477
478 ;;; The PRINT-OBJECT method for RANDOM-STATE used to have a bogus
479 ;;; dimension argument for MAKE-ARRAY.
480 (with-test (:name :print-random-state)
481   (assert (equalp *random-state*
482                   (read-from-string
483                    (write-to-string *random-state*)))))
484
485 (with-test (:name :write-return-value)
486   (assert (= 123 (funcall (compile nil (lambda ()
487                                          (write 123)))))))
488
489 (with-test (:name :write/write-to-string-compiler-macro-lp/598374+581564)
490   (let ((test (compile nil
491                        `(lambda (object &optional output-stream)
492                           (write object
493                                  :stream output-stream)))))
494     (assert (equal "(HELLO WORLD)"
495                    (with-output-to-string (*standard-output*)
496                      (let ((list '(hello world)))
497                        (assert (eq list (funcall test list)))))))
498     (assert (equal "12"
499                    (with-output-to-string (*standard-output*)
500                      (assert (eql 12 (funcall test 12)))))))
501   (let ((test (compile nil
502                        `(lambda ()
503                           (let ((*print-length* 42))
504                             (write-to-string *print-length* :length nil))))))
505     (assert (equal "42" (funcall test)))))
506
507 (with-test (:name (:format :compile-literal-dest-string))
508   (assert (eq :warned
509               (handler-case
510                   (compile nil
511                            `(lambda (x) (format "~A" x)))
512                 ((and warning (not style-warning)) ()
513                   :warned)))))
514
515 (with-test (:name :bug-308961)
516   (assert (string= (format nil "~4,1F" 0.001) " 0.0"))
517   (assert (string= (format nil "~4,1@F" 0.001) "+0.0"))
518   (assert (string= (format nil "~E" 0.01) "1.e-2"))
519   (assert (string= (format nil "~G" 0.01) "1.00e-2")))
520
521 (with-test (:name (:fp-print-read-consistency single-float))
522   (let ((*random-state* (make-random-state t))
523         (oops))
524     (loop for f = most-positive-single-float then (/ f 2.0)
525           while (> f 0.0)
526           do (loop repeat 10
527                    for fr = (random f)
528                    do (unless (eql fr (read-from-string (prin1-to-string fr)))
529                         (push fr oops)
530                         (return))))
531     (loop for f = most-negative-single-float then (/ f 2.0)
532           while (< f -0.0)
533           do (loop repeat 10
534                    for fr = (- (random (- f)))
535                    do (unless (eql fr (read-from-string (prin1-to-string fr)))
536                         (push fr oops)
537                         (return))))
538     (when oops
539       (error "FP print-read inconsistencies:~%~:{  ~S => ~S~%~}"
540              (mapcar (lambda (f)
541                        (list f (read-from-string (prin1-to-string f))))
542                      oops)))))
543
544 (with-test (:name (:fp-print-read-consistency double-float))
545   (let ((*random-state* (make-random-state t))
546         (oops))
547     ;; FIXME skipping denormalized floats due to bug 793774.
548     (loop for f = most-positive-double-float then (/ f 2d0)
549           while (> f 0d0)
550           do (loop repeat 10
551                    for fr = (random f)
552                    do (unless (float-denormalized-p fr)
553                         (unless (eql fr (read-from-string (prin1-to-string fr)))
554                           (push fr oops)
555                           (return)))))
556     (loop for f = most-negative-double-float then (/ f 2d0)
557           while (< f -0d0)
558           do (loop repeat 10
559                    for fr = (- (random (- f)))
560                    do (unless (float-denormalized-p fr)
561                         (unless (eql fr (read-from-string (prin1-to-string fr)))
562                           (push fr oops)
563                           (return)))))
564     (when oops
565       (error "FP print-read inconsistencies:~%~:{  ~S => ~S~%~}"
566              (mapcar (lambda (f)
567                        (list f (read-from-string (prin1-to-string f))))
568                      oops)))))
569
570 (with-test (:name :bug-811386)
571   (assert (equal "   0.00" (format nil "~7,2,-2f" 0)))
572   (assert (equal "   0.00" (format nil "~7,2,2f" 0)))
573   (assert (equal "   0.01" (format nil "~7,2,-2f" 1)))
574   (assert (equal " 100.00" (format nil "~7,2,2f" 1)))
575   (assert (equal "   0.00" (format nil "~7,2,-2f" 0.1)))
576   (assert (equal "  10.00" (format nil "~7,2,2f" 0.1)))
577   (assert (equal "   0.01" (format nil "~7,2,-2f" 0.5))))
578
579 (with-test (:name :bug-867684)
580   (assert (equal "ab" (format nil "a~0&b"))))
581
582 (with-test (:name :print-unreadably-function)
583   (assert (equal "\"foo\""
584                  (handler-bind ((print-not-readable #'sb-ext:print-unreadably))
585                    (write-to-string (coerce "foo" 'base-string) :readably t)))))
586
587 (with-test (:name :printing-specialized-arrays-readably)
588   (let ((*read-eval* t)
589         (dimss (loop repeat 10
590                      collect (loop repeat (1+ (random 3))
591                                    collect (1+ (random 10)))))
592         (props sb-vm::*specialized-array-element-type-properties*))
593     (labels ((random-elt (type)
594                (case type
595                  (base-char
596                   (code-char (random 128)))
597                  (character
598                   (code-char (random char-code-limit)))
599                  (single-float
600                   (+ least-positive-normalized-single-float
601                      (random most-positive-single-float)))
602                  (double-float
603                   (+ least-positive-normalized-double-float
604                          (random most-positive-double-float)))
605                  (bit
606                   (random 2))
607                  (fixnum
608                   (random most-positive-fixnum))
609                  ((t)
610                   t)
611                  (otherwise
612                   (destructuring-bind (type x) type
613                     (ecase type
614                       (unsigned-byte
615                        (random (1- (expt 2 x))))
616                       (signed-byte
617                        (- (random (expt 2 (1- x)))))
618                       (complex
619                        (complex (random-elt x) (random-elt x)))))))))
620       (dotimes (i (length props))
621         (let ((et (sb-vm::saetp-specifier (aref props i))))
622           (when et
623             (when (eq 'base-char et)
624               ;; base-strings not included in the #. printing.
625               (go :next))
626             (dolist (dims dimss)
627               (let ((a (make-array dims :element-type et)))
628                 (assert (equal et (array-element-type a)))
629                 (dotimes (i (array-total-size a))
630                   (setf (row-major-aref a i) (random-elt et)))
631                 (let ((copy (read-from-string (write-to-string a :readably t))))
632                   (assert (equal dims (array-dimensions copy)))
633                   (assert (equal et (array-element-type copy)))
634                   (assert (equal (array-total-size a) (array-total-size copy)))
635                   (dotimes (i (array-total-size a))
636                     (assert (equal (row-major-aref a i) (row-major-aref copy i)))))))))
637         :next))))
638
639 (with-test (:name (:format :negative-colinc-and-mincol))
640   (assert (raises-error? (format nil "~-2a" 1)))
641   (assert (raises-error? (format nil "~,0a" 1))))
642
643 (with-test (:name :bug-905817)
644   ;; The bug manifests itself in an endless loop in FORMAT.
645   ;; Correct behaviour is to signal an error.
646   (handler-case
647       (with-timeout 5
648         (assert (raises-error? (format nil "e~8,0s" 12395))))
649     (timeout ()
650       (error "Endless loop in FORMAT"))))
651
652 (with-test (:name :format-type-check)
653   (assert (equal "1/10" (format nil "~2r" 1/2)))
654   (assert (raises-error? (format nil "~r" 1.32) sb-format:format-error))
655   (assert (raises-error? (format nil "~c" 1.32) sb-format:format-error))
656   (assert (equal "1/10" (eval '(format nil "~2r" 1/2))))
657   (assert (raises-error? (eval '(format nil "~r" 1.32)) sb-format:format-error))
658   (assert (raises-error? (eval '(format nil "~c" 1.32)) sb-format:format-error)))
659
660 ;;; success