0.8.16.16:
[sbcl.git] / src / code / target-format.lisp
1 ;;;; functions to implement FORMAT and FORMATTER
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!FORMAT")
13 \f
14 ;;;; FORMAT
15
16 (defun format (destination control-string &rest format-arguments)
17   #!+sb-doc
18   "Provides various facilities for formatting output.
19   CONTROL-STRING contains a string to be output, possibly with embedded
20   directives, which are flagged with the escape character \"~\". Directives
21   generally expand into additional text to be output, usually consuming one
22   or more of the FORMAT-ARGUMENTS in the process. A few useful directives
23   are:
24         ~A or ~nA   Prints one argument as if by PRINC
25         ~S or ~nS   Prints one argument as if by PRIN1
26         ~D or ~nD   Prints one argument as a decimal integer
27         ~%          Does a TERPRI
28         ~&          Does a FRESH-LINE
29   where n is the width of the field in which the object is printed.
30
31   DESTINATION controls where the result will go. If DESTINATION is T, then
32   the output is sent to the standard output stream. If it is NIL, then the
33   output is returned in a string as the value of the call. Otherwise,
34   DESTINATION must be a stream to which the output will be sent.
35
36   Example:   (FORMAT NIL \"The answer is ~D.\" 10) => \"The answer is 10.\"
37
38   FORMAT has many additional capabilities not described here. Consult the
39   manual for details."
40   (etypecase destination
41     (null
42      (with-output-to-string (stream)
43        (%format stream control-string format-arguments)))
44     (string
45      (with-output-to-string (stream destination)
46        (%format stream control-string format-arguments)))
47     ((member t)
48      (%format *standard-output* control-string format-arguments)
49      nil)
50     (stream
51      (%format destination control-string format-arguments)
52      nil)))
53
54 (defun %format (stream string-or-fun orig-args &optional (args orig-args))
55   (if (functionp string-or-fun)
56       (apply string-or-fun stream args)
57       (catch 'up-and-out
58         (let* ((string (etypecase string-or-fun
59                          (simple-string
60                           string-or-fun)
61                          (string
62                           (coerce string-or-fun 'simple-string))))
63                (*default-format-error-control-string* string)
64                (*logical-block-popper* nil))
65           (interpret-directive-list stream (tokenize-control-string string)
66                                     orig-args args)))))
67
68 (defun interpret-directive-list (stream directives orig-args args)
69   (if directives
70       (let ((directive (car directives)))
71         (etypecase directive
72           (simple-string
73            (write-string directive stream)
74            (interpret-directive-list stream (cdr directives) orig-args args))
75           (format-directive
76            (multiple-value-bind (new-directives new-args)
77                (let* ((character (format-directive-character directive))
78                       (function
79                        (typecase character
80                          (base-char 
81                        (svref *format-directive-interpreters*
82                               (char-code character)))
83                          (character nil)))
84                       (*default-format-error-offset*
85                        (1- (format-directive-end directive))))
86                  (unless function
87                    (error 'format-error
88                           :complaint "unknown format directive ~@[(character: ~A)~]"
89                           :args (list (char-name character))))
90                  (multiple-value-bind (new-directives new-args)
91                      (funcall function stream directive
92                               (cdr directives) orig-args args)
93                    (values new-directives new-args)))
94              (interpret-directive-list stream new-directives
95                                        orig-args new-args)))))
96       args))
97 \f
98 ;;;; FORMAT directive definition macros and runtime support
99
100 (eval-when (:compile-toplevel :execute)
101
102 ;;; This macro is used to extract the next argument from the current arg list.
103 ;;; This is the version used by format directive interpreters.
104 (sb!xc:defmacro next-arg (&optional offset)
105   `(progn
106      (when (null args)
107        (error 'format-error
108               :complaint "no more arguments"
109               ,@(when offset
110                   `(:offset ,offset))))
111      (when *logical-block-popper*
112        (funcall *logical-block-popper*))
113      (pop args)))
114
115 (sb!xc:defmacro def-complex-format-interpreter (char lambda-list &body body)
116   (let ((defun-name
117             (intern (format nil
118                             "~:@(~:C~)-FORMAT-DIRECTIVE-INTERPRETER"
119                             char)))
120         (directive (gensym))
121         (directives (if lambda-list (car (last lambda-list)) (gensym))))
122     `(progn
123        (defun ,defun-name (stream ,directive ,directives orig-args args)
124          (declare (ignorable stream orig-args args))
125          ,@(if lambda-list
126                `((let ,(mapcar (lambda (var)
127                                  `(,var
128                                    (,(symbolicate "FORMAT-DIRECTIVE-" var)
129                                     ,directive)))
130                                (butlast lambda-list))
131                    (values (progn ,@body) args)))
132                `((declare (ignore ,directive ,directives))
133                  ,@body)))
134        (%set-format-directive-interpreter ,char #',defun-name))))
135
136 (sb!xc:defmacro def-format-interpreter (char lambda-list &body body)
137   (let ((directives (gensym)))
138     `(def-complex-format-interpreter ,char (,@lambda-list ,directives)
139        ,@body
140        ,directives)))
141
142 (sb!xc:defmacro interpret-bind-defaults (specs params &body body)
143   (once-only ((params params))
144     (collect ((bindings))
145       (dolist (spec specs)
146         (destructuring-bind (var default) spec
147           (bindings `(,var (let* ((param-and-offset (pop ,params))
148                                   (offset (car param-and-offset))
149                                   (param (cdr param-and-offset)))
150                              (case param
151                                (:arg (or (next-arg offset) ,default))
152                                (:remaining (length args))
153                                ((nil) ,default)
154                                (t param)))))))
155       `(let* ,(bindings)
156          (when ,params
157            (error 'format-error
158                   :complaint
159                   "too many parameters, expected no more than ~W"
160                   :args (list ,(length specs))
161                   :offset (caar ,params)))
162          ,@body))))
163
164 ) ; EVAL-WHEN
165 \f
166 ;;;; format interpreters and support functions for simple output
167
168 (defun format-write-field (stream string mincol colinc minpad padchar padleft)
169   (unless padleft
170     (write-string string stream))
171   (dotimes (i minpad)
172     (write-char padchar stream))
173   ;; As of sbcl-0.6.12.34, we could end up here when someone tries to
174   ;; print e.g. (FORMAT T "~F" "NOTFLOAT"), in which case ANSI says
175   ;; we're supposed to soldier on bravely, and so we have to deal with
176   ;; the unsupplied-MINCOL-and-COLINC case without blowing up.
177   (when (and mincol colinc)
178     (do ((chars (+ (length string) (max minpad 0)) (+ chars colinc)))
179         ((>= chars mincol))
180       (dotimes (i colinc)
181         (write-char padchar stream))))
182   (when padleft
183     (write-string string stream)))
184
185 (defun format-princ (stream arg colonp atsignp mincol colinc minpad padchar)
186   (format-write-field stream
187                       (if (or arg (not colonp))
188                           (princ-to-string arg)
189                           "()")
190                       mincol colinc minpad padchar atsignp))
191
192 (def-format-interpreter #\A (colonp atsignp params)
193   (if params
194       (interpret-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
195                                 (padchar #\space))
196                      params
197         (format-princ stream (next-arg) colonp atsignp
198                       mincol colinc minpad padchar))
199       (princ (if colonp (or (next-arg) "()") (next-arg)) stream)))
200
201 (defun format-prin1 (stream arg colonp atsignp mincol colinc minpad padchar)
202   (format-write-field stream
203                       (if (or arg (not colonp))
204                           (prin1-to-string arg)
205                           "()")
206                       mincol colinc minpad padchar atsignp))
207
208 (def-format-interpreter #\S (colonp atsignp params)
209   (cond (params
210          (interpret-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
211                                    (padchar #\space))
212                         params
213            (format-prin1 stream (next-arg) colonp atsignp
214                          mincol colinc minpad padchar)))
215         (colonp
216          (let ((arg (next-arg)))
217            (if arg
218                (prin1 arg stream)
219                (princ "()" stream))))
220         (t
221          (prin1 (next-arg) stream))))
222
223 (def-format-interpreter #\C (colonp atsignp params)
224   (interpret-bind-defaults () params
225     (if colonp
226         (format-print-named-character (next-arg) stream)
227         (if atsignp
228             (prin1 (next-arg) stream)
229             (write-char (next-arg) stream)))))
230
231 (defun format-print-named-character (char stream)
232   (let* ((name (char-name char)))
233     (cond (name
234            (write-string (string-capitalize name) stream))
235           (t
236            (write-char char stream)))))
237
238 (def-format-interpreter #\W (colonp atsignp params)
239   (interpret-bind-defaults () params
240     (let ((*print-pretty* (or colonp *print-pretty*))
241           (*print-level* (unless atsignp *print-level*))
242           (*print-length* (unless atsignp *print-length*)))
243       (output-object (next-arg) stream))))
244 \f
245 ;;;; format interpreters and support functions for integer output
246
247 ;;; FORMAT-PRINT-NUMBER does most of the work for the numeric printing
248 ;;; directives. The parameters are interpreted as defined for ~D.
249 (defun format-print-integer (stream number print-commas-p print-sign-p
250                              radix mincol padchar commachar commainterval)
251   (let ((*print-base* radix)
252         (*print-radix* nil))
253     (if (integerp number)
254         (let* ((text (princ-to-string (abs number)))
255                (commaed (if print-commas-p
256                             (format-add-commas text commachar commainterval)
257                             text))
258                (signed (cond ((minusp number)
259                               (concatenate 'string "-" commaed))
260                              (print-sign-p
261                               (concatenate 'string "+" commaed))
262                              (t commaed))))
263           ;; colinc = 1, minpad = 0, padleft = t
264           (format-write-field stream signed mincol 1 0 padchar t))
265         (princ number stream))))
266
267 (defun format-add-commas (string commachar commainterval)
268   (let ((length (length string)))
269     (multiple-value-bind (commas extra) (truncate (1- length) commainterval)
270       (let ((new-string (make-string (+ length commas)))
271             (first-comma (1+ extra)))
272         (replace new-string string :end1 first-comma :end2 first-comma)
273         (do ((src first-comma (+ src commainterval))
274              (dst first-comma (+ dst commainterval 1)))
275             ((= src length))
276           (setf (schar new-string dst) commachar)
277           (replace new-string string :start1 (1+ dst)
278                    :start2 src :end2 (+ src commainterval)))
279         new-string))))
280
281 ;;; FIXME: This is only needed in this file, could be defined with
282 ;;; SB!XC:DEFMACRO inside EVAL-WHEN
283 (defmacro interpret-format-integer (base)
284   `(if (or colonp atsignp params)
285        (interpret-bind-defaults
286            ((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
287            params
288          (format-print-integer stream (next-arg) colonp atsignp ,base mincol
289                                padchar commachar commainterval))
290        (write (next-arg) :stream stream :base ,base :radix nil :escape nil)))
291
292 (def-format-interpreter #\D (colonp atsignp params)
293   (interpret-format-integer 10))
294
295 (def-format-interpreter #\B (colonp atsignp params)
296   (interpret-format-integer 2))
297
298 (def-format-interpreter #\O (colonp atsignp params)
299   (interpret-format-integer 8))
300
301 (def-format-interpreter #\X (colonp atsignp params)
302   (interpret-format-integer 16))
303
304 (def-format-interpreter #\R (colonp atsignp params)
305   (if params
306       (interpret-bind-defaults
307           ((base 10) (mincol 0) (padchar #\space) (commachar #\,)
308            (commainterval 3))
309           params
310         (format-print-integer stream (next-arg) colonp atsignp base mincol
311                               padchar commachar commainterval))
312       (if atsignp
313           (if colonp
314               (format-print-old-roman stream (next-arg))
315               (format-print-roman stream (next-arg)))
316           (if colonp
317               (format-print-ordinal stream (next-arg))
318               (format-print-cardinal stream (next-arg))))))
319
320 (defparameter *cardinal-ones*
321   #(nil "one" "two" "three" "four" "five" "six" "seven" "eight" "nine"))
322
323 (defparameter *cardinal-tens*
324   #(nil nil "twenty" "thirty" "forty"
325         "fifty" "sixty" "seventy" "eighty" "ninety"))
326
327 (defparameter *cardinal-teens*
328   #("ten" "eleven" "twelve" "thirteen" "fourteen"  ;;; RAD
329     "fifteen" "sixteen" "seventeen" "eighteen" "nineteen"))
330
331 (defparameter *cardinal-periods*
332   #("" " thousand" " million" " billion" " trillion" " quadrillion"
333     " quintillion" " sextillion" " septillion" " octillion" " nonillion"
334     " decillion" " undecillion" " duodecillion" " tredecillion"
335     " quattuordecillion" " quindecillion" " sexdecillion" " septendecillion"
336     " octodecillion" " novemdecillion" " vigintillion"))
337
338 (defparameter *ordinal-ones*
339   #(nil "first" "second" "third" "fourth"
340         "fifth" "sixth" "seventh" "eighth" "ninth"))
341
342 (defparameter *ordinal-tens*
343   #(nil "tenth" "twentieth" "thirtieth" "fortieth"
344         "fiftieth" "sixtieth" "seventieth" "eightieth" "ninetieth"))
345
346 (defun format-print-small-cardinal (stream n)
347   (multiple-value-bind (hundreds rem) (truncate n 100)
348     (when (plusp hundreds)
349       (write-string (svref *cardinal-ones* hundreds) stream)
350       (write-string " hundred" stream)
351       (when (plusp rem)
352         (write-char #\space stream)))
353     (when (plusp rem)
354       (multiple-value-bind (tens ones) (truncate rem 10)
355         (cond ((< 1 tens)
356               (write-string (svref *cardinal-tens* tens) stream)
357               (when (plusp ones)
358                 (write-char #\- stream)
359                 (write-string (svref *cardinal-ones* ones) stream)))
360              ((= tens 1)
361               (write-string (svref *cardinal-teens* ones) stream))
362              ((plusp ones)
363               (write-string (svref *cardinal-ones* ones) stream)))))))
364
365 (defun format-print-cardinal (stream n)
366   (cond ((minusp n)
367          (write-string "negative " stream)
368          (format-print-cardinal-aux stream (- n) 0 n))
369         ((zerop n)
370          (write-string "zero" stream))
371         (t
372          (format-print-cardinal-aux stream n 0 n))))
373
374 (defun format-print-cardinal-aux (stream n period err)
375   (multiple-value-bind (beyond here) (truncate n 1000)
376     (unless (<= period 20)
377       (error "number too large to print in English: ~:D" err))
378     (unless (zerop beyond)
379       (format-print-cardinal-aux stream beyond (1+ period) err))
380     (unless (zerop here)
381       (unless (zerop beyond)
382         (write-char #\space stream))
383       (format-print-small-cardinal stream here)
384       (write-string (svref *cardinal-periods* period) stream))))
385
386 (defun format-print-ordinal (stream n)
387   (when (minusp n)
388     (write-string "negative " stream))
389   (let ((number (abs n)))
390     (multiple-value-bind (top bot) (truncate number 100)
391       (unless (zerop top)
392         (format-print-cardinal stream (- number bot)))
393       (when (and (plusp top) (plusp bot))
394         (write-char #\space stream))
395       (multiple-value-bind (tens ones) (truncate bot 10)
396         (cond ((= bot 12) (write-string "twelfth" stream))
397               ((= tens 1)
398                (write-string (svref *cardinal-teens* ones) stream);;;RAD
399                (write-string "th" stream))
400               ((and (zerop tens) (plusp ones))
401                (write-string (svref *ordinal-ones* ones) stream))
402               ((and (zerop ones)(plusp tens))
403                (write-string (svref *ordinal-tens* tens) stream))
404               ((plusp bot)
405                (write-string (svref *cardinal-tens* tens) stream)
406                (write-char #\- stream)
407                (write-string (svref *ordinal-ones* ones) stream))
408               ((plusp number)
409                (write-string "th" stream))
410               (t
411                (write-string "zeroth" stream)))))))
412
413 ;;; Print Roman numerals
414
415 (defun format-print-old-roman (stream n)
416   (unless (< 0 n 5000)
417     (error "Number too large to print in old Roman numerals: ~:D" n))
418   (do ((char-list '(#\D #\C #\L #\X #\V #\I) (cdr char-list))
419        (val-list '(500 100 50 10 5 1) (cdr val-list))
420        (cur-char #\M (car char-list))
421        (cur-val 1000 (car val-list))
422        (start n (do ((i start (progn
423                                 (write-char cur-char stream)
424                                 (- i cur-val))))
425                     ((< i cur-val) i))))
426       ((zerop start))))
427
428 (defun format-print-roman (stream n)
429   (unless (< 0 n 4000)
430     (error "Number too large to print in Roman numerals: ~:D" n))
431   (do ((char-list '(#\D #\C #\L #\X #\V #\I) (cdr char-list))
432        (val-list '(500 100 50 10 5 1) (cdr val-list))
433        (sub-chars '(#\C #\X #\X #\I #\I) (cdr sub-chars))
434        (sub-val '(100 10 10 1 1 0) (cdr sub-val))
435        (cur-char #\M (car char-list))
436        (cur-val 1000 (car val-list))
437        (cur-sub-char #\C (car sub-chars))
438        (cur-sub-val 100 (car sub-val))
439        (start n (do ((i start (progn
440                                 (write-char cur-char stream)
441                                 (- i cur-val))))
442                     ((< i cur-val)
443                      (cond ((<= (- cur-val cur-sub-val) i)
444                             (write-char cur-sub-char stream)
445                             (write-char cur-char stream)
446                             (- i (- cur-val cur-sub-val)))
447                            (t i))))))
448           ((zerop start))))
449 \f
450 ;;;; plural
451
452 (def-format-interpreter #\P (colonp atsignp params)
453   (interpret-bind-defaults () params
454     (let ((arg (if colonp
455                    (if (eq orig-args args)
456                        (error 'format-error
457                               :complaint "no previous argument")
458                        (do ((arg-ptr orig-args (cdr arg-ptr)))
459                            ((eq (cdr arg-ptr) args)
460                             (car arg-ptr))))
461                    (next-arg))))
462       (if atsignp
463           (write-string (if (eql arg 1) "y" "ies") stream)
464           (unless (eql arg 1) (write-char #\s stream))))))
465 \f
466 ;;;; format interpreters and support functions for floating point output
467
468 (defun decimal-string (n)
469   (write-to-string n :base 10 :radix nil :escape nil))
470
471 (def-format-interpreter #\F (colonp atsignp params)
472   (when colonp
473     (error 'format-error
474            :complaint
475            "cannot specify the colon modifier with this directive"))
476   (interpret-bind-defaults ((w nil) (d nil) (k nil) (ovf nil) (pad #\space))
477                            params
478     (format-fixed stream (next-arg) w d k ovf pad atsignp)))
479
480 (defun format-fixed (stream number w d k ovf pad atsign)
481   (if (numberp number)
482       (if (floatp number)
483           (format-fixed-aux stream number w d k ovf pad atsign)
484           (if (rationalp number)
485               (format-fixed-aux stream
486                                 (coerce number 'single-float)
487                                 w d k ovf pad atsign)
488               (format-write-field stream
489                                   (decimal-string number)
490                                   w 1 0 #\space t)))
491       (format-princ stream number nil nil w 1 0 pad)))
492
493 ;;; We return true if we overflowed, so that ~G can output the overflow char
494 ;;; instead of spaces.
495 (defun format-fixed-aux (stream number w d k ovf pad atsign)
496   (cond
497    ((or (not (or w d))
498         (and (floatp number)
499              (or (float-infinity-p number)
500                  (float-nan-p number))))
501     (prin1 number stream)
502     nil)
503    (t
504     (let ((spaceleft w))
505       (when (and w (or atsign (minusp number))) (decf spaceleft))
506       (multiple-value-bind (str len lpoint tpoint)
507           (sb!impl::flonum-to-string (abs number) spaceleft d k)
508         ;;if caller specifically requested no fraction digits, suppress the
509         ;;optional trailing zero
510         (when (and d (zerop d)) (setq tpoint nil))
511         (when w
512           (decf spaceleft len)
513           ;;optional leading zero
514           (when lpoint
515             (if (or (> spaceleft 0) tpoint) ;force at least one digit
516                 (decf spaceleft)
517                 (setq lpoint nil)))
518           ;;optional trailing zero
519           (when tpoint
520             (if (> spaceleft 0)
521                 (decf spaceleft)
522                 (setq tpoint nil))))
523         (cond ((and w (< spaceleft 0) ovf)
524                ;;field width overflow
525                (dotimes (i w) (write-char ovf stream))
526                t)
527               (t
528                (when w (dotimes (i spaceleft) (write-char pad stream)))
529                (if (minusp number)
530                    (write-char #\- stream)
531                    (if atsign (write-char #\+ stream)))
532                (when lpoint (write-char #\0 stream))
533                (write-string str stream)
534                (when tpoint (write-char #\0 stream))
535                nil)))))))
536
537 (def-format-interpreter #\E (colonp atsignp params)
538   (when colonp
539     (error 'format-error
540            :complaint
541            "cannot specify the colon modifier with this directive"))
542   (interpret-bind-defaults
543       ((w nil) (d nil) (e nil) (k 1) (ovf nil) (pad #\space) (mark nil))
544       params
545     (format-exponential stream (next-arg) w d e k ovf pad mark atsignp)))
546
547 (defun format-exponential (stream number w d e k ovf pad marker atsign)
548   (if (numberp number)
549       (if (floatp number)
550           (format-exp-aux stream number w d e k ovf pad marker atsign)
551           (if (rationalp number)
552               (format-exp-aux stream
553                               (coerce number 'single-float)
554                               w d e k ovf pad marker atsign)
555               (format-write-field stream
556                                   (decimal-string number)
557                                   w 1 0 #\space t)))
558       (format-princ stream number nil nil w 1 0 pad)))
559
560 (defun format-exponent-marker (number)
561   (if (typep number *read-default-float-format*)
562       #\e
563       (typecase number
564         (single-float #\f)
565         (double-float #\d)
566         (short-float #\s)
567         (long-float #\l))))
568
569 ;;; Here we prevent the scale factor from shifting all significance out of
570 ;;; a number to the right. We allow insignificant zeroes to be shifted in
571 ;;; to the left right, athough it is an error to specify k and d such that this
572 ;;; occurs. Perhaps we should detect both these condtions and flag them as
573 ;;; errors. As for now, we let the user get away with it, and merely guarantee
574 ;;; that at least one significant digit will appear.
575
576 ;;; Raymond Toy writes: The Hyperspec seems to say that the exponent
577 ;;; marker is always printed. Make it so. Also, the original version
578 ;;; causes errors when printing infinities or NaN's. The Hyperspec is
579 ;;; silent here, so let's just print out infinities and NaN's instead
580 ;;; of causing an error.
581 (defun format-exp-aux (stream number w d e k ovf pad marker atsign)
582   (if (and (floatp number)
583            (or (float-infinity-p number)
584                (float-nan-p number)))
585       (prin1 number stream)
586       (multiple-value-bind (num expt) (sb!impl::scale-exponent (abs number))
587         (let* ((expt (- expt k))
588                (estr (decimal-string (abs expt)))
589                (elen (if e (max (length estr) e) (length estr)))
590                (fdig (if d (if (plusp k) (1+ (- d k)) d) nil))
591                (fmin (if (minusp k) (- 1 k) nil))
592                (spaceleft (if w
593                               (- w 2 elen
594                                  (if (or atsign (minusp number))
595                                      1 0))
596                               nil)))
597           (if (and w ovf e (> elen e)) ;exponent overflow
598               (dotimes (i w) (write-char ovf stream))
599               (multiple-value-bind (fstr flen lpoint)
600                   (sb!impl::flonum-to-string num spaceleft fdig k fmin)
601                 (when w
602                   (decf spaceleft flen)
603                   (when lpoint
604                     (if (> spaceleft 0)
605                         (decf spaceleft)
606                         (setq lpoint nil))))
607                 (cond ((and w (< spaceleft 0) ovf)
608                        ;;significand overflow
609                        (dotimes (i w) (write-char ovf stream)))
610                       (t (when w
611                            (dotimes (i spaceleft) (write-char pad stream)))
612                          (if (minusp number)
613                              (write-char #\- stream)
614                              (if atsign (write-char #\+ stream)))
615                          (when lpoint (write-char #\0 stream))
616                          (write-string fstr stream)
617                          (write-char (if marker
618                                          marker
619                                          (format-exponent-marker number))
620                                      stream)
621                          (write-char (if (minusp expt) #\- #\+) stream)
622                          (when e
623                            ;;zero-fill before exponent if necessary
624                            (dotimes (i (- e (length estr)))
625                              (write-char #\0 stream)))
626                          (write-string estr stream)))))))))
627
628 (def-format-interpreter #\G (colonp atsignp params)
629   (when colonp
630     (error 'format-error
631            :complaint
632            "cannot specify the colon modifier with this directive"))
633   (interpret-bind-defaults
634       ((w nil) (d nil) (e nil) (k nil) (ovf nil) (pad #\space) (mark nil))
635       params
636     (format-general stream (next-arg) w d e k ovf pad mark atsignp)))
637
638 (defun format-general (stream number w d e k ovf pad marker atsign)
639   (if (numberp number)
640       (if (floatp number)
641           (format-general-aux stream number w d e k ovf pad marker atsign)
642           (if (rationalp number)
643               (format-general-aux stream
644                                   (coerce number 'single-float)
645                                   w d e k ovf pad marker atsign)
646               (format-write-field stream
647                                   (decimal-string number)
648                                   w 1 0 #\space t)))
649       (format-princ stream number nil nil w 1 0 pad)))
650
651 ;;; Raymond Toy writes: same change as for format-exp-aux
652 (defun format-general-aux (stream number w d e k ovf pad marker atsign)
653   (if (and (floatp number)
654            (or (float-infinity-p number)
655                (float-nan-p number)))
656       (prin1 number stream)
657       (multiple-value-bind (ignore n) (sb!impl::scale-exponent (abs number))
658         (declare (ignore ignore))
659         ;; KLUDGE: Default d if omitted. The procedure is taken directly from
660         ;; the definition given in the manual, and is not very efficient, since
661         ;; we generate the digits twice. Future maintainers are encouraged to
662         ;; improve on this. -- rtoy?? 1998??
663         (unless d
664           (multiple-value-bind (str len)
665               (sb!impl::flonum-to-string (abs number))
666             (declare (ignore str))
667             (let ((q (if (= len 1) 1 (1- len))))
668               (setq d (max q (min n 7))))))
669         (let* ((ee (if e (+ e 2) 4))
670                (ww (if w (- w ee) nil))
671                (dd (- d n)))
672           (cond ((<= 0 dd d)
673                  (let ((char (if (format-fixed-aux stream number ww dd nil
674                                                    ovf pad atsign)
675                                  ovf
676                                  #\space)))
677                    (dotimes (i ee) (write-char char stream))))
678                 (t
679                  (format-exp-aux stream number w d e (or k 1)
680                                  ovf pad marker atsign)))))))
681
682 (def-format-interpreter #\$ (colonp atsignp params)
683   (interpret-bind-defaults ((d 2) (n 1) (w 0) (pad #\space)) params
684     (format-dollars stream (next-arg) d n w pad colonp atsignp)))
685
686 (defun format-dollars (stream number d n w pad colon atsign)
687   (when (rationalp number)
688     ;; This coercion to SINGLE-FLOAT seems as though it gratuitously
689     ;; loses precision (why not LONG-FLOAT?) but it's the default
690     ;; behavior in the ANSI spec, so in some sense it's the right
691     ;; thing, and at least the user shouldn't be surprised.
692     (setq number (coerce number 'single-float)))
693   (if (floatp number)
694       (let* ((signstr (if (minusp number) "-" (if atsign "+" "")))
695              (signlen (length signstr)))
696         (multiple-value-bind (str strlen ig2 ig3 pointplace)
697             (sb!impl::flonum-to-string number nil d nil)
698           (declare (ignore ig2 ig3 strlen))
699           (when colon
700             (write-string signstr stream))
701           (dotimes (i (- w signlen (max n pointplace) 1 d))
702             (write-char pad stream))
703           (unless colon
704             (write-string signstr stream))
705           (dotimes (i (- n pointplace))
706             (write-char #\0 stream))
707           (write-string str stream)))
708       (format-write-field stream
709                           (decimal-string number)
710                           w 1 0 #\space t)))
711 \f
712 ;;;; FORMAT interpreters and support functions for line/page breaks etc.
713
714 (def-format-interpreter #\% (colonp atsignp params)
715   (when (or colonp atsignp)
716     (error 'format-error
717            :complaint
718            "cannot specify either colon or atsign for this directive"))
719   (interpret-bind-defaults ((count 1)) params
720     (dotimes (i count)
721       (terpri stream))))
722
723 (def-format-interpreter #\& (colonp atsignp params)
724   (when (or colonp atsignp)
725     (error 'format-error
726            :complaint
727            "cannot specify either colon or atsign for this directive"))
728   (interpret-bind-defaults ((count 1)) params
729     (fresh-line stream)
730     (dotimes (i (1- count))
731       (terpri stream))))
732
733 (def-format-interpreter #\| (colonp atsignp params)
734   (when (or colonp atsignp)
735     (error 'format-error
736            :complaint
737            "cannot specify either colon or atsign for this directive"))
738   (interpret-bind-defaults ((count 1)) params
739     (dotimes (i count)
740       (write-char (code-char form-feed-char-code) stream))))
741
742 (def-format-interpreter #\~ (colonp atsignp params)
743   (when (or colonp atsignp)
744     (error 'format-error
745            :complaint
746            "cannot specify either colon or atsign for this directive"))
747   (interpret-bind-defaults ((count 1)) params
748     (dotimes (i count)
749       (write-char #\~ stream))))
750
751 (def-complex-format-interpreter #\newline (colonp atsignp params directives)
752   (when (and colonp atsignp)
753     (error 'format-error
754            :complaint
755            "cannot specify both colon and atsign for this directive"))
756   (interpret-bind-defaults () params
757     (when atsignp
758       (write-char #\newline stream)))
759   (if (and (not colonp)
760            directives
761            (simple-string-p (car directives)))
762       (cons (string-left-trim *format-whitespace-chars*
763                               (car directives))
764             (cdr directives))
765       directives))
766 \f
767 ;;;; format interpreters and support functions for tabs and simple pretty
768 ;;;; printing
769
770 (def-format-interpreter #\T (colonp atsignp params)
771   (if colonp
772       (interpret-bind-defaults ((n 1) (m 1)) params
773         (pprint-tab (if atsignp :section-relative :section) n m stream))
774       (if atsignp
775           (interpret-bind-defaults ((colrel 1) (colinc 1)) params
776             (format-relative-tab stream colrel colinc))
777           (interpret-bind-defaults ((colnum 1) (colinc 1)) params
778             (format-absolute-tab stream colnum colinc)))))
779
780 (defun output-spaces (stream n)
781   (let ((spaces #.(make-string 100 :initial-element #\space)))
782     (loop
783       (when (< n (length spaces))
784         (return))
785       (write-string spaces stream)
786       (decf n (length spaces)))
787     (write-string spaces stream :end n)))
788
789 (defun format-relative-tab (stream colrel colinc)
790   (if (sb!pretty:pretty-stream-p stream)
791       (pprint-tab :line-relative colrel colinc stream)
792       (let* ((cur (sb!impl::charpos stream))
793              (spaces (if (and cur (plusp colinc))
794                          (- (* (ceiling (+ cur colrel) colinc) colinc) cur)
795                          colrel)))
796         (output-spaces stream spaces))))
797
798 (defun format-absolute-tab (stream colnum colinc)
799   (if (sb!pretty:pretty-stream-p stream)
800       (pprint-tab :line colnum colinc stream)
801       (let ((cur (sb!impl::charpos stream)))
802         (cond ((null cur)
803                (write-string "  " stream))
804               ((< cur colnum)
805                (output-spaces stream (- colnum cur)))
806               (t
807                (unless (zerop colinc)
808                  (output-spaces stream
809                                 (- colinc (rem (- cur colnum) colinc)))))))))
810
811 (def-format-interpreter #\_ (colonp atsignp params)
812   (interpret-bind-defaults () params
813     (pprint-newline (if colonp
814                         (if atsignp
815                             :mandatory
816                             :fill)
817                         (if atsignp
818                             :miser
819                             :linear))
820                     stream)))
821
822 (def-format-interpreter #\I (colonp atsignp params)
823   (when atsignp
824     (error 'format-error
825            :complaint "cannot specify the at-sign modifier"))
826   (interpret-bind-defaults ((n 0)) params
827     (pprint-indent (if colonp :current :block) n stream)))
828 \f
829 ;;;; format interpreter for ~*
830
831 (def-format-interpreter #\* (colonp atsignp params)
832   (if atsignp
833       (if colonp
834           (error 'format-error
835                  :complaint "cannot specify both colon and at-sign")
836           (interpret-bind-defaults ((posn 0)) params
837             (if (<= 0 posn (length orig-args))
838                 (setf args (nthcdr posn orig-args))
839                 (error 'format-error
840                        :complaint "Index ~W is out of bounds. (It should ~
841                                    have been between 0 and ~W.)"
842                        :args (list posn (length orig-args))))))
843       (if colonp
844           (interpret-bind-defaults ((n 1)) params
845             (do ((cur-posn 0 (1+ cur-posn))
846                  (arg-ptr orig-args (cdr arg-ptr)))
847                 ((eq arg-ptr args)
848                  (let ((new-posn (- cur-posn n)))
849                    (if (<= 0 new-posn (length orig-args))
850                        (setf args (nthcdr new-posn orig-args))
851                        (error 'format-error
852                               :complaint
853                               "Index ~W is out of bounds. (It should 
854                                have been between 0 and ~W.)"
855                               :args
856                               (list new-posn (length orig-args))))))))
857           (interpret-bind-defaults ((n 1)) params
858             (dotimes (i n)
859               (next-arg))))))
860 \f
861 ;;;; format interpreter for indirection
862
863 (def-format-interpreter #\? (colonp atsignp params string end)
864   (when colonp
865     (error 'format-error
866            :complaint "cannot specify the colon modifier"))
867   (interpret-bind-defaults () params
868     (handler-bind
869         ((format-error
870           (lambda (condition)
871             (error 'format-error
872                    :complaint
873                    "~A~%while processing indirect format string:"
874                    :args (list condition)
875                    :print-banner nil
876                    :control-string string
877                    :offset (1- end)))))
878       (if atsignp
879           (setf args (%format stream (next-arg) orig-args args))
880           (%format stream (next-arg) (next-arg))))))
881 \f
882 ;;;; format interpreters for capitalization
883
884 (def-complex-format-interpreter #\( (colonp atsignp params directives)
885   (let ((close (find-directive directives #\) nil)))
886     (unless close
887       (error 'format-error
888              :complaint "no corresponding close paren"))
889     (interpret-bind-defaults () params
890       (let* ((posn (position close directives))
891              (before (subseq directives 0 posn))
892              (after (nthcdr (1+ posn) directives))
893              (stream (make-case-frob-stream stream
894                                             (if colonp
895                                                 (if atsignp
896                                                     :upcase
897                                                     :capitalize)
898                                                 (if atsignp
899                                                     :capitalize-first
900                                                     :downcase)))))
901         (setf args (interpret-directive-list stream before orig-args args))
902         after))))
903
904 (def-complex-format-interpreter #\) ()
905   (error 'format-error
906          :complaint "no corresponding open paren"))
907 \f
908 ;;;; format interpreters and support functions for conditionalization
909
910 (def-complex-format-interpreter #\[ (colonp atsignp params directives)
911   (multiple-value-bind (sublists last-semi-with-colon-p remaining)
912       (parse-conditional-directive directives)
913     (setf args
914           (if atsignp
915               (if colonp
916                   (error 'format-error
917                          :complaint
918                      "cannot specify both the colon and at-sign modifiers")
919                   (if (cdr sublists)
920                       (error 'format-error
921                              :complaint
922                              "can only specify one section")
923                       (interpret-bind-defaults () params
924                         (let ((prev-args args)
925                               (arg (next-arg)))
926                           (if arg
927                               (interpret-directive-list stream
928                                                         (car sublists)
929                                                         orig-args
930                                                         prev-args)
931                               args)))))
932               (if colonp
933                   (if (= (length sublists) 2)
934                       (interpret-bind-defaults () params
935                         (if (next-arg)
936                             (interpret-directive-list stream (car sublists)
937                                                       orig-args args)
938                             (interpret-directive-list stream (cadr sublists)
939                                                       orig-args args)))
940                       (error 'format-error
941                              :complaint
942                              "must specify exactly two sections"))
943                   (interpret-bind-defaults ((index (next-arg))) params
944                     (let* ((default (and last-semi-with-colon-p
945                                          (pop sublists)))
946                            (last (1- (length sublists)))
947                            (sublist
948                             (if (<= 0 index last)
949                                 (nth (- last index) sublists)
950                                 default)))
951                       (interpret-directive-list stream sublist orig-args
952                                                 args))))))
953     remaining))
954
955 (def-complex-format-interpreter #\; ()
956   (error 'format-error
957          :complaint
958          "~~; not contained within either ~~[...~~] or ~~<...~~>"))
959
960 (def-complex-format-interpreter #\] ()
961   (error 'format-error
962          :complaint
963          "no corresponding open bracket"))
964 \f
965 ;;;; format interpreter for up-and-out
966
967 (defvar *outside-args*)
968
969 (def-format-interpreter #\^ (colonp atsignp params)
970   (when atsignp
971     (error 'format-error
972            :complaint "cannot specify the at-sign modifier"))
973   (when (and colonp (not *up-up-and-out-allowed*))
974     (error 'format-error
975            :complaint "attempt to use ~~:^ outside a ~~:{...~~} construct"))
976   (when (case (length params)
977           (0 (if colonp
978                  (null *outside-args*)
979                  (null args)))
980           (1 (interpret-bind-defaults ((count 0)) params
981                (zerop count)))
982           (2 (interpret-bind-defaults ((arg1 0) (arg2 0)) params
983                (= arg1 arg2)))
984           (t (interpret-bind-defaults ((arg1 0) (arg2 0) (arg3 0)) params
985                (<= arg1 arg2 arg3))))
986     (throw (if colonp 'up-up-and-out 'up-and-out)
987            args)))
988 \f
989 ;;;; format interpreters for iteration
990
991 (def-complex-format-interpreter #\{
992                                 (colonp atsignp params string end directives)
993   (let ((close (find-directive directives #\} nil)))
994     (unless close
995       (error 'format-error
996              :complaint
997              "no corresponding close brace"))
998     (interpret-bind-defaults ((max-count nil)) params
999       (let* ((closed-with-colon (format-directive-colonp close))
1000              (posn (position close directives))
1001              (insides (if (zerop posn)
1002                           (next-arg)
1003                           (subseq directives 0 posn)))
1004              (*up-up-and-out-allowed* colonp))
1005         (labels
1006             ((do-guts (orig-args args)
1007                (if (zerop posn)
1008                    (handler-bind
1009                        ((format-error
1010                          (lambda (condition)
1011                            (error
1012                             'format-error
1013                             :complaint
1014                             "~A~%while processing indirect format string:"
1015                             :args (list condition)
1016                             :print-banner nil
1017                             :control-string string
1018                             :offset (1- end)))))
1019                      (%format stream insides orig-args args))
1020                    (interpret-directive-list stream insides
1021                                              orig-args args)))
1022              (bind-args (orig-args args)
1023                (if colonp
1024                    (let* ((arg (next-arg))
1025                           (*logical-block-popper* nil)
1026                           (*outside-args* args))
1027                      (catch 'up-and-out
1028                        (do-guts arg arg))
1029                      args)
1030                    (do-guts orig-args args)))
1031              (do-loop (orig-args args)
1032                (catch (if colonp 'up-up-and-out 'up-and-out)
1033                  (loop
1034                    (when (and (not closed-with-colon) (null args))
1035                      (return))
1036                    (when (and max-count (minusp (decf max-count)))
1037                      (return))
1038                    (setf args (bind-args orig-args args))
1039                    (when (and closed-with-colon (null args))
1040                      (return)))
1041                  args)))
1042           (if atsignp
1043               (setf args (do-loop orig-args args))
1044               (let ((arg (next-arg))
1045                     (*logical-block-popper* nil))
1046                 (do-loop arg arg)))
1047           (nthcdr (1+ posn) directives))))))
1048
1049 (def-complex-format-interpreter #\} ()
1050   (error 'format-error
1051          :complaint "no corresponding open brace"))
1052 \f
1053 ;;;; format interpreters and support functions for justification
1054
1055 (def-complex-format-interpreter #\<
1056                                 (colonp atsignp params string end directives)
1057   (multiple-value-bind (segments first-semi close remaining)
1058       (parse-format-justification directives)
1059     (setf args
1060           (if (format-directive-colonp close)
1061               (multiple-value-bind (prefix per-line-p insides suffix)
1062                   (parse-format-logical-block segments colonp first-semi
1063                                               close params string end)
1064                 (interpret-format-logical-block stream orig-args args
1065                                                 prefix per-line-p insides
1066                                                 suffix atsignp))
1067               (let ((count (reduce #'+ (mapcar (lambda (x) (count-if #'illegal-inside-justification-p x)) segments))))
1068                 (when (> count 0)
1069                   ;; ANSI specifies that "an error is signalled" in this
1070                   ;; situation.
1071                   (error 'format-error
1072                          :complaint "~D illegal directive~:P found inside justification block"
1073                          :args (list count)
1074                          :references (list '(:ansi-cl :section (22 3 5 2)))))
1075                 (interpret-format-justification stream orig-args args
1076                                                 segments colonp atsignp
1077                                                 first-semi params))))
1078     remaining))
1079
1080 (defun interpret-format-justification
1081        (stream orig-args args segments colonp atsignp first-semi params)
1082   (interpret-bind-defaults
1083       ((mincol 0) (colinc 1) (minpad 0) (padchar #\space))
1084       params
1085     (let ((newline-string nil)
1086           (strings nil)
1087           (extra-space 0)
1088           (line-len 0))
1089       (setf args
1090             (catch 'up-and-out
1091               (when (and first-semi (format-directive-colonp first-semi))
1092                 (interpret-bind-defaults
1093                     ((extra 0)
1094                      (len (or (sb!impl::line-length stream) 72)))
1095                     (format-directive-params first-semi)
1096                   (setf newline-string
1097                         (with-output-to-string (stream)
1098                           (setf args
1099                                 (interpret-directive-list stream
1100                                                           (pop segments)
1101                                                           orig-args
1102                                                           args))))
1103                   (setf extra-space extra)
1104                   (setf line-len len)))
1105               (dolist (segment segments)
1106                 (push (with-output-to-string (stream)
1107                         (setf args
1108                               (interpret-directive-list stream segment
1109                                                         orig-args args)))
1110                       strings))
1111               args))
1112       (format-justification stream newline-string extra-space line-len strings
1113                             colonp atsignp mincol colinc minpad padchar)))
1114   args)
1115
1116 (defun format-justification (stream newline-prefix extra-space line-len strings
1117                              pad-left pad-right mincol colinc minpad padchar)
1118   (setf strings (reverse strings))
1119   (let* ((num-gaps (+ (1- (length strings))
1120                       (if pad-left 1 0)
1121                       (if pad-right 1 0)))
1122          (chars (+ (* num-gaps minpad)
1123                    (loop
1124                      for string in strings
1125                      summing (length string))))
1126          (length (if (> chars mincol)
1127                      (+ mincol (* (ceiling (- chars mincol) colinc) colinc))
1128                      mincol))
1129          (padding (+ (- length chars) (* num-gaps minpad))))
1130     (when (and newline-prefix
1131                (> (+ (or (sb!impl::charpos stream) 0)
1132                      length extra-space)
1133                   line-len))
1134       (write-string newline-prefix stream))
1135     (flet ((do-padding ()
1136              (let ((pad-len
1137                     (if (zerop num-gaps) padding (truncate padding num-gaps))))
1138                (decf padding pad-len)
1139                (decf num-gaps)
1140                (dotimes (i pad-len) (write-char padchar stream)))))
1141       (when (or pad-left (and (not pad-right) (null (cdr strings))))
1142         (do-padding))
1143       (when strings
1144         (write-string (car strings) stream)
1145         (dolist (string (cdr strings))
1146           (do-padding)
1147           (write-string string stream)))
1148       (when pad-right
1149         (do-padding)))))
1150
1151 (defun interpret-format-logical-block
1152        (stream orig-args args prefix per-line-p insides suffix atsignp)
1153   (let ((arg (if atsignp args (next-arg))))
1154     (if per-line-p
1155         (pprint-logical-block
1156             (stream arg :per-line-prefix prefix :suffix suffix)
1157           (let ((*logical-block-popper* (lambda () (pprint-pop))))
1158             (catch 'up-and-out
1159               (interpret-directive-list stream insides
1160                                         (if atsignp orig-args arg)
1161                                         arg))))
1162         (pprint-logical-block (stream arg :prefix prefix :suffix suffix)
1163           (let ((*logical-block-popper* (lambda () (pprint-pop))))
1164             (catch 'up-and-out
1165               (interpret-directive-list stream insides
1166                                         (if atsignp orig-args arg)
1167                                         arg))))))
1168   (if atsignp nil args))
1169 \f
1170 ;;;; format interpreter and support functions for user-defined method
1171
1172 (def-format-interpreter #\/ (string start end colonp atsignp params)
1173   (let ((symbol (extract-user-fun-name string start end)))
1174     (collect ((args))
1175       (dolist (param-and-offset params)
1176         (let ((param (cdr param-and-offset)))
1177           (case param
1178             (:arg (args (next-arg)))
1179             (:remaining (args (length args)))
1180             (t (args param)))))
1181       (apply (fdefinition symbol) stream (next-arg) colonp atsignp (args)))))