636902455428089432c6df8b57750eef9d7729fe
[sbcl.git] / src / code / late-format.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB!FORMAT")
11 \f
12 (define-condition format-error (error reference-condition)
13   ((complaint :reader format-error-complaint :initarg :complaint)
14    (args :reader format-error-args :initarg :args :initform nil)
15    (control-string :reader format-error-control-string
16                    :initarg :control-string
17                    :initform *default-format-error-control-string*)
18    (offset :reader format-error-offset :initarg :offset
19            :initform *default-format-error-offset*)
20    (second-relative :reader format-error-second-relative
21                     :initarg :second-relative :initform nil)
22    (print-banner :reader format-error-print-banner :initarg :print-banner
23                  :initform t))
24   (:report %print-format-error)
25   (:default-initargs :references nil))
26
27 (defun %print-format-error (condition stream)
28   (format stream
29           "~:[~*~;error in ~S: ~]~?~@[~%  ~A~%  ~V@T^~@[~V@T^~]~]"
30           (format-error-print-banner condition)
31           'format
32           (format-error-complaint condition)
33           (format-error-args condition)
34           (format-error-control-string condition)
35           (format-error-offset condition)
36           (format-error-second-relative condition)))
37 \f
38 (def!struct format-directive
39   (string (missing-arg) :type simple-string)
40   (start (missing-arg) :type (and unsigned-byte fixnum))
41   (end (missing-arg) :type (and unsigned-byte fixnum))
42   (character (missing-arg) :type character)
43   (colonp nil :type (member t nil))
44   (atsignp nil :type (member t nil))
45   (params nil :type list))
46 (def!method print-object ((x format-directive) stream)
47   (print-unreadable-object (x stream)
48     (write-string (format-directive-string x)
49                   stream
50                   :start (format-directive-start x)
51                   :end (format-directive-end x))))
52 \f
53 ;;;; TOKENIZE-CONTROL-STRING
54
55 (defun tokenize-control-string (string)
56   (declare (simple-string string))
57   (let ((index 0)
58         (end (length string))
59         (result nil)
60         ;; FIXME: consider rewriting this 22.3.5.2-related processing
61         ;; using specials to maintain state and doing the logic inside
62         ;; the directive expanders themselves.
63         (block)
64         (pprint)
65         (semicolon)
66         (justification-semicolon))
67     (loop
68       (let ((next-directive (or (position #\~ string :start index) end)))
69         (when (> next-directive index)
70           (push (subseq string index next-directive) result))
71         (when (= next-directive end)
72           (return))
73         (let* ((directive (parse-directive string next-directive))
74                (char (format-directive-character directive)))
75           ;; this processing is required by CLHS 22.3.5.2
76           (cond
77             ((char= char #\<) (push directive block))
78             ((and block (char= char #\;) (format-directive-colonp directive))
79              (setf semicolon directive))
80             ((char= char #\>)
81              (unless block
82                (error 'format-error
83                       :complaint "~~> without a matching ~~<"
84                       :control-string string
85                       :offset next-directive))
86              (cond
87                ((format-directive-colonp directive)
88                 (unless pprint
89                   (setf pprint (car block)))
90                 (setf semicolon nil))
91                (semicolon
92                 (unless justification-semicolon
93                   (setf justification-semicolon semicolon))))
94              (pop block))
95             ;; block cases are handled by the #\< expander/interpreter
96             ((not block)
97              (case char
98                ((#\W #\I #\_) (unless pprint (setf pprint directive)))
99                (#\T (when (and (format-directive-colonp directive)
100                                (not pprint))
101                       (setf pprint directive))))))
102           (push directive result)
103           (setf index (format-directive-end directive)))))
104     (when (and pprint justification-semicolon)
105       (let ((pprint-offset (1- (format-directive-end pprint)))
106             (justification-offset
107              (1- (format-directive-end justification-semicolon))))
108         (error 'format-error
109                :complaint "misuse of justification and pprint directives"
110                :control-string string
111                :offset (min pprint-offset justification-offset)
112                :second-relative (- (max pprint-offset justification-offset)
113                                    (min pprint-offset justification-offset)
114                                    1)
115                :references (list '(:ansi-cl :section (22 3 5 2))))))
116     (nreverse result)))
117
118 (defun parse-directive (string start)
119   (let ((posn (1+ start)) (params nil) (colonp nil) (atsignp nil)
120         (end (length string)))
121     (flet ((get-char ()
122              (if (= posn end)
123                  (error 'format-error
124                         :complaint "string ended before directive was found"
125                         :control-string string
126                         :offset start)
127                  (schar string posn)))
128            (check-ordering ()
129              (when (or colonp atsignp)
130                (error 'format-error
131                       :complaint "parameters found after #\\: or #\\@ modifier"
132                       :control-string string
133                       :offset posn
134                       :references (list '(:ansi-cl :section (22 3)))))))
135       (loop
136         (let ((char (get-char)))
137           (cond ((or (char<= #\0 char #\9) (char= char #\+) (char= char #\-))
138                  (check-ordering)
139                  (multiple-value-bind (param new-posn)
140                      (parse-integer string :start posn :junk-allowed t)
141                    (push (cons posn param) params)
142                    (setf posn new-posn)
143                    (case (get-char)
144                      (#\,)
145                      ((#\: #\@)
146                       (decf posn))
147                      (t
148                       (return)))))
149                 ((or (char= char #\v)
150                      (char= char #\V))
151                  (check-ordering)
152                  (push (cons posn :arg) params)
153                  (incf posn)
154                  (case (get-char)
155                    (#\,)
156                    ((#\: #\@)
157                     (decf posn))
158                    (t
159                     (return))))
160                 ((char= char #\#)
161                  (check-ordering)
162                  (push (cons posn :remaining) params)
163                  (incf posn)
164                  (case (get-char)
165                    (#\,)
166                    ((#\: #\@)
167                     (decf posn))
168                    (t
169                     (return))))
170                 ((char= char #\')
171                  (check-ordering)
172                  (incf posn)
173                  (push (cons posn (get-char)) params)
174                  (incf posn)
175                  (unless (char= (get-char) #\,)
176                    (decf posn)))
177                 ((char= char #\,)
178                  (check-ordering)
179                  (push (cons posn nil) params))
180                 ((char= char #\:)
181                  (if colonp
182                      (error 'format-error
183                             :complaint "too many colons supplied"
184                             :control-string string
185                             :offset posn
186                             :references (list '(:ansi-cl :section (22 3))))
187                      (setf colonp t)))
188                 ((char= char #\@)
189                  (if atsignp
190                      (error 'format-error
191                             :complaint "too many #\\@ characters supplied"
192                             :control-string string
193                             :offset posn
194                             :references (list '(:ansi-cl :section (22 3))))
195                      (setf atsignp t)))
196                 (t
197                  (when (and (char= (schar string (1- posn)) #\,)
198                             (or (< posn 2)
199                                 (char/= (schar string (- posn 2)) #\')))
200                    (check-ordering)
201                    (push (cons (1- posn) nil) params))
202                  (return))))
203         (incf posn))
204       (let ((char (get-char)))
205         (when (char= char #\/)
206           (let ((closing-slash (position #\/ string :start (1+ posn))))
207             (if closing-slash
208                 (setf posn closing-slash)
209                 (error 'format-error
210                        :complaint "no matching closing slash"
211                        :control-string string
212                        :offset posn))))
213         (make-format-directive
214          :string string :start start :end (1+ posn)
215          :character (char-upcase char)
216          :colonp colonp :atsignp atsignp
217          :params (nreverse params))))))
218 \f
219 ;;;; FORMATTER stuff
220
221 (sb!xc:defmacro formatter (control-string)
222   `#',(%formatter control-string))
223
224 (defun %formatter (control-string)
225   (block nil
226     (catch 'need-orig-args
227       (let* ((*simple-args* nil)
228              (*only-simple-args* t)
229              (guts (expand-control-string control-string))
230              (args nil))
231         (dolist (arg *simple-args*)
232           (push `(,(car arg)
233                   (error
234                    'format-error
235                    :complaint "required argument missing"
236                    :control-string ,control-string
237                    :offset ,(cdr arg)))
238                 args))
239         (return `(lambda (stream &optional ,@args &rest args)
240                    ,guts
241                    args))))
242     (let ((*orig-args-available* t)
243           (*only-simple-args* nil))
244       `(lambda (stream &rest orig-args)
245          (let ((args orig-args))
246            ,(expand-control-string control-string)
247            args)))))
248
249 (defun expand-control-string (string)
250   (let* ((string (etypecase string
251                    (simple-string
252                     string)
253                    (string
254                     (coerce string 'simple-string))))
255          (*default-format-error-control-string* string)
256          (directives (tokenize-control-string string)))
257     `(block nil
258        ,@(expand-directive-list directives))))
259
260 (defun expand-directive-list (directives)
261   (let ((results nil)
262         (remaining-directives directives))
263     (loop
264       (unless remaining-directives
265         (return))
266       (multiple-value-bind (form new-directives)
267           (expand-directive (car remaining-directives)
268                             (cdr remaining-directives))
269         (push form results)
270         (setf remaining-directives new-directives)))
271     (reverse results)))
272
273 (defun expand-directive (directive more-directives)
274   (etypecase directive
275     (format-directive
276      (let ((expander
277             (let ((char (format-directive-character directive)))
278               (typecase char
279                 (base-char
280                  (aref *format-directive-expanders* (char-code char)))
281                 (character nil))))
282            (*default-format-error-offset*
283             (1- (format-directive-end directive))))
284        (declare (type (or null function) expander))
285        (if expander
286            (funcall expander directive more-directives)
287            (error 'format-error
288                   :complaint "unknown directive ~@[(character: ~A)~]"
289                   :args (list (char-name (format-directive-character directive)))))))
290     (simple-string
291      (values `(write-string ,directive stream)
292              more-directives))))
293
294 (defmacro-mundanely expander-next-arg (string offset)
295   `(if args
296        (pop args)
297        (error 'format-error
298               :complaint "no more arguments"
299               :control-string ,string
300               :offset ,offset)))
301
302 (defun expand-next-arg (&optional offset)
303   (if (or *orig-args-available* (not *only-simple-args*))
304       `(,*expander-next-arg-macro*
305         ,*default-format-error-control-string*
306         ,(or offset *default-format-error-offset*))
307       (let ((symbol (gensym "FORMAT-ARG-")))
308         (push (cons symbol (or offset *default-format-error-offset*))
309               *simple-args*)
310         symbol)))
311
312 (defmacro expand-bind-defaults (specs params &body body)
313   (once-only ((params params))
314     (if specs
315         (collect ((expander-bindings) (runtime-bindings))
316                  (dolist (spec specs)
317                    (destructuring-bind (var default) spec
318                      (let ((symbol (gensym)))
319                        (expander-bindings
320                         `(,var ',symbol))
321                        (runtime-bindings
322                         `(list ',symbol
323                                (let* ((param-and-offset (pop ,params))
324                                       (offset (car param-and-offset))
325                                       (param (cdr param-and-offset)))
326                                  (case param
327                                    (:arg `(or ,(expand-next-arg offset)
328                                               ,,default))
329                                    (:remaining
330                                     (setf *only-simple-args* nil)
331                                     '(length args))
332                                    ((nil) ,default)
333                                    (t param))))))))
334                  `(let ,(expander-bindings)
335                     `(let ,(list ,@(runtime-bindings))
336                        ,@(if ,params
337                              (error
338                               'format-error
339                               :complaint
340                               "too many parameters, expected no more than ~W"
341                               :args (list ,(length specs))
342                               :offset (caar ,params)))
343                        ,,@body)))
344         `(progn
345            (when ,params
346              (error 'format-error
347                     :complaint "too many parameters, expected none"
348                     :offset (caar ,params)))
349            ,@body))))
350 \f
351 ;;;; format directive machinery
352
353 ;;; FIXME: only used in this file, could be SB!XC:DEFMACRO in EVAL-WHEN
354 (defmacro def-complex-format-directive (char lambda-list &body body)
355   (let ((defun-name (intern (format nil
356                                     "~:@(~:C~)-FORMAT-DIRECTIVE-EXPANDER"
357                                     char)))
358         (directive (gensym))
359         (directives (if lambda-list (car (last lambda-list)) (gensym))))
360     `(progn
361        (defun ,defun-name (,directive ,directives)
362          ,@(if lambda-list
363                `((let ,(mapcar (lambda (var)
364                                  `(,var
365                                    (,(symbolicate "FORMAT-DIRECTIVE-" var)
366                                     ,directive)))
367                                (butlast lambda-list))
368                    ,@body))
369                `((declare (ignore ,directive ,directives))
370                  ,@body)))
371        (%set-format-directive-expander ,char #',defun-name))))
372
373 ;;; FIXME: only used in this file, could be SB!XC:DEFMACRO in EVAL-WHEN
374 (defmacro def-format-directive (char lambda-list &body body)
375   (let ((directives (gensym))
376         (declarations nil)
377         (body-without-decls body))
378     (loop
379       (let ((form (car body-without-decls)))
380         (unless (and (consp form) (eq (car form) 'declare))
381           (return))
382         (push (pop body-without-decls) declarations)))
383     (setf declarations (reverse declarations))
384     `(def-complex-format-directive ,char (,@lambda-list ,directives)
385        ,@declarations
386        (values (progn ,@body-without-decls)
387                ,directives))))
388
389 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
390
391 (defun %set-format-directive-expander (char fn)
392   (setf (aref *format-directive-expanders* (char-code (char-upcase char))) fn)
393   char)
394
395 (defun %set-format-directive-interpreter (char fn)
396   (setf (aref *format-directive-interpreters*
397               (char-code (char-upcase char)))
398         fn)
399   char)
400
401 (defun find-directive (directives kind stop-at-semi)
402   (if directives
403       (let ((next (car directives)))
404         (if (format-directive-p next)
405             (let ((char (format-directive-character next)))
406               (if (or (char= kind char)
407                       (and stop-at-semi (char= char #\;)))
408                   (car directives)
409                   (find-directive
410                    (cdr (flet ((after (char)
411                                  (member (find-directive (cdr directives)
412                                                          char
413                                                          nil)
414                                          directives)))
415                           (case char
416                             (#\( (after #\)))
417                             (#\< (after #\>))
418                             (#\[ (after #\]))
419                             (#\{ (after #\}))
420                             (t directives))))
421                    kind stop-at-semi)))
422             (find-directive (cdr directives) kind stop-at-semi)))))
423
424 ) ; EVAL-WHEN
425 \f
426 ;;;; format directives for simple output
427
428 (def-format-directive #\A (colonp atsignp params)
429   (if params
430       (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
431                              (padchar #\space))
432                      params
433         `(format-princ stream ,(expand-next-arg) ',colonp ',atsignp
434                        ,mincol ,colinc ,minpad ,padchar))
435       `(princ ,(if colonp
436                    `(or ,(expand-next-arg) "()")
437                    (expand-next-arg))
438               stream)))
439
440 (def-format-directive #\S (colonp atsignp params)
441   (cond (params
442          (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
443                                 (padchar #\space))
444                         params
445            `(format-prin1 stream ,(expand-next-arg) ,colonp ,atsignp
446                           ,mincol ,colinc ,minpad ,padchar)))
447         (colonp
448          `(let ((arg ,(expand-next-arg)))
449             (if arg
450                 (prin1 arg stream)
451                 (princ "()" stream))))
452         (t
453          `(prin1 ,(expand-next-arg) stream))))
454
455 (def-format-directive #\C (colonp atsignp params)
456   (expand-bind-defaults () params
457     (if colonp
458         `(format-print-named-character ,(expand-next-arg) stream)
459         (if atsignp
460             `(prin1 ,(expand-next-arg) stream)
461             `(write-char ,(expand-next-arg) stream)))))
462
463 (def-format-directive #\W (colonp atsignp params)
464   (expand-bind-defaults () params
465     (if (or colonp atsignp)
466         `(let (,@(when colonp
467                    '((*print-pretty* t)))
468                ,@(when atsignp
469                    '((*print-level* nil)
470                      (*print-length* nil))))
471            (output-object ,(expand-next-arg) stream))
472         `(output-object ,(expand-next-arg) stream))))
473 \f
474 ;;;; format directives for integer output
475
476 (defun expand-format-integer (base colonp atsignp params)
477   (if (or colonp atsignp params)
478       (expand-bind-defaults
479           ((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
480           params
481         `(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
482                                ,base ,mincol ,padchar ,commachar
483                                ,commainterval))
484       `(write ,(expand-next-arg) :stream stream :base ,base :radix nil
485               :escape nil)))
486
487 (def-format-directive #\D (colonp atsignp params)
488   (expand-format-integer 10 colonp atsignp params))
489
490 (def-format-directive #\B (colonp atsignp params)
491   (expand-format-integer 2 colonp atsignp params))
492
493 (def-format-directive #\O (colonp atsignp params)
494   (expand-format-integer 8 colonp atsignp params))
495
496 (def-format-directive #\X (colonp atsignp params)
497   (expand-format-integer 16 colonp atsignp params))
498
499 (def-format-directive #\R (colonp atsignp params)
500   (expand-bind-defaults
501       ((base nil) (mincol 0) (padchar #\space) (commachar #\,)
502        (commainterval 3))
503       params
504     (let ((n-arg (gensym)))
505       `(let ((,n-arg ,(expand-next-arg)))
506          (if ,base
507              (format-print-integer stream ,n-arg ,colonp ,atsignp
508                                    ,base ,mincol
509                                    ,padchar ,commachar ,commainterval)
510              ,(if atsignp
511                   (if colonp
512                       `(format-print-old-roman stream ,n-arg)
513                       `(format-print-roman stream ,n-arg))
514                   (if colonp
515                       `(format-print-ordinal stream ,n-arg)
516                       `(format-print-cardinal stream ,n-arg))))))))
517 \f
518 ;;;; format directive for pluralization
519
520 (def-format-directive #\P (colonp atsignp params end)
521   (expand-bind-defaults () params
522     (let ((arg (cond
523                 ((not colonp)
524                  (expand-next-arg))
525                 (*orig-args-available*
526                  `(if (eq orig-args args)
527                       (error 'format-error
528                              :complaint "no previous argument"
529                              :offset ,(1- end))
530                       (do ((arg-ptr orig-args (cdr arg-ptr)))
531                           ((eq (cdr arg-ptr) args)
532                            (car arg-ptr)))))
533                 (*only-simple-args*
534                  (unless *simple-args*
535                    (error 'format-error
536                           :complaint "no previous argument"))
537                  (caar *simple-args*))
538                 (t
539                  (/show0 "THROWing NEED-ORIG-ARGS from tilde-P")
540                  (throw 'need-orig-args nil)))))
541       (if atsignp
542           `(write-string (if (eql ,arg 1) "y" "ies") stream)
543           `(unless (eql ,arg 1) (write-char #\s stream))))))
544 \f
545 ;;;; format directives for floating point output
546
547 (def-format-directive #\F (colonp atsignp params)
548   (when colonp
549     (error 'format-error
550            :complaint
551            "The colon modifier cannot be used with this directive."))
552   (expand-bind-defaults ((w nil) (d nil) (k nil) (ovf nil) (pad #\space)) params
553     `(format-fixed stream ,(expand-next-arg) ,w ,d ,k ,ovf ,pad ,atsignp)))
554
555 (def-format-directive #\E (colonp atsignp params)
556   (when colonp
557     (error 'format-error
558            :complaint
559            "The colon modifier cannot be used with this directive."))
560   (expand-bind-defaults
561       ((w nil) (d nil) (e nil) (k 1) (ovf nil) (pad #\space) (mark nil))
562       params
563     `(format-exponential stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark
564                          ,atsignp)))
565
566 (def-format-directive #\G (colonp atsignp params)
567   (when colonp
568     (error 'format-error
569            :complaint
570            "The colon modifier cannot be used with this directive."))
571   (expand-bind-defaults
572       ((w nil) (d nil) (e nil) (k nil) (ovf nil) (pad #\space) (mark nil))
573       params
574     `(format-general stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark ,atsignp)))
575
576 (def-format-directive #\$ (colonp atsignp params)
577   (expand-bind-defaults ((d 2) (n 1) (w 0) (pad #\space)) params
578     `(format-dollars stream ,(expand-next-arg) ,d ,n ,w ,pad ,colonp
579                      ,atsignp)))
580 \f
581 ;;;; format directives for line/page breaks etc.
582
583 (def-format-directive #\% (colonp atsignp params)
584   (when (or colonp atsignp)
585     (error 'format-error
586            :complaint
587            "The colon and atsign modifiers cannot be used with this directive."
588            ))
589   (if params
590       (expand-bind-defaults ((count 1)) params
591         `(dotimes (i ,count)
592            (terpri stream)))
593       '(terpri stream)))
594
595 (def-format-directive #\& (colonp atsignp params)
596   (when (or colonp atsignp)
597     (error 'format-error
598            :complaint
599            "The colon and atsign modifiers cannot be used with this directive."
600            ))
601   (if params
602       (expand-bind-defaults ((count 1)) params
603         `(progn
604            (fresh-line stream)
605            (dotimes (i (1- ,count))
606              (terpri stream))))
607       '(fresh-line stream)))
608
609 (def-format-directive #\| (colonp atsignp params)
610   (when (or colonp atsignp)
611     (error 'format-error
612            :complaint
613            "The colon and atsign modifiers cannot be used with this directive."
614            ))
615   (if params
616       (expand-bind-defaults ((count 1)) params
617         `(dotimes (i ,count)
618            (write-char (code-char form-feed-char-code) stream)))
619       '(write-char (code-char form-feed-char-code) stream)))
620
621 (def-format-directive #\~ (colonp atsignp params)
622   (when (or colonp atsignp)
623     (error 'format-error
624            :complaint
625            "The colon and atsign modifiers cannot be used with this directive."
626            ))
627   (if params
628       (expand-bind-defaults ((count 1)) params
629         `(dotimes (i ,count)
630            (write-char #\~ stream)))
631       '(write-char #\~ stream)))
632
633 (def-complex-format-directive #\newline (colonp atsignp params directives)
634   (when (and colonp atsignp)
635     (error 'format-error
636            :complaint "both colon and atsign modifiers used simultaneously"))
637   (values (expand-bind-defaults () params
638             (if atsignp
639                 '(write-char #\newline stream)
640                 nil))
641           (if (and (not colonp)
642                    directives
643                    (simple-string-p (car directives)))
644               (cons (string-left-trim *format-whitespace-chars*
645                                       (car directives))
646                     (cdr directives))
647               directives)))
648 \f
649 ;;;; format directives for tabs and simple pretty printing
650
651 (def-format-directive #\T (colonp atsignp params)
652   (if colonp
653       (expand-bind-defaults ((n 1) (m 1)) params
654         `(pprint-tab ,(if atsignp :section-relative :section)
655                      ,n ,m stream))
656       (if atsignp
657           (expand-bind-defaults ((colrel 1) (colinc 1)) params
658             `(format-relative-tab stream ,colrel ,colinc))
659           (expand-bind-defaults ((colnum 1) (colinc 1)) params
660             `(format-absolute-tab stream ,colnum ,colinc)))))
661
662 (def-format-directive #\_ (colonp atsignp params)
663   (expand-bind-defaults () params
664     `(pprint-newline ,(if colonp
665                           (if atsignp
666                               :mandatory
667                               :fill)
668                           (if atsignp
669                               :miser
670                               :linear))
671                      stream)))
672
673 (def-format-directive #\I (colonp atsignp params)
674   (when atsignp
675     (error 'format-error
676            :complaint
677            "cannot use the at-sign modifier with this directive"))
678   (expand-bind-defaults ((n 0)) params
679     `(pprint-indent ,(if colonp :current :block) ,n stream)))
680 \f
681 ;;;; format directive for ~*
682
683 (def-format-directive #\* (colonp atsignp params end)
684   (if atsignp
685       (if colonp
686           (error 'format-error
687                  :complaint
688                  "both colon and atsign modifiers used simultaneously")
689           (expand-bind-defaults ((posn 0)) params
690             (unless *orig-args-available*
691               (/show0 "THROWing NEED-ORIG-ARGS from tilde-@*")
692               (throw 'need-orig-args nil))
693             `(if (<= 0 ,posn (length orig-args))
694                  (setf args (nthcdr ,posn orig-args))
695                  (error 'format-error
696                         :complaint "Index ~W out of bounds. Should have been ~
697                                     between 0 and ~W."
698                         :args (list ,posn (length orig-args))
699                         :offset ,(1- end)))))
700       (if colonp
701           (expand-bind-defaults ((n 1)) params
702             (unless *orig-args-available*
703               (/show0 "THROWing NEED-ORIG-ARGS from tilde-:*")
704               (throw 'need-orig-args nil))
705             `(do ((cur-posn 0 (1+ cur-posn))
706                   (arg-ptr orig-args (cdr arg-ptr)))
707                  ((eq arg-ptr args)
708                   (let ((new-posn (- cur-posn ,n)))
709                     (if (<= 0 new-posn (length orig-args))
710                         (setf args (nthcdr new-posn orig-args))
711                         (error 'format-error
712                                :complaint
713                                "Index ~W is out of bounds; should have been ~
714                                 between 0 and ~W."
715                                :args (list new-posn (length orig-args))
716                                :offset ,(1- end)))))))
717           (if params
718               (expand-bind-defaults ((n 1)) params
719                 (setf *only-simple-args* nil)
720                 `(dotimes (i ,n)
721                    ,(expand-next-arg)))
722               (expand-next-arg)))))
723 \f
724 ;;;; format directive for indirection
725
726 (def-format-directive #\? (colonp atsignp params string end)
727   (when colonp
728     (error 'format-error
729            :complaint "cannot use the colon modifier with this directive"))
730   (expand-bind-defaults () params
731     `(handler-bind
732          ((format-error
733            (lambda (condition)
734              (error 'format-error
735                     :complaint
736                     "~A~%while processing indirect format string:"
737                     :args (list condition)
738                     :print-banner nil
739                     :control-string ,string
740                     :offset ,(1- end)))))
741        ,(if atsignp
742             (if *orig-args-available*
743                 `(setf args (%format stream ,(expand-next-arg) orig-args args))
744                 (throw 'need-orig-args nil))
745             `(%format stream ,(expand-next-arg) ,(expand-next-arg))))))
746 \f
747 ;;;; format directives for capitalization
748
749 (def-complex-format-directive #\( (colonp atsignp params directives)
750   (let ((close (find-directive directives #\) nil)))
751     (unless close
752       (error 'format-error
753              :complaint "no corresponding close parenthesis"))
754     (let* ((posn (position close directives))
755            (before (subseq directives 0 posn))
756            (after (nthcdr (1+ posn) directives)))
757       (values
758        (expand-bind-defaults () params
759          `(let ((stream (make-case-frob-stream stream
760                                                ,(if colonp
761                                                     (if atsignp
762                                                         :upcase
763                                                         :capitalize)
764                                                     (if atsignp
765                                                         :capitalize-first
766                                                         :downcase)))))
767             ,@(expand-directive-list before)))
768        after))))
769
770 (def-complex-format-directive #\) ()
771   (error 'format-error
772          :complaint "no corresponding open parenthesis"))
773 \f
774 ;;;; format directives and support functions for conditionalization
775
776 (def-complex-format-directive #\[ (colonp atsignp params directives)
777   (multiple-value-bind (sublists last-semi-with-colon-p remaining)
778       (parse-conditional-directive directives)
779     (values
780      (if atsignp
781          (if colonp
782              (error 'format-error
783                     :complaint
784                     "both colon and atsign modifiers used simultaneously")
785              (if (cdr sublists)
786                  (error 'format-error
787                         :complaint
788                         "Can only specify one section")
789                  (expand-bind-defaults () params
790                    (expand-maybe-conditional (car sublists)))))
791          (if colonp
792              (if (= (length sublists) 2)
793                  (expand-bind-defaults () params
794                    (expand-true-false-conditional (car sublists)
795                                                   (cadr sublists)))
796                  (error 'format-error
797                         :complaint
798                         "must specify exactly two sections"))
799              (expand-bind-defaults ((index nil)) params
800                (setf *only-simple-args* nil)
801                (let ((clauses nil)
802                      (case `(or ,index ,(expand-next-arg))))
803                  (when last-semi-with-colon-p
804                    (push `(t ,@(expand-directive-list (pop sublists)))
805                          clauses))
806                  (let ((count (length sublists)))
807                    (dolist (sublist sublists)
808                      (push `(,(decf count)
809                              ,@(expand-directive-list sublist))
810                            clauses)))
811                  `(case ,case ,@clauses)))))
812      remaining)))
813
814 (defun parse-conditional-directive (directives)
815   (let ((sublists nil)
816         (last-semi-with-colon-p nil)
817         (remaining directives))
818     (loop
819       (let ((close-or-semi (find-directive remaining #\] t)))
820         (unless close-or-semi
821           (error 'format-error
822                  :complaint "no corresponding close bracket"))
823         (let ((posn (position close-or-semi remaining)))
824           (push (subseq remaining 0 posn) sublists)
825           (setf remaining (nthcdr (1+ posn) remaining))
826           (when (char= (format-directive-character close-or-semi) #\])
827             (return))
828           (setf last-semi-with-colon-p
829                 (format-directive-colonp close-or-semi)))))
830     (values sublists last-semi-with-colon-p remaining)))
831
832 (defun expand-maybe-conditional (sublist)
833   (flet ((hairy ()
834            `(let ((prev-args args)
835                   (arg ,(expand-next-arg)))
836               (when arg
837                 (setf args prev-args)
838                 ,@(expand-directive-list sublist)))))
839     (if *only-simple-args*
840         (multiple-value-bind (guts new-args)
841             (let ((*simple-args* *simple-args*))
842               (values (expand-directive-list sublist)
843                       *simple-args*))
844           (cond ((and new-args (eq *simple-args* (cdr new-args)))
845                  (setf *simple-args* new-args)
846                  `(when ,(caar new-args)
847                     ,@guts))
848                 (t
849                  (setf *only-simple-args* nil)
850                  (hairy))))
851         (hairy))))
852
853 (defun expand-true-false-conditional (true false)
854   (let ((arg (expand-next-arg)))
855     (flet ((hairy ()
856              `(if ,arg
857                   (progn
858                     ,@(expand-directive-list true))
859                   (progn
860                     ,@(expand-directive-list false)))))
861       (if *only-simple-args*
862           (multiple-value-bind (true-guts true-args true-simple)
863               (let ((*simple-args* *simple-args*)
864                     (*only-simple-args* t))
865                 (values (expand-directive-list true)
866                         *simple-args*
867                         *only-simple-args*))
868             (multiple-value-bind (false-guts false-args false-simple)
869                 (let ((*simple-args* *simple-args*)
870                       (*only-simple-args* t))
871                   (values (expand-directive-list false)
872                           *simple-args*
873                           *only-simple-args*))
874               (if (= (length true-args) (length false-args))
875                   `(if ,arg
876                        (progn
877                          ,@true-guts)
878                        ,(do ((false false-args (cdr false))
879                              (true true-args (cdr true))
880                              (bindings nil (cons `(,(caar false) ,(caar true))
881                                                  bindings)))
882                             ((eq true *simple-args*)
883                              (setf *simple-args* true-args)
884                              (setf *only-simple-args*
885                                    (and true-simple false-simple))
886                              (if bindings
887                                  `(let ,bindings
888                                     ,@false-guts)
889                                  `(progn
890                                     ,@false-guts)))))
891                   (progn
892                     (setf *only-simple-args* nil)
893                     (hairy)))))
894           (hairy)))))
895
896 (def-complex-format-directive #\; ()
897   (error 'format-error
898          :complaint
899          "~~; directive not contained within either ~~[...~~] or ~~<...~~>"))
900
901 (def-complex-format-directive #\] ()
902   (error 'format-error
903          :complaint
904          "no corresponding open bracket"))
905 \f
906 ;;;; format directive for up-and-out
907
908 (def-format-directive #\^ (colonp atsignp params)
909   (when atsignp
910     (error 'format-error
911            :complaint "cannot use the at-sign modifier with this directive"))
912   (when (and colonp (not *up-up-and-out-allowed*))
913     (error 'format-error
914            :complaint "attempt to use ~~:^ outside a ~~:{...~~} construct"))
915   `(when ,(expand-bind-defaults ((arg1 nil) (arg2 nil) (arg3 nil)) params
916             `(cond (,arg3 (<= ,arg1 ,arg2 ,arg3))
917                    (,arg2 (eql ,arg1 ,arg2))
918                    (,arg1 (eql ,arg1 0))
919                    (t ,(if colonp
920                            '(null outside-args)
921                            (progn
922                              (setf *only-simple-args* nil)
923                              '(null args))))))
924      ,(if colonp
925           '(return-from outside-loop nil)
926           '(return))))
927 \f
928 ;;;; format directives for iteration
929
930 (def-complex-format-directive #\{ (colonp atsignp params string end directives)
931   (let ((close (find-directive directives #\} nil)))
932     (unless close
933       (error 'format-error
934              :complaint "no corresponding close brace"))
935     (let* ((closed-with-colon (format-directive-colonp close))
936            (posn (position close directives)))
937       (labels
938           ((compute-insides ()
939              (if (zerop posn)
940                  (if *orig-args-available*
941                      `((handler-bind
942                            ((format-error
943                              (lambda (condition)
944                                (error 'format-error
945                                       :complaint
946                               "~A~%while processing indirect format string:"
947                                       :args (list condition)
948                                       :print-banner nil
949                                       :control-string ,string
950                                       :offset ,(1- end)))))
951                          (setf args
952                                (%format stream inside-string orig-args args))))
953                      (throw 'need-orig-args nil))
954                  (let ((*up-up-and-out-allowed* colonp))
955                    (expand-directive-list (subseq directives 0 posn)))))
956            (compute-loop (count)
957              (when atsignp
958                (setf *only-simple-args* nil))
959              `(loop
960                 ,@(unless closed-with-colon
961                     '((when (null args)
962                         (return))))
963                 ,@(when count
964                     `((when (and ,count (minusp (decf ,count)))
965                         (return))))
966                 ,@(if colonp
967                       (let ((*expander-next-arg-macro* 'expander-next-arg)
968                             (*only-simple-args* nil)
969                             (*orig-args-available* t))
970                         `((let* ((orig-args ,(expand-next-arg))
971                                  (outside-args args)
972                                  (args orig-args))
973                             (declare (ignorable orig-args outside-args args))
974                             (block nil
975                               ,@(compute-insides)))))
976                       (compute-insides))
977                 ,@(when closed-with-colon
978                     '((when (null args)
979                         (return))))))
980            (compute-block (count)
981              (if colonp
982                  `(block outside-loop
983                     ,(compute-loop count))
984                  (compute-loop count)))
985            (compute-bindings (count)
986              (if atsignp
987                  (compute-block count)
988                  `(let* ((orig-args ,(expand-next-arg))
989                          (args orig-args))
990                    (declare (ignorable orig-args args))
991                    ,(let ((*expander-next-arg-macro* 'expander-next-arg)
992                           (*only-simple-args* nil)
993                           (*orig-args-available* t))
994                       (compute-block count))))))
995         (values (if params
996                     (expand-bind-defaults ((count nil)) params
997                       (if (zerop posn)
998                           `(let ((inside-string ,(expand-next-arg)))
999                             ,(compute-bindings count))
1000                           (compute-bindings count)))
1001                     (if (zerop posn)
1002                         `(let ((inside-string ,(expand-next-arg)))
1003                           ,(compute-bindings nil))
1004                         (compute-bindings nil)))
1005                 (nthcdr (1+ posn) directives))))))
1006
1007 (def-complex-format-directive #\} ()
1008   (error 'format-error
1009          :complaint "no corresponding open brace"))
1010 \f
1011 ;;;; format directives and support functions for justification
1012
1013 (defparameter *illegal-inside-justification*
1014   (mapcar (lambda (x) (parse-directive x 0))
1015           '("~W" "~:W" "~@W" "~:@W"
1016             "~_" "~:_" "~@_" "~:@_"
1017             "~:>" "~:@>"
1018             "~I" "~:I" "~@I" "~:@I"
1019             "~:T" "~:@T")))
1020
1021 (defun illegal-inside-justification-p (directive)
1022   (member directive *illegal-inside-justification*
1023           :test (lambda (x y)
1024                   (and (format-directive-p x)
1025                        (format-directive-p y)
1026                        (eql (format-directive-character x) (format-directive-character y))
1027                        (eql (format-directive-colonp x) (format-directive-colonp y))
1028                        (eql (format-directive-atsignp x) (format-directive-atsignp y))))))
1029
1030 (def-complex-format-directive #\< (colonp atsignp params string end directives)
1031   (multiple-value-bind (segments first-semi close remaining)
1032       (parse-format-justification directives)
1033     (values
1034      (if (format-directive-colonp close)
1035          (multiple-value-bind (prefix per-line-p insides suffix)
1036              (parse-format-logical-block segments colonp first-semi
1037                                          close params string end)
1038            (expand-format-logical-block prefix per-line-p insides
1039                                         suffix atsignp))
1040          (let ((count (reduce #'+ (mapcar (lambda (x) (count-if #'illegal-inside-justification-p x)) segments))))
1041            (when (> count 0)
1042              ;; ANSI specifies that "an error is signalled" in this
1043              ;; situation.
1044              (error 'format-error
1045                     :complaint "~D illegal directive~:P found inside justification block"
1046                     :args (list count)
1047                     :references (list '(:ansi-cl :section (22 3 5 2)))))
1048            (expand-format-justification segments colonp atsignp
1049                                         first-semi params)))
1050      remaining)))
1051
1052 (def-complex-format-directive #\> ()
1053   (error 'format-error
1054          :complaint "no corresponding open bracket"))
1055
1056 (defun parse-format-logical-block
1057        (segments colonp first-semi close params string end)
1058   (when params
1059     (error 'format-error
1060            :complaint "No parameters can be supplied with ~~<...~~:>."
1061            :offset (caar params)))
1062   (multiple-value-bind (prefix insides suffix)
1063       (multiple-value-bind (prefix-default suffix-default)
1064           (if colonp (values "(" ")") (values "" ""))
1065         (flet ((extract-string (list prefix-p)
1066                  (let ((directive (find-if #'format-directive-p list)))
1067                    (if directive
1068                        (error 'format-error
1069                               :complaint
1070                               "cannot include format directives inside the ~
1071                                ~:[suffix~;prefix~] segment of ~~<...~~:>"
1072                               :args (list prefix-p)
1073                               :offset (1- (format-directive-end directive))
1074                               :references
1075                               (list '(:ansi-cl :section (22 3 5 2))))
1076                        (apply #'concatenate 'string list)))))
1077         (case (length segments)
1078           (0 (values prefix-default nil suffix-default))
1079           (1 (values prefix-default (car segments) suffix-default))
1080           (2 (values (extract-string (car segments) t)
1081                      (cadr segments) suffix-default))
1082           (3 (values (extract-string (car segments) t)
1083                      (cadr segments)
1084                      (extract-string (caddr segments) nil)))
1085           (t
1086            (error 'format-error
1087                   :complaint "too many segments for ~~<...~~:>")))))
1088     (when (format-directive-atsignp close)
1089       (setf insides
1090             (add-fill-style-newlines insides
1091                                      string
1092                                      (if first-semi
1093                                          (format-directive-end first-semi)
1094                                          end))))
1095     (values prefix
1096             (and first-semi (format-directive-atsignp first-semi))
1097             insides
1098             suffix)))
1099
1100 (defun add-fill-style-newlines (list string offset &optional last-directive)
1101   (cond
1102     (list
1103      (let ((directive (car list)))
1104        (cond
1105          ((simple-string-p directive)
1106           (let* ((non-space (position #\Space directive :test #'char/=))
1107                  (newlinep (and last-directive
1108                                 (char=
1109                                  (format-directive-character last-directive)
1110                                  #\Newline))))
1111             (cond
1112               ((and newlinep non-space)
1113                (nconc
1114                 (list (subseq directive 0 non-space))
1115                 (add-fill-style-newlines-aux
1116                  (subseq directive non-space) string (+ offset non-space))
1117                 (add-fill-style-newlines
1118                  (cdr list) string (+ offset (length directive)))))
1119               (newlinep
1120                (cons directive
1121                      (add-fill-style-newlines
1122                       (cdr list) string (+ offset (length directive)))))
1123               (t
1124                (nconc (add-fill-style-newlines-aux directive string offset)
1125                       (add-fill-style-newlines
1126                        (cdr list) string (+ offset (length directive))))))))
1127          (t
1128           (cons directive
1129                 (add-fill-style-newlines
1130                  (cdr list) string
1131                  (format-directive-end directive) directive))))))
1132     (t nil)))
1133
1134 (defun add-fill-style-newlines-aux (literal string offset)
1135   (let ((end (length literal))
1136         (posn 0))
1137     (collect ((results))
1138       (loop
1139         (let ((blank (position #\space literal :start posn)))
1140           (when (null blank)
1141             (results (subseq literal posn))
1142             (return))
1143           (let ((non-blank (or (position #\space literal :start blank
1144                                          :test #'char/=)
1145                                end)))
1146             (results (subseq literal posn non-blank))
1147             (results (make-format-directive
1148                       :string string :character #\_
1149                       :start (+ offset non-blank) :end (+ offset non-blank)
1150                       :colonp t :atsignp nil :params nil))
1151             (setf posn non-blank))
1152           (when (= posn end)
1153             (return))))
1154       (results))))
1155
1156 (defun parse-format-justification (directives)
1157   (let ((first-semi nil)
1158         (close nil)
1159         (remaining directives))
1160     (collect ((segments))
1161       (loop
1162         (let ((close-or-semi (find-directive remaining #\> t)))
1163           (unless close-or-semi
1164             (error 'format-error
1165                    :complaint "no corresponding close bracket"))
1166           (let ((posn (position close-or-semi remaining)))
1167             (segments (subseq remaining 0 posn))
1168             (setf remaining (nthcdr (1+ posn) remaining)))
1169           (when (char= (format-directive-character close-or-semi)
1170                        #\>)
1171             (setf close close-or-semi)
1172             (return))
1173           (unless first-semi
1174             (setf first-semi close-or-semi))))
1175       (values (segments) first-semi close remaining))))
1176
1177 (sb!xc:defmacro expander-pprint-next-arg (string offset)
1178   `(progn
1179      (when (null args)
1180        (error 'format-error
1181               :complaint "no more arguments"
1182               :control-string ,string
1183               :offset ,offset))
1184      (pprint-pop)
1185      (pop args)))
1186
1187 (defun expand-format-logical-block (prefix per-line-p insides suffix atsignp)
1188   `(let ((arg ,(if atsignp 'args (expand-next-arg))))
1189      ,@(when atsignp
1190          (setf *only-simple-args* nil)
1191          '((setf args nil)))
1192      (pprint-logical-block
1193          (stream arg
1194                  ,(if per-line-p :per-line-prefix :prefix) ,prefix
1195                  :suffix ,suffix)
1196        (let ((args arg)
1197              ,@(unless atsignp
1198                  `((orig-args arg))))
1199          (declare (ignorable args ,@(unless atsignp '(orig-args))))
1200          (block nil
1201            ,@(let ((*expander-next-arg-macro* 'expander-pprint-next-arg)
1202                    (*only-simple-args* nil)
1203                    (*orig-args-available*
1204                     (if atsignp *orig-args-available* t)))
1205                (expand-directive-list insides)))))))
1206
1207 (defun expand-format-justification (segments colonp atsignp first-semi params)
1208   (let ((newline-segment-p
1209          (and first-semi
1210               (format-directive-colonp first-semi))))
1211     (expand-bind-defaults
1212         ((mincol 0) (colinc 1) (minpad 0) (padchar #\space))
1213         params
1214       `(let ((segments nil)
1215              ,@(when newline-segment-p
1216                  '((newline-segment nil)
1217                    (extra-space 0)
1218                    (line-len 72))))
1219          (block nil
1220            ,@(when newline-segment-p
1221                `((setf newline-segment
1222                        (with-output-to-string (stream)
1223                          ,@(expand-directive-list (pop segments))))
1224                  ,(expand-bind-defaults
1225                       ((extra 0)
1226                        (line-len '(or (sb!impl::line-length stream) 72)))
1227                       (format-directive-params first-semi)
1228                     `(setf extra-space ,extra line-len ,line-len))))
1229            ,@(mapcar (lambda (segment)
1230                        `(push (with-output-to-string (stream)
1231                                 ,@(expand-directive-list segment))
1232                               segments))
1233                      segments))
1234          (format-justification stream
1235                                ,@(if newline-segment-p
1236                                      '(newline-segment extra-space line-len)
1237                                      '(nil 0 0))
1238                                segments ,colonp ,atsignp
1239                                ,mincol ,colinc ,minpad ,padchar)))))
1240 \f
1241 ;;;; format directive and support function for user-defined method
1242
1243 (def-format-directive #\/ (string start end colonp atsignp params)
1244   (let ((symbol (extract-user-fun-name string start end)))
1245     (collect ((param-names) (bindings))
1246       (dolist (param-and-offset params)
1247         (let ((param (cdr param-and-offset)))
1248           (let ((param-name (gensym)))
1249             (param-names param-name)
1250             (bindings `(,param-name
1251                         ,(case param
1252                            (:arg (expand-next-arg))
1253                            (:remaining '(length args))
1254                            (t param)))))))
1255       `(let ,(bindings)
1256          (,symbol stream ,(expand-next-arg) ,colonp ,atsignp
1257                   ,@(param-names))))))
1258
1259 (defun extract-user-fun-name (string start end)
1260   (let ((slash (position #\/ string :start start :end (1- end)
1261                          :from-end t)))
1262     (unless slash
1263       (error 'format-error
1264              :complaint "malformed ~~/ directive"))
1265     (let* ((name (string-upcase (let ((foo string))
1266                                   ;; Hack alert: This is to keep the compiler
1267                                   ;; quiet about deleting code inside the
1268                                   ;; subseq expansion.
1269                                   (subseq foo (1+ slash) (1- end)))))
1270            (first-colon (position #\: name))
1271            (second-colon (if first-colon (position #\: name :start (1+ first-colon))))
1272            (package-name (if first-colon
1273                              (subseq name 0 first-colon)
1274                              "COMMON-LISP-USER"))
1275            (package (find-package package-name)))
1276       (unless package
1277         ;; FIXME: should be PACKAGE-ERROR? Could we just use
1278         ;; FIND-UNDELETED-PACKAGE-OR-LOSE?
1279         (error 'format-error
1280                :complaint "no package named ~S"
1281                :args (list package-name)))
1282       (intern (cond
1283                 ((and second-colon (= second-colon (1+ first-colon)))
1284                  (subseq name (1+ second-colon)))
1285                 (first-colon
1286                  (subseq name (1+ first-colon)))
1287                 (t name))
1288               package))))
1289
1290 ;;; compile-time checking for argument mismatch.  This code is
1291 ;;; inspired by that of Gerd Moellmann, and comes decorated with
1292 ;;; FIXMEs:
1293 (defun %compiler-walk-format-string (string args)
1294   (declare (type simple-string string))
1295   (let ((*default-format-error-control-string* string))
1296     (macrolet ((incf-both (&optional (increment 1))
1297                  `(progn
1298                    (incf min ,increment)
1299                    (incf max ,increment)))
1300                (walk-complex-directive (function)
1301                  `(multiple-value-bind (min-inc max-inc remaining)
1302                    (,function directive directives args)
1303                    (incf min min-inc)
1304                    (incf max max-inc)
1305                    (setq directives remaining))))
1306       ;; FIXME: these functions take a list of arguments as well as
1307       ;; the directive stream.  This is to enable possibly some
1308       ;; limited type checking on FORMAT's arguments, as well as
1309       ;; simple argument count mismatch checking: when the minimum and
1310       ;; maximum argument counts are the same at a given point, we
1311       ;; know which argument is going to be used for a given
1312       ;; directive, and some (annotated below) require arguments of
1313       ;; particular types.
1314       (labels
1315           ((walk-justification (justification directives args)
1316              (declare (ignore args))
1317              (let ((*default-format-error-offset*
1318                     (1- (format-directive-end justification))))
1319                (multiple-value-bind (segments first-semi close remaining)
1320                    (parse-format-justification directives)
1321                  (declare (ignore segments first-semi))
1322                  (cond
1323                    ((not (format-directive-colonp close))
1324                     (values 0 0 directives))
1325                    ((format-directive-atsignp justification)
1326                     (values 0 sb!xc:call-arguments-limit directives))
1327                    ;; FIXME: here we could assert that the
1328                    ;; corresponding argument was a list.
1329                    (t (values 1 1 remaining))))))
1330            (walk-conditional (conditional directives args)
1331              (let ((*default-format-error-offset*
1332                     (1- (format-directive-end conditional))))
1333                (multiple-value-bind (sublists last-semi-with-colon-p remaining)
1334                    (parse-conditional-directive directives)
1335                  (declare (ignore last-semi-with-colon-p))
1336                  (let ((sub-max
1337                         (loop for s in sublists
1338                               maximize (nth-value
1339                                         1 (walk-directive-list s args)))))
1340                    (cond
1341                      ((format-directive-atsignp conditional)
1342                       (values 1 (max 1 sub-max) remaining))
1343                      ((loop for p in (format-directive-params conditional)
1344                             thereis (or (integerp (cdr p))
1345                                         (memq (cdr p) '(:remaining :arg))))
1346                       (values 0 sub-max remaining))
1347                      ;; FIXME: if not COLONP, then the next argument
1348                      ;; must be a number.
1349                      (t (values 1 (1+ sub-max) remaining)))))))
1350            (walk-iteration (iteration directives args)
1351              (declare (ignore args))
1352              (let ((*default-format-error-offset*
1353                     (1- (format-directive-end iteration))))
1354                (let* ((close (find-directive directives #\} nil))
1355                       (posn (or (position close directives)
1356                                 (error 'format-error
1357                                        :complaint "no corresponding close brace")))
1358                       (remaining (nthcdr (1+ posn) directives)))
1359                  ;; FIXME: if POSN is zero, the next argument must be
1360                  ;; a format control (either a function or a string).
1361                  (if (format-directive-atsignp iteration)
1362                      (values (if (zerop posn) 1 0)
1363                              sb!xc:call-arguments-limit
1364                              remaining)
1365                      ;; FIXME: the argument corresponding to this
1366                      ;; directive must be a list.
1367                      (let ((nreq (if (zerop posn) 2 1)))
1368                        (values nreq nreq remaining))))))
1369            (walk-directive-list (directives args)
1370              (let ((min 0) (max 0))
1371                (loop
1372                 (let ((directive (pop directives)))
1373                   (when (null directive)
1374                     (return (values min (min max sb!xc:call-arguments-limit))))
1375                   (when (format-directive-p directive)
1376                     (incf-both (count :arg (format-directive-params directive)
1377                                       :key #'cdr))
1378                     (let ((c (format-directive-character directive)))
1379                       (cond
1380                         ((find c "ABCDEFGORSWX$/")
1381                          (incf-both))
1382                         ((char= c #\P)
1383                          (unless (format-directive-colonp directive)
1384                            (incf-both)))
1385                         ((or (find c "IT%&|_();>~") (char= c #\Newline)))
1386                         ;; FIXME: check correspondence of ~( and ~)
1387                         ((char= c #\<)
1388                          (walk-complex-directive walk-justification))
1389                         ((char= c #\[)
1390                          (walk-complex-directive walk-conditional))
1391                         ((char= c #\{)
1392                          (walk-complex-directive walk-iteration))
1393                         ((char= c #\?)
1394                          ;; FIXME: the argument corresponding to this
1395                          ;; directive must be a format control.
1396                          (cond
1397                            ((format-directive-atsignp directive)
1398                             (incf min)
1399                             (setq max sb!xc:call-arguments-limit))
1400                            (t (incf-both 2))))
1401                         (t (throw 'give-up-format-string-walk nil))))))))))
1402         (catch 'give-up-format-string-walk
1403           (let ((directives (tokenize-control-string string)))
1404             (walk-directive-list directives args)))))))