source: branches/0.17.x/abcl/src/org/armedbear/lisp/format.lisp

Last change on this file was 11784, checked in by ehuelsmann, 16 years ago

Add a function which seems to be missing in our sources (MISSING-ARG).

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 117.9 KB
Line 
1;;; format.lisp
2;;;
3;;; Copyright (C) 2004-2007 Peter Graves
4;;; $Id: format.lisp 11784 2009-04-26 06:49:37Z ehuelsmann $
5;;;
6;;; This program is free software; you can redistribute it and/or
7;;; modify it under the terms of the GNU General Public License
8;;; as published by the Free Software Foundation; either version 2
9;;; of the License, or (at your option) any later version.
10;;;
11;;; This program is distributed in the hope that it will be useful,
12;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
13;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14;;; GNU General Public License for more details.
15;;;
16;;; You should have received a copy of the GNU General Public License
17;;; along with this program; if not, write to the Free Software
18;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
19;;;
20;;; As a special exception, the copyright holders of this library give you
21;;; permission to link this library with independent modules to produce an
22;;; executable, regardless of the license terms of these independent
23;;; modules, and to copy and distribute the resulting executable under
24;;; terms of your choice, provided that you also meet, for each linked
25;;; independent module, the terms and conditions of the license of that
26;;; module.  An independent module is a module which is not derived from
27;;; or based on this library.  If you modify this library, you may extend
28;;; this exception to your version of the library, but you are not
29;;; obligated to do so.  If you do not wish to do so, delete this
30;;; exception statement from your version.
31
32;;; Adapted from CMUCL/SBCL.
33
34(in-package "SYSTEM")
35
36;;; From primordial-extensions.lisp.
37
38;;; Concatenate together the names of some strings and symbols,
39;;; producing a symbol in the current package.
40(eval-when (:compile-toplevel :load-toplevel :execute)
41  (defun symbolicate (&rest things)
42    (let ((name (apply #'concatenate 'string (mapcar #'string things))))
43      (values (intern name)))))
44
45;;; a helper function for various macros which expect clauses of a
46;;; given length, etc.
47;;;
48;;; Return true if X is a proper list whose length is between MIN and
49;;; MAX (inclusive).
50(eval-when (:compile-toplevel :load-toplevel :execute)
51  (defun proper-list-of-length-p (x min &optional (max min))
52    ;; FIXME: This implementation will hang on circular list
53    ;; structure. Since this is an error-checking utility, i.e. its
54    ;; job is to deal with screwed-up input, it'd be good style to fix
55    ;; it so that it can deal with circular list structure.
56    (cond ((minusp max) nil)
57          ((null x) (zerop min))
58          ((consp x)
59           (and (plusp max)
60                (proper-list-of-length-p (cdr x)
61                                         (if (plusp (1- min))
62                                             (1- min)
63                                             0)
64                                         (1- max))))
65          (t nil))))
66
67;;; From early-extensions.lisp.
68
69(defconstant form-feed-char-code 12)
70
71(defmacro named-let (name binds &body body)
72  (dolist (x binds)
73    (unless (proper-list-of-length-p x 2)
74      (error "malformed NAMED-LET variable spec: ~S" x)))
75  `(labels ((,name ,(mapcar #'first binds) ,@body))
76     (,name ,@(mapcar #'second binds))))
77
78;;;; ONCE-ONLY
79;;;;
80;;;; "The macro ONCE-ONLY has been around for a long time on various
81;;;; systems [..] if you can understand how to write and when to use
82;;;; ONCE-ONLY, then you truly understand macro." -- Peter Norvig,
83;;;; _Paradigms of Artificial Intelligence Programming: Case Studies
84;;;; in Common Lisp_, p. 853
85
86;;; ONCE-ONLY is a utility useful in writing source transforms and
87;;; macros. It provides a concise way to wrap a LET around some code
88;;; to ensure that some forms are only evaluated once.
89;;;
90;;; Create a LET* which evaluates each value expression, binding a
91;;; temporary variable to the result, and wrapping the LET* around the
92;;; result of the evaluation of BODY. Within the body, each VAR is
93;;; bound to the corresponding temporary variable.
94(defmacro once-only (specs &body body)
95  (named-let frob ((specs specs)
96       (body body))
97             (if (null specs)
98                 `(progn ,@body)
99                 (let ((spec (first specs)))
100                   ;; FIXME: should just be DESTRUCTURING-BIND of SPEC
101                   (unless (proper-list-of-length-p spec 2)
102                     (error "malformed ONCE-ONLY binding spec: ~S" spec))
103                   (let* ((name (first spec))
104                          (exp-temp (gensym (symbol-name name))))
105                     `(let ((,exp-temp ,(second spec))
106                            (,name (gensym "ONCE-ONLY-")))
107                        `(let ((,,name ,,exp-temp))
108                           ,,(frob (rest specs) body))))))))
109
110;;; From print.lisp.
111
112;;; FLONUM-TO-STRING (and its subsidiary function FLOAT-STRING) does
113;;; most of the work for all printing of floating point numbers in the
114;;; printer and in FORMAT. It converts a floating point number to a
115;;; string in a free or fixed format with no exponent. The
116;;; interpretation of the arguments is as follows:
117;;;
118;;;     X - The floating point number to convert, which must not be
119;;;   negative.
120;;;     WIDTH    - The preferred field width, used to determine the number
121;;;   of fraction digits to produce if the FDIGITS parameter
122;;;   is unspecified or NIL. If the non-fraction digits and the
123;;;   decimal point alone exceed this width, no fraction digits
124;;;   will be produced unless a non-NIL value of FDIGITS has been
125;;;   specified. Field overflow is not considerd an error at this
126;;;   level.
127;;;     FDIGITS  - The number of fractional digits to produce. Insignificant
128;;;   trailing zeroes may be introduced as needed. May be
129;;;   unspecified or NIL, in which case as many digits as possible
130;;;   are generated, subject to the constraint that there are no
131;;;   trailing zeroes.
132;;;     SCALE    - If this parameter is specified or non-NIL, then the number
133;;;   printed is (* x (expt 10 scale)). This scaling is exact,
134;;;   and cannot lose precision.
135;;;     FMIN     - This parameter, if specified or non-NIL, is the minimum
136;;;   number of fraction digits which will be produced, regardless
137;;;   of the value of WIDTH or FDIGITS. This feature is used by
138;;;   the ~E format directive to prevent complete loss of
139;;;   significance in the printed value due to a bogus choice of
140;;;   scale factor.
141;;;
142;;; Most of the optional arguments are for the benefit for FORMAT and are not
143;;; used by the printer.
144;;;
145;;; Returns:
146;;; (VALUES DIGIT-STRING DIGIT-LENGTH LEADING-POINT TRAILING-POINT DECPNT)
147;;; where the results have the following interpretation:
148;;;
149;;;     DIGIT-STRING    - The decimal representation of X, with decimal point.
150;;;     DIGIT-LENGTH    - The length of the string DIGIT-STRING.
151;;;     LEADING-POINT   - True if the first character of DIGIT-STRING is the
152;;;          decimal point.
153;;;     TRAILING-POINT  - True if the last character of DIGIT-STRING is the
154;;;          decimal point.
155;;;     POINT-POS       - The position of the digit preceding the decimal
156;;;          point. Zero indicates point before first digit.
157;;;
158;;; NOTE: FLONUM-TO-STRING goes to a lot of trouble to guarantee
159;;; accuracy. Specifically, the decimal number printed is the closest
160;;; possible approximation to the true value of the binary number to
161;;; be printed from among all decimal representations with the same
162;;; number of digits. In free-format output, i.e. with the number of
163;;; digits unconstrained, it is guaranteed that all the information is
164;;; preserved, so that a properly- rounding reader can reconstruct the
165;;; original binary number, bit-for-bit, from its printed decimal
166;;; representation. Furthermore, only as many digits as necessary to
167;;; satisfy this condition will be printed.
168;;;
169;;; FLOAT-STRING actually generates the digits for positive numbers.
170;;; The algorithm is essentially that of algorithm Dragon4 in "How to
171;;; Print Floating-Point Numbers Accurately" by Steele and White. The
172;;; current (draft) version of this paper may be found in
173;;; [CMUC]<steele>tradix.press. DO NOT EVEN THINK OF ATTEMPTING TO
174;;; UNDERSTAND THIS CODE WITHOUT READING THE PAPER!
175
176(defun flonum-to-string (x &optional width fdigits scale fmin)
177  (declare (ignore fmin)) ; FIXME
178  (cond ((zerop x)
179   ;; Zero is a special case which FLOAT-STRING cannot handle.
180   (if fdigits
181       (let ((s (make-string (1+ fdigits) :initial-element #\0)))
182         (setf (schar s 0) #\.)
183         (values s (length s) t (zerop fdigits) 0))
184       (values "." 1 t t 0)))
185  (t
186         (when scale
187           (setf x (* x (expt 10 scale))))
188         (let* ((s (float-string x))
189                (length (length s))
190                (index (position #\. s)))
191           (when (and (< x 1)
192                      (> length 0)
193                      (eql (schar s 0) #\0))
194             (setf s (subseq s 1)
195                   length (length s)
196                   index (position #\. s)))
197           (when fdigits
198             ;; "Leading zeros are not permitted, except that a single zero
199             ;; digit is output before the decimal point if the printed value
200             ;; is less than one, and this single zero digit is not output at
201             ;; all if w=d+1."
202             (let ((actual-fdigits (- length index 1)))
203               (cond ((< actual-fdigits fdigits)
204                      ;; Add the required number of trailing zeroes.
205                      (setf s (concatenate 'string s
206                                           (make-string (- fdigits actual-fdigits)
207                                                        :initial-element #\0))
208                            length (length s)))
209                     ((> actual-fdigits fdigits)
210                      (let* ((desired-length (+ index 1 fdigits))
211                             (c (schar s desired-length)))
212                        (setf s (subseq s 0 (+ index 1 fdigits))
213                              length (length s)
214                              index (position #\. s))
215                        (when (char>= c #\5)
216                          (setf s (round-up s)
217                                length (length s)
218                                index (position #\. s))))))))
219           (when (and width (> length width))
220             ;; The string is too long. Shorten it by removing insignificant
221             ;; trailing zeroes if possible.
222             (let ((minimum-width (+ (1+ index) (or fdigits 0))))
223               (when (< minimum-width width)
224                 (setf minimum-width width))
225               (when (> length minimum-width)
226                 ;; But we don't want to shorten e.g. "1.7d100"...
227                 (when (every #'digit-char-p (subseq s (1+ index)))
228                   (let ((c (schar s minimum-width)))
229                     (setf s (subseq s 0 minimum-width)
230                           length minimum-width)
231                     (when (char>= c #\5)
232                       (setf s (round-up s)
233                             length (length s)
234                             index (position #\. s))))))))
235           (values s length (eql index 0) (eql index (1- length)) index)))))
236
237(defun round-up (string)
238  (let* ((index (position #\. string))
239         (n (read-from-string (setf string (remove #\. string))))
240         (s (princ-to-string (incf n))))
241    (loop for char across string
242      while (equal char #\0)
243      do (setf s (concatenate 'string "0" s)))
244    (cond ((null index)
245           s)
246          (t
247           (when (> (length s) (length string))
248             ;; Rounding up made the string longer, which means we went from (say) 99
249             ;; to 100. Drop the trailing #\0 and move the #\. one character to the
250             ;; right.
251             (setf s (subseq s 0 (1- (length s))))
252             (incf index))
253           (concatenate 'string (subseq s 0 index) "." (subseq s index))))))
254
255
256(defun scale-exponent (original-x)
257  (let* ((x (coerce original-x 'long-float)))
258    (multiple-value-bind (sig exponent) (decode-float x)
259      (declare (ignore sig))
260      (if (= x 0.0l0)
261    (values (float 0.0l0 original-x) 1)
262    (let* ((ex (locally (declare (optimize (safety 0)))
263                       (the fixnum
264                            (round (* exponent (log 2l0 10))))))
265     (x (if (minusp ex)
266      (if (float-denormalized-p x)
267          (* x 1.0l16 (expt 10.0l0 (- (- ex) 16)))
268          (* x 10.0l0 (expt 10.0l0 (- (- ex) 1))))
269      (/ x 10.0l0 (expt 10.0l0 (1- ex))))))
270      (do ((d 10.0l0 (* d 10.0l0))
271     (y x (/ x d))
272     (ex ex (1+ ex)))
273    ((< y 1.0l0)
274     (do ((m 10.0l0 (* m 10.0l0))
275          (z y (* y m))
276          (ex ex (1- ex)))
277         ((>= z 0.1l0)
278          (values (float z original-x) ex))
279                   (declare (long-float m) (integer ex))))
280              (declare (long-float d))))))))
281
282(defconstant double-float-exponent-byte
283  (byte 11 20))
284
285(defun float-denormalized-p (x)
286  "Return true if the double-float X is denormalized."
287  (and (zerop (ldb double-float-exponent-byte (double-float-high-bits x)))
288       (not (zerop x))))
289
290;;; From early-format.lisp.
291
292(in-package #:format)
293
294(defparameter *format-whitespace-chars*
295  (vector #\space
296    #\newline
297          #\tab))
298
299(defvar *format-directive-expanders*
300  (make-array char-code-limit :initial-element nil))
301(defvar *format-directive-interpreters*
302  (make-array char-code-limit :initial-element nil))
303
304(defvar *default-format-error-control-string* nil)
305(defvar *default-format-error-offset* nil)
306
307;;;; specials used to communicate information
308
309;;; Used both by the expansion stuff and the interpreter stuff. When it is
310;;; non-NIL, up-up-and-out (~:^) is allowed. Otherwise, ~:^ isn't allowed.
311(defvar *up-up-and-out-allowed* nil)
312
313;;; Used by the interpreter stuff. When it's non-NIL, it's a function
314;;; that will invoke PPRINT-POP in the right lexical environemnt.
315(declaim (type (or null function) *logical-block-popper*))
316(defvar *logical-block-popper* nil)
317
318;;; Used by the expander stuff. This is bindable so that ~<...~:>
319;;; can change it.
320(defvar *expander-next-arg-macro* 'expander-next-arg)
321
322;;; Used by the expander stuff. Initially starts as T, and gets set to NIL
323;;; if someone needs to do something strange with the arg list (like use
324;;; the rest, or something).
325(defvar *only-simple-args*)
326
327;;; Used by the expander stuff. We do an initial pass with this as NIL.
328;;; If someone doesn't like this, they (THROW 'NEED-ORIG-ARGS NIL) and we try
329;;; again with it bound to T. If this is T, we don't try to do anything
330;;; fancy with args.
331(defvar *orig-args-available* nil)
332
333;;; Used by the expander stuff. List of (symbol . offset) for simple args.
334(defvar *simple-args*)
335
336;;; From late-format.lisp.
337
338(in-package #:format)
339
340(define-condition format-error (error)
341  ((complaint :reader format-error-complaint :initarg :complaint)
342   (args :reader format-error-args :initarg :args :initform nil)
343   (control-string :reader format-error-control-string
344       :initarg :control-string
345       :initform *default-format-error-control-string*)
346   (offset :reader format-error-offset :initarg :offset
347     :initform *default-format-error-offset*)
348   (print-banner :reader format-error-print-banner :initarg :print-banner
349     :initform t))
350  (:report %print-format-error))
351
352(defun %print-format-error (condition stream)
353  (format stream
354    "~:[~;error in format: ~]~
355           ~?~@[~%  ~A~%  ~V@T^~]"
356    (format-error-print-banner condition)
357    (format-error-complaint condition)
358    (format-error-args condition)
359    (format-error-control-string condition)
360    (format-error-offset condition)))
361
362(defun missing-arg ()
363  (error "Missing argument in format directive"))
364
365(defstruct format-directive
366  (string (missing-arg) :type simple-string)
367  (start (missing-arg) :type (and unsigned-byte fixnum))
368  (end (missing-arg) :type (and unsigned-byte fixnum))
369  (character (missing-arg) :type base-char)
370  (colonp nil :type (member t nil))
371  (atsignp nil :type (member t nil))
372  (params nil :type list))
373(defmethod print-object ((x format-directive) stream)
374  (print-unreadable-object (x stream)
375                           (write-string (format-directive-string x)
376                                         stream
377                                         :start (format-directive-start x)
378                                         :end (format-directive-end x))))
379
380;;;; TOKENIZE-CONTROL-STRING
381
382(defun tokenize-control-string (string)
383  (declare (simple-string string))
384  (let ((index 0)
385  (end (length string))
386  (result nil)
387  (in-block nil)
388  (pprint nil)
389  (semi nil)
390  (justification-semi 0))
391    (declare (type index fixnum))
392    (loop
393      (let ((next-directive (or (position #\~ string :start index) end)))
394        (declare (type index next-directive))
395  (when (> next-directive index)
396    (push (subseq string index next-directive) result))
397  (when (= next-directive end)
398    (return))
399  (let* ((directive (parse-directive string next-directive))
400         (directive-char (format-directive-character directive)))
401          (declare (type character directive-char))
402    ;; We are looking for illegal combinations of format
403    ;; directives in the control string.  See the last paragraph
404    ;; of CLHS 22.3.5.2: "an error is also signaled if the
405    ;; ~<...~:;...~> form of ~<...~> is used in the same format
406    ;; string with ~W, ~_, ~<...~:>, ~I, or ~:T."
407    (cond ((char= #\< directive-char)
408     ;; Found a justification or logical block
409     (setf in-block t))
410    ((and in-block (char= #\; directive-char))
411     ;; Found a semi colon in a justification or logical block
412     (setf semi t))
413    ((char= #\> directive-char)
414     ;; End of justification or logical block.  Figure out which.
415     (setf in-block nil)
416     (cond ((format-directive-colonp directive)
417      ;; A logical-block directive.  Note that fact, and also
418      ;; note that we don't care if we found any ~;
419      ;; directives in the block.
420      (setf pprint t)
421      (setf semi nil))
422           (semi
423      ;; A justification block with a ~; directive in it.
424      (incf justification-semi))))
425    ((and (not in-block)
426          (or (and (char= #\T directive-char) (format-directive-colonp directive))
427        (char= #\W directive-char)
428        (char= #\_ directive-char)
429        (char= #\I directive-char)))
430     (setf pprint t)))
431    (push directive result)
432    (setf index (format-directive-end directive)))))
433    (when (and pprint (plusp justification-semi))
434      (error 'format-error
435       :complaint "A justification directive cannot be in the same format string~%~
436             as ~~W, ~~I, ~~:T, or a logical-block directive."
437       :control-string string
438       :offset 0))
439    (nreverse result)))
440
441(defun parse-directive (string start)
442  (let ((posn (1+ start)) (params nil) (colonp nil) (atsignp nil)
443  (end (length string)))
444    (flet ((get-char ()
445                     (if (= posn end)
446                         (error 'format-error
447                                :complaint "String ended before directive was found."
448                                :control-string string
449                                :offset start)
450                         (schar string posn)))
451     (check-ordering ()
452                           (when (or colonp atsignp)
453                             (error 'format-error
454                                    :complaint "parameters found after #\\: or #\\@ modifier"
455                                    :control-string string
456                                    :offset posn))))
457      (loop
458  (let ((char (get-char)))
459    (cond ((or (char<= #\0 char #\9) (char= char #\+) (char= char #\-))
460     (check-ordering)
461     (multiple-value-bind (param new-posn)
462                   (parse-integer string :start posn :junk-allowed t)
463       (push (cons posn param) params)
464       (setf posn new-posn)
465       (case (get-char)
466         (#\,)
467         ((#\: #\@)
468          (decf posn))
469         (t
470          (return)))))
471    ((or (char= char #\v)
472         (char= char #\V))
473     (check-ordering)
474     (push (cons posn :arg) params)
475     (incf posn)
476     (case (get-char)
477       (#\,)
478       ((#\: #\@)
479        (decf posn))
480       (t
481        (return))))
482    ((char= char #\#)
483     (check-ordering)
484     (push (cons posn :remaining) params)
485     (incf posn)
486     (case (get-char)
487       (#\,)
488       ((#\: #\@)
489        (decf posn))
490       (t
491        (return))))
492    ((char= char #\')
493     (check-ordering)
494     (incf posn)
495     (push (cons posn (get-char)) params)
496     (incf posn)
497     (unless (char= (get-char) #\,)
498       (decf posn)))
499    ((char= char #\,)
500     (check-ordering)
501     (push (cons posn nil) params))
502    ((char= char #\:)
503     (if colonp
504         (error 'format-error
505          :complaint "too many colons supplied"
506          :control-string string
507          :offset posn)
508         (setf colonp t)))
509    ((char= char #\@)
510     (if atsignp
511         (error 'format-error
512          :complaint "too many #\\@ characters supplied"
513          :control-string string
514          :offset posn)
515         (setf atsignp t)))
516    (t
517     (when (and (char= (schar string (1- posn)) #\,)
518          (or (< posn 2)
519        (char/= (schar string (- posn 2)) #\')))
520       (check-ordering)
521       (push (cons (1- posn) nil) params))
522     (return))))
523  (incf posn))
524      (let ((char (get-char)))
525  (when (char= char #\/)
526    (let ((closing-slash (position #\/ string :start (1+ posn))))
527      (if closing-slash
528    (setf posn closing-slash)
529    (error 'format-error
530           :complaint "no matching closing slash"
531           :control-string string
532           :offset posn))))
533  (make-format-directive
534   :string string :start start :end (1+ posn)
535   :character (char-upcase char)
536   :colonp colonp :atsignp atsignp
537   :params (nreverse params))))))
538
539;;;; FORMATTER stuff
540
541(defmacro formatter (control-string)
542  `#',(%formatter control-string))
543
544(defun %formatter (control-string)
545  (block nil
546    (catch 'need-orig-args
547      (let* ((*simple-args* nil)
548       (*only-simple-args* t)
549       (guts (expand-control-string control-string))
550       (args nil))
551  (dolist (arg *simple-args*)
552    (push `(,(car arg)
553      (error
554       'format-error
555       :complaint "required argument missing"
556       :control-string ,control-string
557       :offset ,(cdr arg)))
558    args))
559  (return `(lambda (stream &optional ,@args &rest args)
560       ,guts
561       args))))
562    (let ((*orig-args-available* t)
563    (*only-simple-args* nil))
564      `(lambda (stream &rest orig-args)
565   (let ((args orig-args))
566     ,(expand-control-string control-string)
567     args)))))
568
569(defun expand-control-string (string)
570  (let* ((string (etypecase string
571       (simple-string
572        string)
573       (string
574        (coerce string 'simple-string))))
575   (*default-format-error-control-string* string)
576   (directives (tokenize-control-string string)))
577    `(block nil
578       ,@(expand-directive-list directives))))
579
580(defun expand-directive-list (directives)
581  (let ((results nil)
582  (remaining-directives directives))
583    (loop
584      (unless remaining-directives
585  (return))
586      (multiple-value-bind (form new-directives)
587        (expand-directive (car remaining-directives)
588                          (cdr remaining-directives))
589  (push form results)
590  (setf remaining-directives new-directives)))
591    (reverse results)))
592
593(defun expand-directive (directive more-directives)
594  (etypecase directive
595    (format-directive
596     (let ((expander
597      (aref *format-directive-expanders*
598      (char-code (format-directive-character directive))))
599     (*default-format-error-offset*
600      (1- (format-directive-end directive))))
601       (declare (type (or null function) expander))
602       (if expander
603     (funcall expander directive more-directives)
604     (error 'format-error
605      :complaint "unknown directive ~@[(character: ~A)~]"
606      :args (list (char-name (format-directive-character directive)))))))
607    (simple-string
608     (values `(write-string ,directive stream)
609       more-directives))))
610
611(defmacro expander-next-arg (string offset)
612  `(if args
613       (pop args)
614       (error 'format-error
615        :complaint "no more arguments"
616        :control-string ,string
617        :offset ,offset)))
618
619(defun expand-next-arg (&optional offset)
620  (if (or *orig-args-available* (not *only-simple-args*))
621      `(,*expander-next-arg-macro*
622  ,*default-format-error-control-string*
623  ,(or offset *default-format-error-offset*))
624      (let ((symbol (gensym "FORMAT-ARG-")))
625  (push (cons symbol (or offset *default-format-error-offset*))
626        *simple-args*)
627  symbol)))
628
629(defmacro expand-bind-defaults (specs params &body body)
630  (sys::once-only ((params params))
631                  (if specs
632                      (collect ((expander-bindings) (runtime-bindings))
633                               (dolist (spec specs)
634                                 (destructuring-bind (var default) spec
635                                                     (let ((symbol (gensym)))
636                                                       (expander-bindings
637                                                        `(,var ',symbol))
638                                                       (runtime-bindings
639                                                        `(list ',symbol
640                                                               (let* ((param-and-offset (pop ,params))
641                                                                      (offset (car param-and-offset))
642                                                                      (param (cdr param-and-offset)))
643                                                                 (case param
644                                                                   (:arg `(or ,(expand-next-arg offset)
645                                                                              ,,default))
646                                                                   (:remaining
647                                                                    (setf *only-simple-args* nil)
648                                                                    '(length args))
649                                                                   ((nil) ,default)
650                                                                   (t param))))))))
651                               `(let ,(expander-bindings)
652                                  `(let ,(list ,@(runtime-bindings))
653                                     ,@(if ,params
654                                           (error
655                                            'format-error
656                                            :complaint
657                                            "too many parameters, expected no more than ~W"
658                                            :args (list ,(length specs))
659                                            :offset (caar ,params)))
660                                     ,,@body)))
661                      `(progn
662                         (when ,params
663                           (error 'format-error
664                                  :complaint "too many parameters, expected none"
665                                  :offset (caar ,params)))
666                         ,@body))))
667
668;;;; format directive machinery
669
670;;; FIXME: only used in this file, could be SB!XC:DEFMACRO in EVAL-WHEN
671(defmacro def-complex-format-directive (char lambda-list &body body)
672  (let ((defun-name
673          (intern (concatenate 'string
674                               (let ((name (char-name char)))
675                                 (cond (name
676                                        (string-capitalize name))
677                                       (t
678                                        (string char))))
679                               "-FORMAT-DIRECTIVE-EXPANDER")))
680  (directive (gensym))
681  (directives (if lambda-list (car (last lambda-list)) (gensym))))
682    `(progn
683       (defun ,defun-name (,directive ,directives)
684   ,@(if lambda-list
685         `((let ,(mapcar (lambda (var)
686         `(,var
687           (,(sys::symbolicate "FORMAT-DIRECTIVE-" var)
688            ,directive)))
689             (butlast lambda-list))
690       ,@body))
691         `((declare (ignore ,directive ,directives))
692     ,@body)))
693       (%set-format-directive-expander ,char #',defun-name))))
694
695;;; FIXME: only used in this file, could be SB!XC:DEFMACRO in EVAL-WHEN
696(defmacro def-format-directive (char lambda-list &body body)
697  (let ((directives (gensym))
698  (declarations nil)
699  (body-without-decls body))
700    (loop
701      (let ((form (car body-without-decls)))
702  (unless (and (consp form) (eq (car form) 'declare))
703    (return))
704  (push (pop body-without-decls) declarations)))
705    (setf declarations (reverse declarations))
706    `(def-complex-format-directive ,char (,@lambda-list ,directives)
707       ,@declarations
708       (values (progn ,@body-without-decls)
709         ,directives))))
710
711(eval-when (:compile-toplevel :load-toplevel :execute)
712
713  (defun %set-format-directive-expander (char fn)
714    (setf (aref *format-directive-expanders* (char-code (char-upcase char))) fn)
715    char)
716
717  (defun %set-format-directive-interpreter (char fn)
718    (setf (aref *format-directive-interpreters*
719                (char-code (char-upcase char)))
720          fn)
721    char)
722
723  (defun find-directive (directives kind stop-at-semi)
724    (if directives
725        (let ((next (car directives)))
726          (if (format-directive-p next)
727              (let ((char (format-directive-character next)))
728                (if (or (char= kind char)
729                        (and stop-at-semi (char= char #\;)))
730                    (car directives)
731                    (find-directive
732                     (cdr (flet ((after (char)
733                                   (member (find-directive (cdr directives)
734                                                           char
735                                                           nil)
736                                           directives)))
737                            (case char
738                              (#\( (after #\)))
739                              (#\< (after #\>))
740                              (#\[ (after #\]))
741                              (#\{ (after #\}))
742                              (t directives))))
743                     kind stop-at-semi)))
744              (find-directive (cdr directives) kind stop-at-semi)))))
745
746  ) ; EVAL-WHEN
747
748;;;; format directives for simple output
749
750(def-format-directive #\A (colonp atsignp params)
751  (if params
752      (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
753           (padchar #\space))
754                            params
755                            `(format-princ stream ,(expand-next-arg) ',colonp ',atsignp
756                                           ,mincol ,colinc ,minpad ,padchar))
757      `(princ ,(if colonp
758       `(or ,(expand-next-arg) "()")
759       (expand-next-arg))
760        stream)))
761
762(def-format-directive #\S (colonp atsignp params)
763  (cond (params
764   (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
765        (padchar #\space))
766                               params
767                               `(format-prin1 stream ,(expand-next-arg) ,colonp ,atsignp
768                                              ,mincol ,colinc ,minpad ,padchar)))
769  (colonp
770   `(let ((arg ,(expand-next-arg)))
771      (if arg
772    (prin1 arg stream)
773    (princ "()" stream))))
774  (t
775   `(prin1 ,(expand-next-arg) stream))))
776
777(def-format-directive #\C (colonp atsignp params)
778  (expand-bind-defaults () params
779                        (if colonp
780                            `(format-print-named-character ,(expand-next-arg) stream)
781                            (if atsignp
782                                `(prin1 ,(expand-next-arg) stream)
783                                `(write-char ,(expand-next-arg) stream)))))
784
785(def-format-directive #\W (colonp atsignp params)
786  (expand-bind-defaults () params
787                        (if (or colonp atsignp)
788                            `(let (,@(when colonp
789                                       '((*print-pretty* t)))
790                                   ,@(when atsignp
791                                       '((*print-level* nil)
792                                         (*print-length* nil))))
793                               (sys::output-object ,(expand-next-arg) stream))
794                            `(sys::output-object ,(expand-next-arg) stream))))
795
796;;;; format directives for integer output
797
798(defun expand-format-integer (base colonp atsignp params)
799  (if (or colonp atsignp params)
800      (expand-bind-defaults
801       ((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
802       params
803       `(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
804                              ,base ,mincol ,padchar ,commachar
805                              ,commainterval))
806      `(write ,(expand-next-arg) :stream stream :base ,base :radix nil
807        :escape nil)))
808
809(def-format-directive #\D (colonp atsignp params)
810  (expand-format-integer 10 colonp atsignp params))
811
812(def-format-directive #\B (colonp atsignp params)
813  (expand-format-integer 2 colonp atsignp params))
814
815(def-format-directive #\O (colonp atsignp params)
816  (expand-format-integer 8 colonp atsignp params))
817
818(def-format-directive #\X (colonp atsignp params)
819  (expand-format-integer 16 colonp atsignp params))
820
821(def-format-directive #\R (colonp atsignp params)
822  (expand-bind-defaults
823   ((base nil) (mincol 0) (padchar #\space) (commachar #\,)
824    (commainterval 3))
825   params
826   (let ((n-arg (gensym)))
827     `(let ((,n-arg ,(expand-next-arg)))
828        (if ,base
829            (format-print-integer stream ,n-arg ,colonp ,atsignp
830                                  ,base ,mincol
831                                  ,padchar ,commachar ,commainterval)
832            ,(if atsignp
833                 (if colonp
834                     `(format-print-old-roman stream ,n-arg)
835                     `(format-print-roman stream ,n-arg))
836                 (if colonp
837                     `(format-print-ordinal stream ,n-arg)
838                     `(format-print-cardinal stream ,n-arg))))))))
839
840;;;; format directive for pluralization
841
842(def-format-directive #\P (colonp atsignp params end)
843  (expand-bind-defaults () params
844                        (let ((arg (cond
845                                    ((not colonp)
846                                     (expand-next-arg))
847                                    (*orig-args-available*
848                                     `(if (eq orig-args args)
849                                          (error 'format-error
850                                                 :complaint "no previous argument"
851                                                 :offset ,(1- end))
852                                          (do ((arg-ptr orig-args (cdr arg-ptr)))
853                                              ((eq (cdr arg-ptr) args)
854                                               (car arg-ptr)))))
855                                    (*only-simple-args*
856                                     (unless *simple-args*
857                                       (error 'format-error
858                                              :complaint "no previous argument"))
859                                     (caar *simple-args*))
860                                    (t
861                                     (throw 'need-orig-args nil)))))
862                          (if atsignp
863                              `(write-string (if (eql ,arg 1) "y" "ies") stream)
864                              `(unless (eql ,arg 1) (write-char #\s stream))))))
865
866;;;; format directives for floating point output
867
868(def-format-directive #\F (colonp atsignp params)
869  (when colonp
870    (error 'format-error
871     :complaint
872     "The colon modifier cannot be used with this directive."))
873  (expand-bind-defaults ((w nil) (d nil) (k nil) (ovf nil) (pad #\space)) params
874                        `(format-fixed stream ,(expand-next-arg) ,w ,d ,k ,ovf ,pad ,atsignp)))
875
876(def-format-directive #\E (colonp atsignp params)
877  (when colonp
878    (error 'format-error
879     :complaint
880     "The colon modifier cannot be used with this directive."))
881  (expand-bind-defaults
882   ((w nil) (d nil) (e nil) (k 1) (ovf nil) (pad #\space) (mark nil))
883   params
884   `(format-exponential stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark
885                        ,atsignp)))
886
887(def-format-directive #\G (colonp atsignp params)
888  (when colonp
889    (error 'format-error
890     :complaint
891     "The colon modifier cannot be used with this directive."))
892  (expand-bind-defaults
893   ((w nil) (d nil) (e nil) (k nil) (ovf nil) (pad #\space) (mark nil))
894   params
895   `(format-general stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark ,atsignp)))
896
897(def-format-directive #\$ (colonp atsignp params)
898  (expand-bind-defaults ((d 2) (n 1) (w 0) (pad #\space)) params
899                        `(format-dollars stream ,(expand-next-arg) ,d ,n ,w ,pad ,colonp
900                                         ,atsignp)))
901
902;;;; format directives for line/page breaks etc.
903
904(def-format-directive #\% (colonp atsignp params)
905  (when (or colonp atsignp)
906    (error 'format-error
907     :complaint
908     "The colon and atsign modifiers cannot be used with this directive."
909     ))
910  (if params
911      (expand-bind-defaults ((count 1)) params
912                            `(dotimes (i ,count)
913                               (terpri stream)))
914      '(terpri stream)))
915
916(def-format-directive #\& (colonp atsignp params)
917  (when (or colonp atsignp)
918    (error 'format-error
919     :complaint
920     "The colon and atsign modifiers cannot be used with this directive."
921     ))
922  (if params
923      (expand-bind-defaults ((count 1)) params
924                            `(progn
925                               (fresh-line stream)
926                               (dotimes (i (1- ,count))
927                                 (terpri stream))))
928      '(fresh-line stream)))
929
930(def-format-directive #\| (colonp atsignp params)
931  (when (or colonp atsignp)
932    (error 'format-error
933     :complaint
934     "The colon and atsign modifiers cannot be used with this directive."
935     ))
936  (if params
937      (expand-bind-defaults ((count 1)) params
938                            `(dotimes (i ,count)
939                               (write-char (code-char sys::form-feed-char-code) stream)))
940      '(write-char (code-char sys::form-feed-char-code) stream)))
941
942(def-format-directive #\~ (colonp atsignp params)
943  (when (or colonp atsignp)
944    (error 'format-error
945     :complaint
946     "The colon and atsign modifiers cannot be used with this directive."
947     ))
948  (if params
949      (expand-bind-defaults ((count 1)) params
950                            `(dotimes (i ,count)
951                               (write-char #\~ stream)))
952      '(write-char #\~ stream)))
953
954(def-complex-format-directive #\newline (colonp atsignp params directives)
955  (when (and colonp atsignp)
956    (error 'format-error
957     :complaint "both colon and atsign modifiers used simultaneously"))
958  (values (expand-bind-defaults () params
959                                (if atsignp
960                                    '(write-char #\newline stream)
961                                    nil))
962    (if (and (not colonp)
963       directives
964       (simple-string-p (car directives)))
965        (cons (string-left-trim *format-whitespace-chars*
966              (car directives))
967        (cdr directives))
968        directives)))
969
970;;;; format directives for tabs and simple pretty printing
971
972(def-format-directive #\T (colonp atsignp params)
973  (if colonp
974      (expand-bind-defaults ((n 1) (m 1)) params
975                            `(pprint-tab ,(if atsignp :section-relative :section)
976                                         ,n ,m stream))
977      (if atsignp
978    (expand-bind-defaults ((colrel 1) (colinc 1)) params
979                                `(format-relative-tab stream ,colrel ,colinc))
980    (expand-bind-defaults ((colnum 1) (colinc 1)) params
981                                `(format-absolute-tab stream ,colnum ,colinc)))))
982
983(def-format-directive #\_ (colonp atsignp params)
984  (expand-bind-defaults () params
985                        `(pprint-newline ,(if colonp
986                                              (if atsignp
987                                                  :mandatory
988                                                  :fill)
989                                              (if atsignp
990                                                  :miser
991                                                  :linear))
992                                         stream)))
993
994(def-format-directive #\I (colonp atsignp params)
995  (when atsignp
996    (error 'format-error
997     :complaint
998     "cannot use the at-sign modifier with this directive"))
999  (expand-bind-defaults ((n 0)) params
1000                        `(pprint-indent ,(if colonp :current :block) ,n stream)))
1001
1002;;;; format directive for ~*
1003
1004(def-format-directive #\* (colonp atsignp params end)
1005  (if atsignp
1006      (if colonp
1007    (error 'format-error
1008     :complaint
1009     "both colon and atsign modifiers used simultaneously")
1010    (expand-bind-defaults ((posn 0)) params
1011                                (unless *orig-args-available*
1012                                  (throw 'need-orig-args nil))
1013                                `(if (<= 0 ,posn (length orig-args))
1014                                     (setf args (nthcdr ,posn orig-args))
1015                                     (error 'format-error
1016                                            :complaint "Index ~W out of bounds. Should have been ~
1017                                            between 0 and ~W."
1018                                            :args (list ,posn (length orig-args))
1019                                            :offset ,(1- end)))))
1020      (if colonp
1021    (expand-bind-defaults ((n 1)) params
1022                                (unless *orig-args-available*
1023                                  (throw 'need-orig-args nil))
1024                                `(do ((cur-posn 0 (1+ cur-posn))
1025                                      (arg-ptr orig-args (cdr arg-ptr)))
1026                                     ((eq arg-ptr args)
1027                                      (let ((new-posn (- cur-posn ,n)))
1028                                        (if (<= 0 new-posn (length orig-args))
1029                                            (setf args (nthcdr new-posn orig-args))
1030                                            (error 'format-error
1031                                                   :complaint
1032                                                   "Index ~W is out of bounds; should have been ~
1033                                                    between 0 and ~W."
1034                                                   :args (list new-posn (length orig-args))
1035                                                   :offset ,(1- end)))))))
1036    (if params
1037        (expand-bind-defaults ((n 1)) params
1038                                    (setf *only-simple-args* nil)
1039                                    `(dotimes (i ,n)
1040                                       ,(expand-next-arg)))
1041        (expand-next-arg)))))
1042
1043;;;; format directive for indirection
1044
1045(def-format-directive #\? (colonp atsignp params string end)
1046  (when colonp
1047    (error 'format-error
1048     :complaint "cannot use the colon modifier with this directive"))
1049  (expand-bind-defaults () params
1050                        `(handler-bind
1051                           ((format-error
1052                             (lambda (condition)
1053                               (error 'format-error
1054                                      :complaint
1055                                      "~A~%while processing indirect format string:"
1056                                      :args (list condition)
1057                                      :print-banner nil
1058                                      :control-string ,string
1059                                      :offset ,(1- end)))))
1060                           ,(if atsignp
1061                                (if *orig-args-available*
1062                                    `(setf args (%format stream ,(expand-next-arg) orig-args args))
1063                                    (throw 'need-orig-args nil))
1064                                `(%format stream ,(expand-next-arg) ,(expand-next-arg))))))
1065
1066;;;; format directives for capitalization
1067
1068(def-complex-format-directive #\( (colonp atsignp params directives)
1069  (let ((close (find-directive directives #\) nil)))
1070    (unless close
1071      (error 'format-error
1072       :complaint "no corresponding close parenthesis"))
1073    (let* ((posn (position close directives))
1074     (before (subseq directives 0 posn))
1075     (after (nthcdr (1+ posn) directives)))
1076      (values
1077       (expand-bind-defaults () params
1078                             `(let ((stream (sys::make-case-frob-stream stream
1079                                                                        ,(if colonp
1080                                                                             (if atsignp
1081                                                                                 :upcase
1082                                                                                 :capitalize)
1083                                                                             (if atsignp
1084                                                                                 :capitalize-first
1085                                                                                 :downcase)))))
1086                                ,@(expand-directive-list before)))
1087       after))))
1088
1089(def-complex-format-directive #\) ()
1090  (error 'format-error
1091   :complaint "no corresponding open parenthesis"))
1092
1093;;;; format directives and support functions for conditionalization
1094
1095(def-complex-format-directive #\[ (colonp atsignp params directives)
1096  (multiple-value-bind (sublists last-semi-with-colon-p remaining)
1097      (parse-conditional-directive directives)
1098    (values
1099     (if atsignp
1100   (if colonp
1101       (error 'format-error
1102        :complaint
1103        "both colon and atsign modifiers used simultaneously")
1104       (if (cdr sublists)
1105     (error 'format-error
1106      :complaint
1107      "Can only specify one section")
1108     (expand-bind-defaults () params
1109                   (expand-maybe-conditional (car sublists)))))
1110   (if colonp
1111       (if (= (length sublists) 2)
1112     (expand-bind-defaults () params
1113                   (expand-true-false-conditional (car sublists)
1114                                                  (cadr sublists)))
1115     (error 'format-error
1116      :complaint
1117      "must specify exactly two sections"))
1118       (expand-bind-defaults ((index nil)) params
1119               (setf *only-simple-args* nil)
1120               (let ((clauses nil)
1121                     (case `(or ,index ,(expand-next-arg))))
1122                 (when last-semi-with-colon-p
1123                   (push `(t ,@(expand-directive-list (pop sublists)))
1124                         clauses))
1125                 (let ((count (length sublists)))
1126                   (dolist (sublist sublists)
1127                     (push `(,(decf count)
1128                             ,@(expand-directive-list sublist))
1129                           clauses)))
1130                 `(case ,case ,@clauses)))))
1131     remaining)))
1132
1133(defun parse-conditional-directive (directives)
1134  (let ((sublists nil)
1135  (last-semi-with-colon-p nil)
1136  (remaining directives))
1137    (loop
1138      (let ((close-or-semi (find-directive remaining #\] t)))
1139  (unless close-or-semi
1140    (error 'format-error
1141     :complaint "no corresponding close bracket"))
1142  (let ((posn (position close-or-semi remaining)))
1143    (push (subseq remaining 0 posn) sublists)
1144    (setf remaining (nthcdr (1+ posn) remaining))
1145    (when (char= (format-directive-character close-or-semi) #\])
1146      (return))
1147    (setf last-semi-with-colon-p
1148    (format-directive-colonp close-or-semi)))))
1149    (values sublists last-semi-with-colon-p remaining)))
1150
1151(defun expand-maybe-conditional (sublist)
1152  (flet ((hairy ()
1153           `(let ((prev-args args)
1154                  (arg ,(expand-next-arg)))
1155              (when arg
1156                (setf args prev-args)
1157                ,@(expand-directive-list sublist)))))
1158    (if *only-simple-args*
1159  (multiple-value-bind (guts new-args)
1160            (let ((*simple-args* *simple-args*))
1161              (values (expand-directive-list sublist)
1162                      *simple-args*))
1163    (cond ((and new-args (eq *simple-args* (cdr new-args)))
1164     (setf *simple-args* new-args)
1165     `(when ,(caar new-args)
1166        ,@guts))
1167    (t
1168     (setf *only-simple-args* nil)
1169     (hairy))))
1170  (hairy))))
1171
1172(defun expand-true-false-conditional (true false)
1173  (let ((arg (expand-next-arg)))
1174    (flet ((hairy ()
1175             `(if ,arg
1176                  (progn
1177                    ,@(expand-directive-list true))
1178                  (progn
1179                    ,@(expand-directive-list false)))))
1180      (if *only-simple-args*
1181    (multiple-value-bind (true-guts true-args true-simple)
1182            (let ((*simple-args* *simple-args*)
1183                  (*only-simple-args* t))
1184              (values (expand-directive-list true)
1185                      *simple-args*
1186                      *only-simple-args*))
1187      (multiple-value-bind (false-guts false-args false-simple)
1188              (let ((*simple-args* *simple-args*)
1189                    (*only-simple-args* t))
1190                (values (expand-directive-list false)
1191                        *simple-args*
1192                        *only-simple-args*))
1193        (if (= (length true-args) (length false-args))
1194      `(if ,arg
1195           (progn
1196       ,@true-guts)
1197           ,(do ((false false-args (cdr false))
1198           (true true-args (cdr true))
1199           (bindings nil (cons `(,(caar false) ,(caar true))
1200             bindings)))
1201          ((eq true *simple-args*)
1202           (setf *simple-args* true-args)
1203           (setf *only-simple-args*
1204           (and true-simple false-simple))
1205           (if bindings
1206         `(let ,bindings
1207            ,@false-guts)
1208         `(progn
1209            ,@false-guts)))))
1210      (progn
1211        (setf *only-simple-args* nil)
1212        (hairy)))))
1213    (hairy)))))
1214
1215(def-complex-format-directive #\; ()
1216  (error 'format-error
1217   :complaint
1218   "~~; directive not contained within either ~~[...~~] or ~~<...~~>"))
1219
1220(def-complex-format-directive #\] ()
1221  (error 'format-error
1222   :complaint
1223   "no corresponding open bracket"))
1224
1225;;;; format directive for up-and-out
1226
1227(def-format-directive #\^ (colonp atsignp params)
1228  (when atsignp
1229    (error 'format-error
1230     :complaint "cannot use the at-sign modifier with this directive"))
1231  (when (and colonp (not *up-up-and-out-allowed*))
1232    (error 'format-error
1233     :complaint "attempt to use ~~:^ outside a ~~:{...~~} construct"))
1234  `(when ,(expand-bind-defaults ((arg1 nil) (arg2 nil) (arg3 nil)) params
1235                                `(cond (,arg3 (<= ,arg1 ,arg2 ,arg3))
1236                                       (,arg2 (eql ,arg1 ,arg2))
1237                                       (,arg1 (eql ,arg1 0))
1238                                       (t ,(if colonp
1239                                               '(null outside-args)
1240                                               (progn
1241                                                 (setf *only-simple-args* nil)
1242                                                 '(null args))))))
1243     ,(if colonp
1244    '(return-from outside-loop nil)
1245    '(return))))
1246
1247;;;; format directives for iteration
1248
1249(def-complex-format-directive #\{ (colonp atsignp params string end directives)
1250  (let ((close (find-directive directives #\} nil)))
1251    (unless close
1252      (error 'format-error
1253       :complaint "no corresponding close brace"))
1254    (let* ((closed-with-colon (format-directive-colonp close))
1255     (posn (position close directives)))
1256      (labels
1257        ((compute-insides ()
1258           (if (zerop posn)
1259               (if *orig-args-available*
1260                   `((handler-bind
1261                       ((format-error
1262                         (lambda (condition)
1263                           (error 'format-error
1264                                  :complaint
1265                                  "~A~%while processing indirect format string:"
1266                                  :args (list condition)
1267                                  :print-banner nil
1268                                  :control-string ,string
1269                                  :offset ,(1- end)))))
1270                       (setf args
1271                             (%format stream inside-string orig-args args))))
1272                   (throw 'need-orig-args nil))
1273               (let ((*up-up-and-out-allowed* colonp))
1274                 (expand-directive-list (subseq directives 0 posn)))))
1275         (compute-loop (count)
1276           (when atsignp
1277             (setf *only-simple-args* nil))
1278           `(loop
1279              ,@(unless closed-with-colon
1280                  '((when (null args)
1281                      (return))))
1282              ,@(when count
1283                  `((when (and ,count (minusp (decf ,count)))
1284                      (return))))
1285              ,@(if colonp
1286                    (let ((*expander-next-arg-macro* 'expander-next-arg)
1287                          (*only-simple-args* nil)
1288                          (*orig-args-available* t))
1289                      `((let* ((orig-args ,(expand-next-arg))
1290                               (outside-args args)
1291                               (args orig-args))
1292                          (declare (ignorable orig-args outside-args args))
1293                          (block nil
1294                            ,@(compute-insides)))))
1295                    (compute-insides))
1296              ,@(when closed-with-colon
1297                  '((when (null args)
1298                      (return))))))
1299         (compute-block (count)
1300           (if colonp
1301               `(block outside-loop
1302                  ,(compute-loop count))
1303               (compute-loop count)))
1304         (compute-bindings (count)
1305            (if atsignp
1306                (compute-block count)
1307                `(let* ((orig-args ,(expand-next-arg))
1308                        (args orig-args))
1309                   (declare (ignorable orig-args args))
1310                   ,(let ((*expander-next-arg-macro* 'expander-next-arg)
1311                          (*only-simple-args* nil)
1312                          (*orig-args-available* t))
1313                      (compute-block count))))))
1314  (values (if params
1315                    (expand-bind-defaults ((count nil)) params
1316                                          (if (zerop posn)
1317                                              `(let ((inside-string ,(expand-next-arg)))
1318                                                 ,(compute-bindings count))
1319                                              (compute-bindings count)))
1320                    (if (zerop posn)
1321                        `(let ((inside-string ,(expand-next-arg)))
1322                           ,(compute-bindings nil))
1323                        (compute-bindings nil)))
1324    (nthcdr (1+ posn) directives))))))
1325
1326(def-complex-format-directive #\} ()
1327  (error 'format-error
1328   :complaint "no corresponding open brace"))
1329
1330;;;; format directives and support functions for justification
1331
1332(defparameter *illegal-inside-justification*
1333  (mapcar (lambda (x) (parse-directive x 0))
1334    '("~W" "~:W" "~@W" "~:@W"
1335      "~_" "~:_" "~@_" "~:@_"
1336      "~:>" "~:@>"
1337      "~I" "~:I" "~@I" "~:@I"
1338      "~:T" "~:@T")))
1339
1340(defun illegal-inside-justification-p (directive)
1341  (member directive *illegal-inside-justification*
1342    :test (lambda (x y)
1343      (and (format-directive-p x)
1344           (format-directive-p y)
1345           (eql (format-directive-character x) (format-directive-character y))
1346           (eql (format-directive-colonp x) (format-directive-colonp y))
1347           (eql (format-directive-atsignp x) (format-directive-atsignp y))))))
1348
1349(def-complex-format-directive #\< (colonp atsignp params string end directives)
1350  (multiple-value-bind (segments first-semi close remaining)
1351    (parse-format-justification directives)
1352    (values
1353     (if (format-directive-colonp close)
1354   (multiple-value-bind (prefix per-line-p insides suffix)
1355           (parse-format-logical-block segments colonp first-semi
1356                                       close params string end)
1357     (expand-format-logical-block prefix per-line-p insides
1358          suffix atsignp))
1359   (let ((count (reduce #'+ (mapcar (lambda (x) (count-if #'illegal-inside-justification-p x)) segments))))
1360     (when (> count 0)
1361       ;; ANSI specifies that "an error is signalled" in this
1362       ;; situation.
1363       (error 'format-error
1364        :complaint "~D illegal directive~:P found inside justification block"
1365        :args (list count)))
1366     (expand-format-justification segments colonp atsignp
1367                                        first-semi params)))
1368     remaining)))
1369
1370(def-complex-format-directive #\> ()
1371  (error 'format-error
1372   :complaint "no corresponding open bracket"))
1373
1374(defun parse-format-logical-block
1375  (segments colonp first-semi close params string end)
1376  (when params
1377    (error 'format-error
1378     :complaint "No parameters can be supplied with ~~<...~~:>."
1379     :offset (caar params)))
1380  (multiple-value-bind (prefix insides suffix)
1381    (multiple-value-bind (prefix-default suffix-default)
1382      (if colonp (values "(" ")") (values "" ""))
1383      (flet ((extract-string (list prefix-p)
1384                             (let ((directive (find-if #'format-directive-p list)))
1385                               (if directive
1386                                   (error 'format-error
1387                                          :complaint
1388                                          "cannot include format directives inside the ~
1389                                           ~:[suffix~;prefix~] segment of ~~<...~~:>"
1390                                          :args (list prefix-p)
1391                                          :offset (1- (format-directive-end directive)))
1392                                   (apply #'concatenate 'string list)))))
1393  (case (length segments)
1394    (0 (values prefix-default nil suffix-default))
1395    (1 (values prefix-default (car segments) suffix-default))
1396    (2 (values (extract-string (car segments) t)
1397         (cadr segments) suffix-default))
1398    (3 (values (extract-string (car segments) t)
1399         (cadr segments)
1400         (extract-string (caddr segments) nil)))
1401    (t
1402     (error 'format-error
1403      :complaint "too many segments for ~~<...~~:>")))))
1404    (when (format-directive-atsignp close)
1405      (setf insides
1406      (add-fill-style-newlines insides
1407             string
1408             (if first-semi
1409           (format-directive-end first-semi)
1410           end))))
1411    (values prefix
1412      (and first-semi (format-directive-atsignp first-semi))
1413      insides
1414      suffix)))
1415
1416(defun add-fill-style-newlines (list string offset &optional last-directive)
1417  (cond
1418   (list
1419    (let ((directive (car list)))
1420      (cond
1421       ((simple-string-p directive)
1422        (let* ((non-space (position #\Space directive :test #'char/=))
1423               (newlinep (and last-directive
1424                              (char=
1425                               (format-directive-character last-directive)
1426                               #\Newline))))
1427          (cond
1428           ((and newlinep non-space)
1429            (nconc
1430             (list (subseq directive 0 non-space))
1431             (add-fill-style-newlines-aux
1432              (subseq directive non-space) string (+ offset non-space))
1433             (add-fill-style-newlines
1434              (cdr list) string (+ offset (length directive)))))
1435           (newlinep
1436            (cons directive
1437                  (add-fill-style-newlines
1438                   (cdr list) string (+ offset (length directive)))))
1439           (t
1440            (nconc (add-fill-style-newlines-aux directive string offset)
1441                   (add-fill-style-newlines
1442                    (cdr list) string (+ offset (length directive))))))))
1443       (t
1444        (cons directive
1445              (add-fill-style-newlines
1446               (cdr list) string
1447               (format-directive-end directive) directive))))))
1448   (t nil)))
1449
1450(defun add-fill-style-newlines-aux (literal string offset)
1451  (let ((end (length literal))
1452  (posn 0))
1453    (collect ((results))
1454             (loop
1455               (let ((blank (position #\space literal :start posn)))
1456                 (when (null blank)
1457                   (results (subseq literal posn))
1458                   (return))
1459                 (let ((non-blank (or (position #\space literal :start blank
1460                                                :test #'char/=)
1461                                      end)))
1462                   (results (subseq literal posn non-blank))
1463                   (results (make-format-directive
1464                             :string string :character #\_
1465                             :start (+ offset non-blank) :end (+ offset non-blank)
1466                             :colonp t :atsignp nil :params nil))
1467                   (setf posn non-blank))
1468                 (when (= posn end)
1469                   (return))))
1470             (results))))
1471
1472(defun parse-format-justification (directives)
1473  (let ((first-semi nil)
1474  (close nil)
1475  (remaining directives))
1476    (collect ((segments))
1477             (loop
1478               (let ((close-or-semi (find-directive remaining #\> t)))
1479                 (unless close-or-semi
1480                   (error 'format-error
1481                          :complaint "no corresponding close bracket"))
1482                 (let ((posn (position close-or-semi remaining)))
1483                   (segments (subseq remaining 0 posn))
1484                   (setf remaining (nthcdr (1+ posn) remaining)))
1485                 (when (char= (format-directive-character close-or-semi)
1486                              #\>)
1487                   (setf close close-or-semi)
1488                   (return))
1489                 (unless first-semi
1490                   (setf first-semi close-or-semi))))
1491             (values (segments) first-semi close remaining))))
1492
1493(defmacro expander-pprint-next-arg (string offset)
1494  `(progn
1495     (when (null args)
1496       (error 'format-error
1497        :complaint "no more arguments"
1498        :control-string ,string
1499        :offset ,offset))
1500     (pprint-pop)
1501     (pop args)))
1502
1503(defun expand-format-logical-block (prefix per-line-p insides suffix atsignp)
1504  `(let ((arg ,(if atsignp 'args (expand-next-arg))))
1505     ,@(when atsignp
1506   (setf *only-simple-args* nil)
1507   '((setf args nil)))
1508     (pprint-logical-block
1509      (stream arg
1510              ,(if per-line-p :per-line-prefix :prefix) ,prefix
1511              :suffix ,suffix)
1512      (let ((args arg)
1513            ,@(unless atsignp
1514                `((orig-args arg))))
1515        (declare (ignorable args ,@(unless atsignp '(orig-args))))
1516        (block nil
1517          ,@(let ((*expander-next-arg-macro* 'expander-pprint-next-arg)
1518                  (*only-simple-args* nil)
1519                  (*orig-args-available*
1520                   (if atsignp *orig-args-available* t)))
1521              (expand-directive-list insides)))))))
1522
1523(defun expand-format-justification (segments colonp atsignp first-semi params)
1524  (let ((newline-segment-p
1525   (and first-semi
1526        (format-directive-colonp first-semi))))
1527    (expand-bind-defaults
1528     ((mincol 0) (colinc 1) (minpad 0) (padchar #\space))
1529     params
1530     `(let ((segments nil)
1531            ,@(when newline-segment-p
1532                '((newline-segment nil)
1533                  (extra-space 0)
1534                  (line-len 72))))
1535        (block nil
1536          ,@(when newline-segment-p
1537              `((setf newline-segment
1538                      (with-output-to-string (stream)
1539                        ,@(expand-directive-list (pop segments))))
1540                ,(expand-bind-defaults
1541                  ((extra 0)
1542                   (line-len '(or #-abcl(sb!impl::line-length stream) 72)))
1543                  (format-directive-params first-semi)
1544                  `(setf extra-space ,extra line-len ,line-len))))
1545          ,@(mapcar (lambda (segment)
1546                      `(push (with-output-to-string (stream)
1547                               ,@(expand-directive-list segment))
1548                             segments))
1549                    segments))
1550        (format-justification stream
1551                              ,@(if newline-segment-p
1552                                    '(newline-segment extra-space line-len)
1553                                    '(nil 0 0))
1554                              segments ,colonp ,atsignp
1555                              ,mincol ,colinc ,minpad ,padchar)))))
1556
1557;;;; format directive and support function for user-defined method
1558
1559(def-format-directive #\/ (string start end colonp atsignp params)
1560  (let ((symbol (extract-user-fun-name string start end)))
1561    (collect ((param-names) (bindings))
1562             (dolist (param-and-offset params)
1563               (let ((param (cdr param-and-offset)))
1564                 (let ((param-name (gensym)))
1565                   (param-names param-name)
1566                   (bindings `(,param-name
1567                               ,(case param
1568                                  (:arg (expand-next-arg))
1569                                  (:remaining '(length args))
1570                                  (t param)))))))
1571             `(let ,(bindings)
1572                (,symbol stream ,(expand-next-arg) ,colonp ,atsignp
1573                 ,@(param-names))))))
1574
1575(defun extract-user-fun-name (string start end)
1576  (let ((slash (position #\/ string :start start :end (1- end)
1577       :from-end t)))
1578    (unless slash
1579      (error 'format-error
1580       :complaint "malformed ~~/ directive"))
1581    (let* ((name (string-upcase (let ((foo string))
1582          ;; Hack alert: This is to keep the compiler
1583          ;; quiet about deleting code inside the
1584          ;; subseq expansion.
1585          (subseq foo (1+ slash) (1- end)))))
1586     (first-colon (position #\: name))
1587     (second-colon (if first-colon (position #\: name :start (1+ first-colon))))
1588     (package-name (if first-colon
1589           (subseq name 0 first-colon)
1590           "COMMON-LISP-USER"))
1591     (package (find-package package-name)))
1592      (unless package
1593  ;; FIXME: should be PACKAGE-ERROR? Could we just use
1594  ;; FIND-UNDELETED-PACKAGE-OR-LOSE?
1595  (error 'format-error
1596         :complaint "no package named ~S"
1597         :args (list package-name)))
1598      (intern (cond
1599               ((and second-colon (= second-colon (1+ first-colon)))
1600                (subseq name (1+ second-colon)))
1601               (first-colon
1602                (subseq name (1+ first-colon)))
1603               (t name))
1604        package))))
1605
1606;;; compile-time checking for argument mismatch.  This code is
1607;;; inspired by that of Gerd Moellmann, and comes decorated with
1608;;; FIXMEs:
1609(defun %compiler-walk-format-string (string args)
1610  (declare (type simple-string string))
1611  (let ((*default-format-error-control-string* string))
1612    (macrolet ((incf-both (&optional (increment 1))
1613                          `(progn
1614                             (incf min ,increment)
1615                             (incf max ,increment)))
1616         (walk-complex-directive (function)
1617                                       `(multiple-value-bind (min-inc max-inc remaining)
1618                                          (,function directive directives args)
1619                                          (incf min min-inc)
1620                                          (incf max max-inc)
1621                                          (setq directives remaining))))
1622      ;; FIXME: these functions take a list of arguments as well as
1623      ;; the directive stream.  This is to enable possibly some
1624      ;; limited type checking on FORMAT's arguments, as well as
1625      ;; simple argument count mismatch checking: when the minimum and
1626      ;; maximum argument counts are the same at a given point, we
1627      ;; know which argument is going to be used for a given
1628      ;; directive, and some (annotated below) require arguments of
1629      ;; particular types.
1630      (labels
1631        ((walk-justification (justification directives args)
1632                             (declare (ignore args))
1633                             (let ((*default-format-error-offset*
1634                                    (1- (format-directive-end justification))))
1635                               (multiple-value-bind (segments first-semi close remaining)
1636                                 (parse-format-justification directives)
1637                                 (declare (ignore segments first-semi))
1638                                 (cond
1639                                  ((not (format-directive-colonp close))
1640                                   (values 0 0 directives))
1641                                  ((format-directive-atsignp justification)
1642                                   (values 0 call-arguments-limit directives))
1643                                  ;; FIXME: here we could assert that the
1644                                  ;; corresponding argument was a list.
1645                                  (t (values 1 1 remaining))))))
1646         (walk-conditional (conditional directives args)
1647                           (let ((*default-format-error-offset*
1648                                  (1- (format-directive-end conditional))))
1649                             (multiple-value-bind (sublists last-semi-with-colon-p remaining)
1650                               (parse-conditional-directive directives)
1651                               (declare (ignore last-semi-with-colon-p))
1652                               (let ((sub-max
1653                                      (loop for s in sublists
1654                                        maximize (nth-value
1655                                                  1 (walk-directive-list s args)))))
1656                                 (cond
1657                                  ((format-directive-atsignp conditional)
1658                                   (values 1 (max 1 sub-max) remaining))
1659                                  ((loop for p in (format-directive-params conditional)
1660                                     thereis (or (integerp (cdr p))
1661                                                 (memq (cdr p) '(:remaining :arg))))
1662                                   (values 0 sub-max remaining))
1663                                  ;; FIXME: if not COLONP, then the next argument
1664                                  ;; must be a number.
1665                                  (t (values 1 (1+ sub-max) remaining)))))))
1666         (walk-iteration (iteration directives args)
1667                         (declare (ignore args))
1668                         (let ((*default-format-error-offset*
1669                                (1- (format-directive-end iteration))))
1670                           (let* ((close (find-directive directives #\} nil))
1671                                  (posn (or (position close directives)
1672                                            (error 'format-error
1673                                                   :complaint "no corresponding close brace")))
1674                                  (remaining (nthcdr (1+ posn) directives)))
1675                             ;; FIXME: if POSN is zero, the next argument must be
1676                             ;; a format control (either a function or a string).
1677                             (if (format-directive-atsignp iteration)
1678                                 (values (if (zerop posn) 1 0)
1679                                         call-arguments-limit
1680                                         remaining)
1681                                 ;; FIXME: the argument corresponding to this
1682                                 ;; directive must be a list.
1683                                 (let ((nreq (if (zerop posn) 2 1)))
1684                                   (values nreq nreq remaining))))))
1685         (walk-directive-list (directives args)
1686                              (let ((min 0) (max 0))
1687                                (loop
1688                                  (let ((directive (pop directives)))
1689                                    (when (null directive)
1690                                      (return (values min (min max call-arguments-limit))))
1691                                    (when (format-directive-p directive)
1692                                      (incf-both (count :arg (format-directive-params directive)
1693                                                        :key #'cdr))
1694                                      (let ((c (format-directive-character directive)))
1695                                        (cond
1696                                         ((find c "ABCDEFGORSWX$/")
1697                                          (incf-both))
1698                                         ((char= c #\P)
1699                                          (unless (format-directive-colonp directive)
1700                                            (incf-both)))
1701                                         ((or (find c "IT%&|_();>") (char= c #\Newline)))
1702                                         ;; FIXME: check correspondence of ~( and ~)
1703                                         ((char= c #\<)
1704                                          (walk-complex-directive walk-justification))
1705                                         ((char= c #\[)
1706                                          (walk-complex-directive walk-conditional))
1707                                         ((char= c #\{)
1708                                          (walk-complex-directive walk-iteration))
1709                                         ((char= c #\?)
1710                                          ;; FIXME: the argument corresponding to this
1711                                          ;; directive must be a format control.
1712                                          (cond
1713                                           ((format-directive-atsignp directive)
1714                                            (incf min)
1715                                            (setq max call-arguments-limit))
1716                                           (t (incf-both 2))))
1717                                         (t (throw 'give-up-format-string-walk nil))))))))))
1718  (catch 'give-up-format-string-walk
1719    (let ((directives (tokenize-control-string string)))
1720      (walk-directive-list directives args)))))))
1721
1722;;; From target-format.lisp.
1723
1724(in-package #:format)
1725
1726(defun format (destination control-string &rest format-arguments)
1727  (etypecase destination
1728    (null
1729     (with-output-to-string (stream)
1730       (%format stream control-string format-arguments)))
1731    (string
1732     (with-output-to-string (stream destination)
1733       (%format stream control-string format-arguments)))
1734    ((member t)
1735     (%format *standard-output* control-string format-arguments)
1736     nil)
1737    ((or stream xp::xp-structure)
1738     (%format destination control-string format-arguments)
1739     nil)))
1740
1741(defun %format (stream string-or-fun orig-args &optional (args orig-args))
1742  (if (functionp string-or-fun)
1743      (apply string-or-fun stream args)
1744      (catch 'up-and-out
1745  (let* ((string (etypecase string-or-fun
1746       (simple-string
1747        string-or-fun)
1748       (string
1749        (coerce string-or-fun 'simple-string))))
1750         (*default-format-error-control-string* string)
1751         (*logical-block-popper* nil))
1752    (interpret-directive-list stream (tokenize-control-string string)
1753            orig-args args)))))
1754
1755(defun interpret-directive-list (stream directives orig-args args)
1756  (if directives
1757      (let ((directive (car directives)))
1758  (etypecase directive
1759    (simple-string
1760     (write-string directive stream)
1761     (interpret-directive-list stream (cdr directives) orig-args args))
1762    (format-directive
1763     (multiple-value-bind (new-directives new-args)
1764             (let* ((character (format-directive-character directive))
1765                    (function
1766                     (svref *format-directive-interpreters*
1767                            (char-code character)))
1768                    (*default-format-error-offset*
1769                     (1- (format-directive-end directive))))
1770               (unless function
1771                 (error 'format-error
1772                        :complaint "unknown format directive ~@[(character: ~A)~]"
1773                        :args (list (char-name character))))
1774               (multiple-value-bind (new-directives new-args)
1775                 (funcall function stream directive
1776                          (cdr directives) orig-args args)
1777                 (values new-directives new-args)))
1778       (interpret-directive-list stream new-directives
1779               orig-args new-args)))))
1780      args))
1781
1782;;;; FORMAT directive definition macros and runtime support
1783
1784(eval-when (:compile-toplevel :execute)
1785
1786  ;;; This macro is used to extract the next argument from the current arg list.
1787  ;;; This is the version used by format directive interpreters.
1788  (defmacro next-arg (&optional offset)
1789    `(progn
1790       (when (null args)
1791         (error 'format-error
1792                :complaint "no more arguments"
1793                ,@(when offset
1794                    `(:offset ,offset))))
1795       (when *logical-block-popper*
1796         (funcall *logical-block-popper*))
1797       (pop args)))
1798
1799  (defmacro def-complex-format-interpreter (char lambda-list &body body)
1800    (let ((defun-name
1801            (intern (concatenate 'string
1802                                 (let ((name (char-name char)))
1803                                   (cond (name
1804                                          (string-capitalize name))
1805                                         (t
1806                                          (string char))))
1807                                 "-FORMAT-DIRECTIVE-INTERPRETER")))
1808          (directive (gensym))
1809          (directives (if lambda-list (car (last lambda-list)) (gensym))))
1810      `(progn
1811         (defun ,defun-name (stream ,directive ,directives orig-args args)
1812           (declare (ignorable stream orig-args args))
1813           ,@(if lambda-list
1814                 `((let ,(mapcar (lambda (var)
1815                                   `(,var
1816                                     (,(sys::symbolicate "FORMAT-DIRECTIVE-" var)
1817                                      ,directive)))
1818                                 (butlast lambda-list))
1819                     (values (progn ,@body) args)))
1820                 `((declare (ignore ,directive ,directives))
1821                   ,@body)))
1822         (%set-format-directive-interpreter ,char #',defun-name))))
1823
1824  (defmacro def-format-interpreter (char lambda-list &body body)
1825    (let ((directives (gensym)))
1826      `(def-complex-format-interpreter ,char (,@lambda-list ,directives)
1827         ,@body
1828         ,directives)))
1829
1830  (defmacro interpret-bind-defaults (specs params &body body)
1831    (sys::once-only ((params params))
1832                    (collect ((bindings))
1833                             (dolist (spec specs)
1834                               (destructuring-bind (var default) spec
1835                                                   (bindings `(,var (let* ((param-and-offset (pop ,params))
1836                                                                           (offset (car param-and-offset))
1837                                                                           (param (cdr param-and-offset)))
1838                                                                      (case param
1839                                                                        (:arg (or (next-arg offset) ,default))
1840                                                                        (:remaining (length args))
1841                                                                        ((nil) ,default)
1842                                                                        (t param)))))))
1843                             `(let* ,(bindings)
1844                                (when ,params
1845                                  (error 'format-error
1846                                         :complaint
1847                                         "too many parameters, expected no more than ~W"
1848                                         :args (list ,(length specs))
1849                                         :offset (caar ,params)))
1850                                ,@body))))
1851
1852  ) ; EVAL-WHEN
1853
1854;;;; format interpreters and support functions for simple output
1855
1856(defun format-write-field (stream string mincol colinc minpad padchar padleft)
1857  (unless padleft
1858    (write-string string stream))
1859  (dotimes (i minpad)
1860    (write-char padchar stream))
1861  ;; As of sbcl-0.6.12.34, we could end up here when someone tries to
1862  ;; print e.g. (FORMAT T "~F" "NOTFLOAT"), in which case ANSI says
1863  ;; we're supposed to soldier on bravely, and so we have to deal with
1864  ;; the unsupplied-MINCOL-and-COLINC case without blowing up.
1865  (when (and mincol colinc)
1866    (do ((chars (+ (length string) (max minpad 0)) (+ chars colinc)))
1867  ((>= chars mincol))
1868      (dotimes (i colinc)
1869  (write-char padchar stream))))
1870  (when padleft
1871    (write-string string stream)))
1872
1873(defun format-princ (stream arg colonp atsignp mincol colinc minpad padchar)
1874  (format-write-field stream
1875          (if (or arg (not colonp))
1876        (princ-to-string arg)
1877        "()")
1878          mincol colinc minpad padchar atsignp))
1879
1880(def-format-interpreter #\A (colonp atsignp params)
1881  (if params
1882      (interpret-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
1883        (padchar #\space))
1884                               params
1885                               (format-princ stream (next-arg) colonp atsignp
1886                                             mincol colinc minpad padchar))
1887      (princ (if colonp (or (next-arg) "()") (next-arg)) stream)))
1888
1889(defun format-prin1 (stream arg colonp atsignp mincol colinc minpad padchar)
1890  (format-write-field stream
1891          (if (or arg (not colonp))
1892        (prin1-to-string arg)
1893        "()")
1894          mincol colinc minpad padchar atsignp))
1895
1896(def-format-interpreter #\S (colonp atsignp params)
1897  (cond (params
1898   (interpret-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
1899           (padchar #\space))
1900                                  params
1901                                  (format-prin1 stream (next-arg) colonp atsignp
1902                                                mincol colinc minpad padchar)))
1903  (colonp
1904   (let ((arg (next-arg)))
1905     (if arg
1906         (prin1 arg stream)
1907         (princ "()" stream))))
1908  (t
1909   (prin1 (next-arg) stream))))
1910
1911(def-format-interpreter #\C (colonp atsignp params)
1912  (interpret-bind-defaults () params
1913                           (if colonp
1914                               (format-print-named-character (next-arg) stream)
1915                               (if atsignp
1916                                   (prin1 (next-arg) stream)
1917                                   (write-char (next-arg) stream)))))
1918
1919(defun format-print-named-character (char stream)
1920  (let* ((name (char-name char)))
1921    (cond (name
1922     (write-string (string-capitalize name) stream))
1923    (t
1924     (write-char char stream)))))
1925
1926(def-format-interpreter #\W (colonp atsignp params)
1927  (interpret-bind-defaults () params
1928                           (let ((*print-pretty* (or colonp *print-pretty*))
1929                                 (*print-level* (unless atsignp *print-level*))
1930                                 (*print-length* (unless atsignp *print-length*)))
1931                             (sys::output-object (next-arg) stream))))
1932
1933;;;; format interpreters and support functions for integer output
1934
1935;;; FORMAT-PRINT-NUMBER does most of the work for the numeric printing
1936;;; directives. The parameters are interpreted as defined for ~D.
1937(defun format-print-integer (stream number print-commas-p print-sign-p
1938                                    radix mincol padchar commachar commainterval)
1939  (let ((*print-base* radix)
1940  (*print-radix* nil))
1941    (if (integerp number)
1942  (let* ((text (princ-to-string (abs number)))
1943         (commaed (if print-commas-p
1944          (format-add-commas text commachar commainterval)
1945          text))
1946         (signed (cond ((minusp number)
1947            (concatenate 'string "-" commaed))
1948           (print-sign-p
1949            (concatenate 'string "+" commaed))
1950           (t commaed))))
1951    ;; colinc = 1, minpad = 0, padleft = t
1952    (format-write-field stream signed mincol 1 0 padchar t))
1953  (princ number stream))))
1954
1955(defun format-add-commas (string commachar commainterval)
1956  (let ((length (length string)))
1957    (multiple-value-bind (commas extra) (truncate (1- length) commainterval)
1958      (let ((new-string (make-string (+ length commas)))
1959      (first-comma (1+ extra)))
1960  (replace new-string string :end1 first-comma :end2 first-comma)
1961  (do ((src first-comma (+ src commainterval))
1962       (dst first-comma (+ dst commainterval 1)))
1963      ((= src length))
1964    (setf (schar new-string dst) commachar)
1965    (replace new-string string :start1 (1+ dst)
1966       :start2 src :end2 (+ src commainterval)))
1967  new-string))))
1968
1969;;; FIXME: This is only needed in this file, could be defined with
1970;;; SB!XC:DEFMACRO inside EVAL-WHEN
1971(defmacro interpret-format-integer (base)
1972  `(if (or colonp atsignp params)
1973       (interpret-bind-defaults
1974        ((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
1975        params
1976        (format-print-integer stream (next-arg) colonp atsignp ,base mincol
1977                              padchar commachar commainterval))
1978       (write (next-arg) :stream stream :base ,base :radix nil :escape nil)))
1979
1980(def-format-interpreter #\D (colonp atsignp params)
1981  (interpret-format-integer 10))
1982
1983(def-format-interpreter #\B (colonp atsignp params)
1984  (interpret-format-integer 2))
1985
1986(def-format-interpreter #\O (colonp atsignp params)
1987  (interpret-format-integer 8))
1988
1989(def-format-interpreter #\X (colonp atsignp params)
1990  (interpret-format-integer 16))
1991
1992(def-format-interpreter #\R (colonp atsignp params)
1993  (interpret-bind-defaults
1994   ((base nil) (mincol 0) (padchar #\space) (commachar #\,)
1995    (commainterval 3))
1996   params
1997   (let ((arg (next-arg)))
1998     (if base
1999         (format-print-integer stream arg colonp atsignp base mincol
2000                               padchar commachar commainterval)
2001         (if atsignp
2002             (if colonp
2003                 (format-print-old-roman stream arg)
2004                 (format-print-roman stream arg))
2005             (if colonp
2006                 (format-print-ordinal stream arg)
2007                 (format-print-cardinal stream arg)))))))
2008
2009(defparameter *cardinal-ones*
2010  #(nil "one" "two" "three" "four" "five" "six" "seven" "eight" "nine"))
2011
2012(defparameter *cardinal-tens*
2013  #(nil nil "twenty" "thirty" "forty"
2014  "fifty" "sixty" "seventy" "eighty" "ninety"))
2015
2016(defparameter *cardinal-teens*
2017  #("ten" "eleven" "twelve" "thirteen" "fourteen"  ;;; RAD
2018          "fifteen" "sixteen" "seventeen" "eighteen" "nineteen"))
2019
2020(defparameter *cardinal-periods*
2021  #("" " thousand" " million" " billion" " trillion" " quadrillion"
2022       " quintillion" " sextillion" " septillion" " octillion" " nonillion"
2023       " decillion" " undecillion" " duodecillion" " tredecillion"
2024       " quattuordecillion" " quindecillion" " sexdecillion" " septendecillion"
2025       " octodecillion" " novemdecillion" " vigintillion"))
2026
2027(defparameter *ordinal-ones*
2028  #(nil "first" "second" "third" "fourth"
2029  "fifth" "sixth" "seventh" "eighth" "ninth"))
2030
2031(defparameter *ordinal-tens*
2032  #(nil "tenth" "twentieth" "thirtieth" "fortieth"
2033  "fiftieth" "sixtieth" "seventieth" "eightieth" "ninetieth"))
2034
2035(defun format-print-small-cardinal (stream n)
2036  (multiple-value-bind (hundreds rem) (truncate n 100)
2037    (when (plusp hundreds)
2038      (write-string (svref *cardinal-ones* hundreds) stream)
2039      (write-string " hundred" stream)
2040      (when (plusp rem)
2041  (write-char #\space stream)))
2042    (when (plusp rem)
2043      (multiple-value-bind (tens ones) (truncate rem 10)
2044  (cond ((< 1 tens)
2045               (write-string (svref *cardinal-tens* tens) stream)
2046               (when (plusp ones)
2047                 (write-char #\- stream)
2048                 (write-string (svref *cardinal-ones* ones) stream)))
2049              ((= tens 1)
2050               (write-string (svref *cardinal-teens* ones) stream))
2051              ((plusp ones)
2052               (write-string (svref *cardinal-ones* ones) stream)))))))
2053
2054(defun format-print-cardinal (stream n)
2055  (cond ((minusp n)
2056   (write-string "negative " stream)
2057   (format-print-cardinal-aux stream (- n) 0 n))
2058  ((zerop n)
2059   (write-string "zero" stream))
2060  (t
2061   (format-print-cardinal-aux stream n 0 n))))
2062
2063(defun format-print-cardinal-aux (stream n period err)
2064  (multiple-value-bind (beyond here) (truncate n 1000)
2065    (unless (<= period 20)
2066      (error "number too large to print in English: ~:D" err))
2067    (unless (zerop beyond)
2068      (format-print-cardinal-aux stream beyond (1+ period) err))
2069    (unless (zerop here)
2070      (unless (zerop beyond)
2071  (write-char #\space stream))
2072      (format-print-small-cardinal stream here)
2073      (write-string (svref *cardinal-periods* period) stream))))
2074
2075(defun format-print-ordinal (stream n)
2076  (when (minusp n)
2077    (write-string "negative " stream))
2078  (let ((number (abs n)))
2079    (multiple-value-bind (top bot) (truncate number 100)
2080      (unless (zerop top)
2081  (format-print-cardinal stream (- number bot)))
2082      (when (and (plusp top) (plusp bot))
2083  (write-char #\space stream))
2084      (multiple-value-bind (tens ones) (truncate bot 10)
2085  (cond ((= bot 12) (write-string "twelfth" stream))
2086        ((= tens 1)
2087         (write-string (svref *cardinal-teens* ones) stream);;;RAD
2088         (write-string "th" stream))
2089        ((and (zerop tens) (plusp ones))
2090         (write-string (svref *ordinal-ones* ones) stream))
2091        ((and (zerop ones)(plusp tens))
2092         (write-string (svref *ordinal-tens* tens) stream))
2093        ((plusp bot)
2094         (write-string (svref *cardinal-tens* tens) stream)
2095         (write-char #\- stream)
2096         (write-string (svref *ordinal-ones* ones) stream))
2097        ((plusp number)
2098         (write-string "th" stream))
2099        (t
2100         (write-string "zeroth" stream)))))))
2101
2102;;; Print Roman numerals
2103
2104(defun format-print-old-roman (stream n)
2105  (unless (< 0 n 5000)
2106    (error "Number too large to print in old Roman numerals: ~:D" n))
2107  (do ((char-list '(#\D #\C #\L #\X #\V #\I) (cdr char-list))
2108       (val-list '(500 100 50 10 5 1) (cdr val-list))
2109       (cur-char #\M (car char-list))
2110       (cur-val 1000 (car val-list))
2111       (start n (do ((i start (progn
2112        (write-char cur-char stream)
2113        (- i cur-val))))
2114        ((< i cur-val) i))))
2115      ((zerop start))))
2116
2117(defun format-print-roman (stream n)
2118  (unless (< 0 n 4000)
2119    (error "Number too large to print in Roman numerals: ~:D" n))
2120  (do ((char-list '(#\D #\C #\L #\X #\V #\I) (cdr char-list))
2121       (val-list '(500 100 50 10 5 1) (cdr val-list))
2122       (sub-chars '(#\C #\X #\X #\I #\I) (cdr sub-chars))
2123       (sub-val '(100 10 10 1 1 0) (cdr sub-val))
2124       (cur-char #\M (car char-list))
2125       (cur-val 1000 (car val-list))
2126       (cur-sub-char #\C (car sub-chars))
2127       (cur-sub-val 100 (car sub-val))
2128       (start n (do ((i start (progn
2129        (write-char cur-char stream)
2130        (- i cur-val))))
2131        ((< i cur-val)
2132         (cond ((<= (- cur-val cur-sub-val) i)
2133          (write-char cur-sub-char stream)
2134          (write-char cur-char stream)
2135          (- i (- cur-val cur-sub-val)))
2136         (t i))))))
2137      ((zerop start))))
2138
2139;;;; plural
2140
2141(def-format-interpreter #\P (colonp atsignp params)
2142  (interpret-bind-defaults () params
2143                           (let ((arg (if colonp
2144                                          (if (eq orig-args args)
2145                                              (error 'format-error
2146                                                     :complaint "no previous argument")
2147                                              (do ((arg-ptr orig-args (cdr arg-ptr)))
2148                                                  ((eq (cdr arg-ptr) args)
2149                                                   (car arg-ptr))))
2150                                          (next-arg))))
2151                             (if atsignp
2152                                 (write-string (if (eql arg 1) "y" "ies") stream)
2153                                 (unless (eql arg 1) (write-char #\s stream))))))
2154
2155;;;; format interpreters and support functions for floating point output
2156
2157(defun decimal-string (n)
2158  (write-to-string n :base 10 :radix nil :escape nil))
2159
2160(def-format-interpreter #\F (colonp atsignp params)
2161  (when colonp
2162    (error 'format-error
2163     :complaint
2164     "cannot specify the colon modifier with this directive"))
2165  (interpret-bind-defaults ((w nil) (d nil) (k nil) (ovf nil) (pad #\space))
2166         params
2167                           (format-fixed stream (next-arg) w d k ovf pad atsignp)))
2168
2169(defun format-fixed (stream number w d k ovf pad atsign)
2170  (if (numberp number)
2171      (if (floatp number)
2172    (format-fixed-aux stream number w d k ovf pad atsign)
2173    (if (rationalp number)
2174        (format-fixed-aux stream
2175        (coerce number 'single-float)
2176        w d k ovf pad atsign)
2177        (format-write-field stream
2178          (decimal-string number)
2179          w 1 0 #\space t)))
2180      (format-princ stream number nil nil w 1 0 pad)))
2181
2182;;; We return true if we overflowed, so that ~G can output the overflow char
2183;;; instead of spaces.
2184(defun format-fixed-aux (stream number w d k ovf pad atsign)
2185  (cond
2186   ((and (floatp number)
2187         (or (sys:float-infinity-p number)
2188             (sys:float-nan-p number)))
2189    (prin1 number stream)
2190    nil)
2191   (t
2192    (let ((spaceleft w))
2193      (when (and w (or atsign (minusp (float-sign number))))
2194        (decf spaceleft))
2195      (multiple-value-bind (str len lpoint tpoint)
2196        (sys::flonum-to-string (abs number) spaceleft d k)
2197  ;;if caller specifically requested no fraction digits, suppress the
2198  ;;optional trailing zero
2199  (when (and d (zerop d))
2200          (setf tpoint nil))
2201  (when w
2202    (decf spaceleft len)
2203    ;;optional leading zero
2204    (when lpoint
2205      (if (or (> spaceleft 0) tpoint) ;force at least one digit
2206    (decf spaceleft)
2207    (setq lpoint nil)))
2208    ;;optional trailing zero
2209    (when tpoint
2210      (if (> spaceleft 0)
2211    (decf spaceleft)
2212    (setq tpoint nil))))
2213  (cond ((and w (< spaceleft 0) ovf)
2214         ;;field width overflow
2215         (dotimes (i w) (write-char ovf stream))
2216         t)
2217        (t
2218         (when w (dotimes (i spaceleft) (write-char pad stream)))
2219         (cond ((minusp (float-sign number))
2220                      (write-char #\- stream))
2221                     (atsign
2222                      (write-char #\+ stream)))
2223         (when lpoint (write-char #\0 stream))
2224         (write-string str stream)
2225         (when tpoint (write-char #\0 stream))
2226         nil)))))))
2227
2228(def-format-interpreter #\E (colonp atsignp params)
2229  (when colonp
2230    (error 'format-error
2231     :complaint
2232     "cannot specify the colon modifier with this directive"))
2233  (interpret-bind-defaults
2234   ((w nil) (d nil) (e nil) (k 1) (ovf nil) (pad #\space) (mark nil))
2235   params
2236   (format-exponential stream (next-arg) w d e k ovf pad mark atsignp)))
2237
2238(defun format-exponential (stream number w d e k ovf pad marker atsign)
2239  (if (numberp number)
2240      (if (floatp number)
2241    (format-exp-aux stream number w d e k ovf pad marker atsign)
2242    (if (rationalp number)
2243        (format-exp-aux stream
2244            (coerce number 'single-float)
2245            w d e k ovf pad marker atsign)
2246        (format-write-field stream
2247          (decimal-string number)
2248          w 1 0 #\space t)))
2249      (format-princ stream number nil nil w 1 0 pad)))
2250
2251(defun format-exponent-marker (number)
2252  (if (typep number *read-default-float-format*)
2253      #\e
2254      (typecase number
2255  (single-float #\f)
2256  (double-float #\d)
2257  (short-float #\s)
2258  (long-float #\l))))
2259
2260;;; Here we prevent the scale factor from shifting all significance out of
2261;;; a number to the right. We allow insignificant zeroes to be shifted in
2262;;; to the left right, athough it is an error to specify k and d such that this
2263;;; occurs. Perhaps we should detect both these condtions and flag them as
2264;;; errors. As for now, we let the user get away with it, and merely guarantee
2265;;; that at least one significant digit will appear.
2266
2267;;; Raymond Toy writes: The Hyperspec seems to say that the exponent
2268;;; marker is always printed. Make it so. Also, the original version
2269;;; causes errors when printing infinities or NaN's. The Hyperspec is
2270;;; silent here, so let's just print out infinities and NaN's instead
2271;;; of causing an error.
2272(defun format-exp-aux (stream number w d e k ovf pad marker atsign)
2273  (if (and (floatp number)
2274     (or (sys::float-infinity-p number)
2275         (sys::float-nan-p number)))
2276      (prin1 number stream)
2277      (multiple-value-bind (num expt) (sys::scale-exponent (abs number))
2278  (let* ((expt (- expt k))
2279         (estr (decimal-string (abs expt)))
2280         (elen (if e (max (length estr) e) (length estr)))
2281         (fdig (if d (if (plusp k) (1+ (- d k)) d) nil))
2282         (fmin (if (minusp k) (- 1 k) nil))
2283         (spaceleft (if w
2284            (- w 2 elen
2285         (if (or atsign (minusp number))
2286             1 0))
2287            nil)))
2288    (if (and w ovf e (> elen e)) ;exponent overflow
2289        (dotimes (i w) (write-char ovf stream))
2290        (multiple-value-bind (fstr flen lpoint)
2291                (sys::flonum-to-string num spaceleft fdig k fmin)
2292    (when w
2293      (decf spaceleft flen)
2294      (when lpoint
2295        (if (> spaceleft 0)
2296      (decf spaceleft)
2297      (setq lpoint nil))))
2298    (cond ((and w (< spaceleft 0) ovf)
2299           ;;significand overflow
2300           (dotimes (i w) (write-char ovf stream)))
2301          (t (when w
2302         (dotimes (i spaceleft) (write-char pad stream)))
2303       (if (minusp number)
2304           (write-char #\- stream)
2305           (if atsign (write-char #\+ stream)))
2306       (when lpoint (write-char #\0 stream))
2307       (write-string fstr stream)
2308       (write-char (if marker
2309           marker
2310           (format-exponent-marker number))
2311             stream)
2312       (write-char (if (minusp expt) #\- #\+) stream)
2313       (when e
2314         ;;zero-fill before exponent if necessary
2315         (dotimes (i (- e (length estr)))
2316           (write-char #\0 stream)))
2317       (write-string estr stream)))))))))
2318
2319(def-format-interpreter #\G (colonp atsignp params)
2320  (when colonp
2321    (error 'format-error
2322     :complaint
2323     "cannot specify the colon modifier with this directive"))
2324  (interpret-bind-defaults
2325   ((w nil) (d nil) (e nil) (k nil) (ovf nil) (pad #\space) (mark nil))
2326   params
2327   (format-general stream (next-arg) w d e k ovf pad mark atsignp)))
2328
2329(defun format-general (stream number w d e k ovf pad marker atsign)
2330  (if (numberp number)
2331      (if (floatp number)
2332    (format-general-aux stream number w d e k ovf pad marker atsign)
2333    (if (rationalp number)
2334        (format-general-aux stream
2335          (coerce number 'single-float)
2336          w d e k ovf pad marker atsign)
2337        (format-write-field stream
2338          (decimal-string number)
2339          w 1 0 #\space t)))
2340      (format-princ stream number nil nil w 1 0 pad)))
2341
2342;;; Raymond Toy writes: same change as for format-exp-aux
2343(defun format-general-aux (stream number w d e k ovf pad marker atsign)
2344  (if (and (floatp number)
2345     (or (sys::float-infinity-p number)
2346         (sys::float-nan-p number)))
2347      (prin1 number stream)
2348      (multiple-value-bind (ignore n) (sys::scale-exponent (abs number))
2349  (declare (ignore ignore))
2350  ;; KLUDGE: Default d if omitted. The procedure is taken directly from
2351  ;; the definition given in the manual, and is not very efficient, since
2352  ;; we generate the digits twice. Future maintainers are encouraged to
2353  ;; improve on this. -- rtoy?? 1998??
2354  (unless d
2355    (multiple-value-bind (str len)
2356            (sys::flonum-to-string (abs number))
2357      (declare (ignore str))
2358      (let ((q (if (= len 1) 1 (1- len))))
2359        (setq d (max q (min n 7))))))
2360  (let* ((ee (if e (+ e 2) 4))
2361         (ww (if w (- w ee) nil))
2362         (dd (- d n)))
2363    (cond ((<= 0 dd d)
2364     (let ((char (if (format-fixed-aux stream number ww dd nil
2365               ovf pad atsign)
2366         ovf
2367         #\space)))
2368       (dotimes (i ee) (write-char char stream))))
2369    (t
2370     (format-exp-aux stream number w d e (or k 1)
2371         ovf pad marker atsign)))))))
2372
2373(def-format-interpreter #\$ (colonp atsignp params)
2374  (interpret-bind-defaults ((d 2) (n 1) (w 0) (pad #\space)) params
2375                           (format-dollars stream (next-arg) d n w pad colonp atsignp)))
2376
2377(defun format-dollars (stream number d n w pad colon atsign)
2378  (when (rationalp number)
2379    ;; This coercion to SINGLE-FLOAT seems as though it gratuitously
2380    ;; loses precision (why not LONG-FLOAT?) but it's the default
2381    ;; behavior in the ANSI spec, so in some sense it's the right
2382    ;; thing, and at least the user shouldn't be surprised.
2383    (setq number (coerce number 'single-float)))
2384  (if (floatp number)
2385      (let* ((signstr (if (minusp number) "-" (if atsign "+" "")))
2386       (signlen (length signstr)))
2387  (multiple-value-bind (str strlen ig2 ig3 pointplace)
2388          (sys::flonum-to-string number nil d nil)
2389    (declare (ignore ig2 ig3 strlen))
2390    (when colon
2391      (write-string signstr stream))
2392    (dotimes (i (- w signlen (max n pointplace) 1 d))
2393      (write-char pad stream))
2394    (unless colon
2395      (write-string signstr stream))
2396    (dotimes (i (- n pointplace))
2397      (write-char #\0 stream))
2398    (write-string str stream)))
2399      (format-write-field stream
2400        (decimal-string number)
2401        w 1 0 #\space t)))
2402
2403;;;; FORMAT interpreters and support functions for line/page breaks etc.
2404
2405(def-format-interpreter #\% (colonp atsignp params)
2406  (when (or colonp atsignp)
2407    (error 'format-error
2408     :complaint
2409     "cannot specify either colon or atsign for this directive"))
2410  (interpret-bind-defaults ((count 1)) params
2411                           (dotimes (i count)
2412                             (terpri stream))))
2413
2414(def-format-interpreter #\& (colonp atsignp params)
2415  (when (or colonp atsignp)
2416    (error 'format-error
2417     :complaint
2418     "cannot specify either colon or atsign for this directive"))
2419  (interpret-bind-defaults ((count 1)) params
2420                           (fresh-line stream)
2421                           (dotimes (i (1- count))
2422                             (terpri stream))))
2423
2424(def-format-interpreter #\| (colonp atsignp params)
2425  (when (or colonp atsignp)
2426    (error 'format-error
2427     :complaint
2428     "cannot specify either colon or atsign for this directive"))
2429  (interpret-bind-defaults ((count 1)) params
2430                           (dotimes (i count)
2431                             (write-char (code-char sys::form-feed-char-code) stream))))
2432
2433(def-format-interpreter #\~ (colonp atsignp params)
2434  (when (or colonp atsignp)
2435    (error 'format-error
2436     :complaint
2437     "cannot specify either colon or atsign for this directive"))
2438  (interpret-bind-defaults ((count 1)) params
2439                           (dotimes (i count)
2440                             (write-char #\~ stream))))
2441
2442(def-complex-format-interpreter #\newline (colonp atsignp params directives)
2443  (when (and colonp atsignp)
2444    (error 'format-error
2445     :complaint
2446     "cannot specify both colon and atsign for this directive"))
2447  (interpret-bind-defaults () params
2448                           (when atsignp
2449                             (write-char #\newline stream)))
2450  (if (and (not colonp)
2451     directives
2452     (simple-string-p (car directives)))
2453      (cons (string-left-trim *format-whitespace-chars*
2454            (car directives))
2455      (cdr directives))
2456      directives))
2457
2458;;;; format interpreters and support functions for tabs and simple pretty
2459;;;; printing
2460
2461(def-format-interpreter #\T (colonp atsignp params)
2462  (if colonp
2463      (interpret-bind-defaults ((n 1) (m 1)) params
2464                               (pprint-tab (if atsignp :section-relative :section) n m stream))
2465      (if atsignp
2466    (interpret-bind-defaults ((colrel 1) (colinc 1)) params
2467                                   (format-relative-tab stream colrel colinc))
2468    (interpret-bind-defaults ((colnum 1) (colinc 1)) params
2469                                   (format-absolute-tab stream colnum colinc)))))
2470
2471(defun output-spaces (stream n)
2472  (let ((spaces #.(make-string 100 :initial-element #\space)))
2473    (loop
2474      (when (< n (length spaces))
2475  (return))
2476      (write-string spaces stream)
2477      (decf n (length spaces)))
2478    (write-string spaces stream :end n)))
2479
2480(defun format-relative-tab (stream colrel colinc)
2481  (if (xp::xp-structure-p stream)
2482      (pprint-tab :line-relative colrel colinc stream)
2483      (let* ((cur (charpos stream))
2484       (spaces (if (and cur (plusp colinc))
2485       (- (* (ceiling (+ cur colrel) colinc) colinc) cur)
2486       colrel)))
2487  (output-spaces stream spaces))))
2488
2489(defun format-absolute-tab (stream colnum colinc)
2490  (if (xp::xp-structure-p stream)
2491      (pprint-tab :line colnum colinc stream)
2492      (let ((cur (charpos stream)))
2493  (cond ((null cur)
2494         (write-string "  " stream))
2495        ((< cur colnum)
2496         (output-spaces stream (- colnum cur)))
2497        (t
2498         (unless (zerop colinc)
2499     (output-spaces stream
2500        (- colinc (rem (- cur colnum) colinc)))))))))
2501
2502(def-format-interpreter #\_ (colonp atsignp params)
2503  (interpret-bind-defaults () params
2504                           (pprint-newline (if colonp
2505                                               (if atsignp
2506                                                   :mandatory
2507                                                   :fill)
2508                                               (if atsignp
2509                                                   :miser
2510                                                   :linear))
2511                                           stream)))
2512
2513(def-format-interpreter #\I (colonp atsignp params)
2514  (when atsignp
2515    (error 'format-error
2516     :complaint "cannot specify the at-sign modifier"))
2517  (interpret-bind-defaults ((n 0)) params
2518                           (pprint-indent (if colonp :current :block) n stream)))
2519
2520;;;; format interpreter for ~*
2521
2522(def-format-interpreter #\* (colonp atsignp params)
2523  (if atsignp
2524      (if colonp
2525    (error 'format-error
2526     :complaint "cannot specify both colon and at-sign")
2527    (interpret-bind-defaults ((posn 0)) params
2528                                   (if (<= 0 posn (length orig-args))
2529                                       (setf args (nthcdr posn orig-args))
2530                                       (error 'format-error
2531                                              :complaint "Index ~W is out of bounds. (It should ~
2532                                              have been between 0 and ~W.)"
2533                                              :args (list posn (length orig-args))))))
2534      (if colonp
2535    (interpret-bind-defaults ((n 1)) params
2536                                   (do ((cur-posn 0 (1+ cur-posn))
2537                                        (arg-ptr orig-args (cdr arg-ptr)))
2538                                       ((eq arg-ptr args)
2539                                        (let ((new-posn (- cur-posn n)))
2540                                          (if (<= 0 new-posn (length orig-args))
2541                                              (setf args (nthcdr new-posn orig-args))
2542                                              (error 'format-error
2543                                                     :complaint
2544                                                     "Index ~W is out of bounds. (It should
2545                                                      have been between 0 and ~W.)"
2546                                                     :args
2547                                                     (list new-posn (length orig-args))))))))
2548    (interpret-bind-defaults ((n 1)) params
2549                                   (dotimes (i n)
2550                                     (next-arg))))))
2551
2552;;;; format interpreter for indirection
2553
2554(def-format-interpreter #\? (colonp atsignp params string end)
2555  (when colonp
2556    (error 'format-error
2557     :complaint "cannot specify the colon modifier"))
2558  (interpret-bind-defaults () params
2559                           (handler-bind
2560                             ((format-error
2561                               (lambda (condition)
2562                                 (error 'format-error
2563                                        :complaint
2564                                        "~A~%while processing indirect format string:"
2565                                        :args (list condition)
2566                                        :print-banner nil
2567                                        :control-string string
2568                                        :offset (1- end)))))
2569                             (if atsignp
2570                                 (setf args (%format stream (next-arg) orig-args args))
2571                                 (%format stream (next-arg) (next-arg))))))
2572
2573;;;; format interpreters for capitalization
2574
2575(def-complex-format-interpreter #\( (colonp atsignp params directives)
2576  (let ((close (find-directive directives #\) nil)))
2577    (unless close
2578      (error 'format-error
2579       :complaint "no corresponding close paren"))
2580    (interpret-bind-defaults () params
2581                             (let* ((posn (position close directives))
2582                                    (before (subseq directives 0 posn))
2583                                    (after (nthcdr (1+ posn) directives))
2584                                    (stream (sys::make-case-frob-stream stream
2585                                                                        (if colonp
2586                                                                            (if atsignp
2587                                                                                :upcase
2588                                                                                :capitalize)
2589                                                                            (if atsignp
2590                                                                                :capitalize-first
2591                                                                                :downcase)))))
2592                               (setf args (interpret-directive-list stream before orig-args args))
2593                               after))))
2594
2595(def-complex-format-interpreter #\) ()
2596  (error 'format-error
2597   :complaint "no corresponding open paren"))
2598
2599;;;; format interpreters and support functions for conditionalization
2600
2601(def-complex-format-interpreter #\[ (colonp atsignp params directives)
2602  (multiple-value-bind (sublists last-semi-with-colon-p remaining)
2603    (parse-conditional-directive directives)
2604    (setf args
2605    (if atsignp
2606        (if colonp
2607      (error 'format-error
2608       :complaint
2609                         "cannot specify both the colon and at-sign modifiers")
2610      (if (cdr sublists)
2611          (error 'format-error
2612           :complaint
2613           "can only specify one section")
2614          (interpret-bind-defaults () params
2615                                               (let ((prev-args args)
2616                                                     (arg (next-arg)))
2617                                                 (if arg
2618                                                     (interpret-directive-list stream
2619                                                                               (car sublists)
2620                                                                               orig-args
2621                                                                               prev-args)
2622                                                     args)))))
2623        (if colonp
2624      (if (= (length sublists) 2)
2625          (interpret-bind-defaults () params
2626                                               (if (next-arg)
2627                                                   (interpret-directive-list stream (car sublists)
2628                                                                             orig-args args)
2629                                                   (interpret-directive-list stream (cadr sublists)
2630                                                                             orig-args args)))
2631          (error 'format-error
2632           :complaint
2633           "must specify exactly two sections"))
2634      (interpret-bind-defaults ((index (next-arg))) params
2635                                           (let* ((default (and last-semi-with-colon-p
2636                                                                (pop sublists)))
2637                                                  (last (1- (length sublists)))
2638                                                  (sublist
2639                                                   (if (<= 0 index last)
2640                                                       (nth (- last index) sublists)
2641                                                       default)))
2642                                             (interpret-directive-list stream sublist orig-args
2643                                                                       args))))))
2644    remaining))
2645
2646(def-complex-format-interpreter #\; ()
2647  (error 'format-error
2648   :complaint
2649   "~~; not contained within either ~~[...~~] or ~~<...~~>"))
2650
2651(def-complex-format-interpreter #\] ()
2652  (error 'format-error
2653   :complaint
2654   "no corresponding open bracket"))
2655
2656;;;; format interpreter for up-and-out
2657
2658(defvar *outside-args*)
2659
2660(def-format-interpreter #\^ (colonp atsignp params)
2661  (when atsignp
2662    (error 'format-error
2663     :complaint "cannot specify the at-sign modifier"))
2664  (when (and colonp (not *up-up-and-out-allowed*))
2665    (error 'format-error
2666     :complaint "attempt to use ~~:^ outside a ~~:{...~~} construct"))
2667  (when (interpret-bind-defaults ((arg1 nil) (arg2 nil) (arg3 nil)) params
2668          (cond (arg3 (<= arg1 arg2 arg3))
2669                (arg2 (eql arg1 arg2))
2670                (arg1 (eql arg1 0))
2671                (t (if colonp
2672                       (null *outside-args*)
2673                       (null args)))))
2674    (throw (if colonp 'up-up-and-out 'up-and-out)
2675     args)))
2676
2677;;;; format interpreters for iteration
2678
2679(def-complex-format-interpreter #\{
2680  (colonp atsignp params string end directives)
2681  (let ((close (find-directive directives #\} nil)))
2682    (unless close
2683      (error 'format-error
2684       :complaint
2685       "no corresponding close brace"))
2686    (interpret-bind-defaults ((max-count nil)) params
2687      (let* ((closed-with-colon (format-directive-colonp close))
2688             (posn (position close directives))
2689             (insides (if (zerop posn)
2690                          (next-arg)
2691                          (subseq directives 0 posn)))
2692             (*up-up-and-out-allowed* colonp))
2693        (labels
2694            ((do-guts (orig-args args)
2695                      (if (zerop posn)
2696                          (handler-bind
2697                            ((format-error
2698                              (lambda (condition)
2699                                (error
2700                                 'format-error
2701                                 :complaint
2702                                 "~A~%while processing indirect format string:"
2703                                 :args (list condition)
2704                                 :print-banner nil
2705                                 :control-string string
2706                                 :offset (1- end)))))
2707                            (%format stream insides orig-args args))
2708                          (interpret-directive-list stream insides
2709                                                    orig-args args)))
2710             (bind-args (orig-args args)
2711                        (if colonp
2712                            (let* ((arg (next-arg))
2713                                   (*logical-block-popper* nil)
2714                                   (*outside-args* args))
2715                              (catch 'up-and-out
2716                                (do-guts arg arg))
2717                              args)
2718                            (do-guts orig-args args)))
2719             (do-loop (orig-args args)
2720                      (catch (if colonp 'up-up-and-out 'up-and-out)
2721                        (loop
2722                          (when (and (not closed-with-colon) (null args))
2723                            (return))
2724                          (when (and max-count (minusp (decf max-count)))
2725                            (return))
2726                          (setf args (bind-args orig-args args))
2727                          (when (and closed-with-colon (null args))
2728                            (return)))
2729                        args)))
2730          (if atsignp
2731              (setf args (do-loop orig-args args))
2732              (let ((arg (next-arg))
2733                    (*logical-block-popper* nil))
2734                (do-loop arg arg)))
2735          (nthcdr (1+ posn) directives))))))
2736
2737(def-complex-format-interpreter #\} ()
2738  (error 'format-error
2739   :complaint "no corresponding open brace"))
2740
2741;;;; format interpreters and support functions for justification
2742
2743(def-complex-format-interpreter #\<
2744  (colonp atsignp params string end directives)
2745  (multiple-value-bind (segments first-semi close remaining)
2746    (parse-format-justification directives)
2747    (setf args
2748    (if (format-directive-colonp close)
2749        (multiple-value-bind (prefix per-line-p insides suffix)
2750                (parse-format-logical-block segments colonp first-semi
2751                                            close params string end)
2752    (interpret-format-logical-block stream orig-args args
2753            prefix per-line-p insides
2754            suffix atsignp))
2755        (let ((count (reduce #'+ (mapcar (lambda (x) (count-if #'illegal-inside-justification-p x)) segments))))
2756    (when (> count 0)
2757      ;; ANSI specifies that "an error is signalled" in this
2758      ;; situation.
2759      (error 'format-error
2760       :complaint "~D illegal directive~:P found inside justification block"
2761       :args (list count)))
2762    (interpret-format-justification stream orig-args args
2763            segments colonp atsignp
2764            first-semi params))))
2765    remaining))
2766
2767(defun interpret-format-justification
2768  (stream orig-args args segments colonp atsignp first-semi params)
2769  (interpret-bind-defaults
2770   ((mincol 0) (colinc 1) (minpad 0) (padchar #\space))
2771   params
2772   (let ((newline-string nil)
2773         (strings nil)
2774         (extra-space 0)
2775         (line-len 0))
2776     (setf args
2777           (catch 'up-and-out
2778             (when (and first-semi (format-directive-colonp first-semi))
2779               (interpret-bind-defaults
2780                ((extra 0)
2781                 (len (or #-abcl(sb!impl::line-length stream) 72)))
2782                (format-directive-params first-semi)
2783                (setf newline-string
2784                      (with-output-to-string (stream)
2785                        (setf args
2786                              (interpret-directive-list stream
2787                                                        (pop segments)
2788                                                        orig-args
2789                                                        args))))
2790                (setf extra-space extra)
2791                (setf line-len len)))
2792             (dolist (segment segments)
2793               (push (with-output-to-string (stream)
2794                       (setf args
2795                             (interpret-directive-list stream segment
2796                                                       orig-args args)))
2797                     strings))
2798             args))
2799     (format-justification stream newline-string extra-space line-len strings
2800                           colonp atsignp mincol colinc minpad padchar)))
2801  args)
2802
2803(defun format-justification (stream newline-prefix extra-space line-len strings
2804                                    pad-left pad-right mincol colinc minpad padchar)
2805  (setf strings (reverse strings))
2806  (let* ((num-gaps (+ (1- (length strings))
2807          (if pad-left 1 0)
2808          (if pad-right 1 0)))
2809   (chars (+ (* num-gaps minpad)
2810       (loop
2811         for string in strings
2812         summing (length string))))
2813   (length (if (> chars mincol)
2814         (+ mincol (* (ceiling (- chars mincol) colinc) colinc))
2815         mincol))
2816   (padding (+ (- length chars) (* num-gaps minpad))))
2817    (when (and newline-prefix
2818         (> (+ (or (charpos stream) 0)
2819         length extra-space)
2820      line-len))
2821      (write-string newline-prefix stream))
2822    (flet ((do-padding ()
2823                       (let ((pad-len (if (zerop num-gaps)
2824                                          padding
2825                                          (truncate padding num-gaps))))
2826                         (decf padding pad-len)
2827                         (decf num-gaps)
2828                         (dotimes (i pad-len) (write-char padchar stream)))))
2829      (when (or pad-left
2830    (and (not pad-right) (null (cdr strings))))
2831  (do-padding))
2832      (when strings
2833  (write-string (car strings) stream)
2834  (dolist (string (cdr strings))
2835    (do-padding)
2836    (write-string string stream)))
2837      (when pad-right
2838  (do-padding)))))
2839
2840(defun interpret-format-logical-block
2841  (stream orig-args args prefix per-line-p insides suffix atsignp)
2842  (let ((arg (if atsignp args (next-arg))))
2843    (if per-line-p
2844  (pprint-logical-block
2845         (stream arg :per-line-prefix prefix :suffix suffix)
2846         (let ((*logical-block-popper* (lambda () (pprint-pop))))
2847           (catch 'up-and-out
2848             (interpret-directive-list stream insides
2849                                       (if atsignp orig-args arg)
2850                                       arg))))
2851  (pprint-logical-block (stream arg :prefix prefix :suffix suffix)
2852                              (let ((*logical-block-popper* (lambda () (pprint-pop))))
2853                                (catch 'up-and-out
2854                                  (interpret-directive-list stream insides
2855                                                            (if atsignp orig-args arg)
2856                                                            arg))))))
2857  (if atsignp nil args))
2858
2859;;;; format interpreter and support functions for user-defined method
2860
2861(def-format-interpreter #\/ (string start end colonp atsignp params)
2862  (let ((symbol (extract-user-fun-name string start end)))
2863    (collect ((args))
2864             (dolist (param-and-offset params)
2865               (let ((param (cdr param-and-offset)))
2866                 (case param
2867                   (:arg (args (next-arg)))
2868                   (:remaining (args (length args)))
2869                   (t (args param)))))
2870             (apply (fdefinition symbol) stream (next-arg) colonp atsignp (args)))))
2871
2872(setf sys::*simple-format-function* #'format)
2873
2874
2875(provide 'format)
Note: See TracBrowser for help on using the repository browser.