1 ;;;; This software is part of the SBCL system. See the README file for
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.
10 (in-package "SB!FORMAT")
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
24 (:report %print-format-error)
25 (:default-initargs :references nil))
27 (defun %print-format-error (condition stream)
29 "~:[~*~;error in ~S: ~]~?~@[~% ~A~% ~V@T^~@[~V@T^~]~]"
30 (format-error-print-banner condition)
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)))
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)
50 :start (format-directive-start x)
51 :end (format-directive-end x))))
53 ;;;; TOKENIZE-CONTROL-STRING
55 (defun tokenize-control-string (string)
56 (declare (simple-string string))
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.
66 (justification-semicolon))
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)
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
77 ((char= char #\<) (push directive block))
78 ((and block (char= char #\;) (format-directive-colonp directive))
79 (setf semicolon directive))
83 :complaint "~~> without a matching ~~<"
84 :control-string string
85 :offset next-directive))
87 ((format-directive-colonp directive)
89 (setf pprint (car block)))
92 (unless justification-semicolon
93 (setf justification-semicolon semicolon))))
95 ;; block cases are handled by the #\< expander/interpreter
98 ((#\W #\I #\_) (unless pprint (setf pprint directive)))
99 (#\T (when (and (format-directive-colonp directive)
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))))
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)
115 :references (list '(:ansi-cl :section (22 3 5 2))))))
118 (defun parse-directive (string start)
119 (let ((posn (1+ start)) (params nil) (colonp nil) (atsignp nil)
120 (end (length string)))
124 :complaint "string ended before directive was found"
125 :control-string string
127 (schar string posn)))
129 (when (or colonp atsignp)
131 :complaint "parameters found after #\\: or #\\@ modifier"
132 :control-string string
134 :references (list '(:ansi-cl :section (22 3)))))))
136 (let ((char (get-char)))
137 (cond ((or (char<= #\0 char #\9) (char= char #\+) (char= char #\-))
139 (multiple-value-bind (param new-posn)
140 (parse-integer string :start posn :junk-allowed t)
141 (push (cons posn param) params)
149 ((or (char= char #\v)
152 (push (cons posn :arg) params)
162 (push (cons posn :remaining) params)
173 (push (cons posn (get-char)) params)
175 (unless (char= (get-char) #\,)
179 (push (cons posn nil) params))
183 :complaint "too many colons supplied"
184 :control-string string
186 :references (list '(:ansi-cl :section (22 3))))
191 :complaint "too many #\\@ characters supplied"
192 :control-string string
194 :references (list '(:ansi-cl :section (22 3))))
197 (when (and (char= (schar string (1- posn)) #\,)
199 (char/= (schar string (- posn 2)) #\')))
201 (push (cons (1- posn) nil) params))
204 (let ((char (get-char)))
205 (when (char= char #\/)
206 (let ((closing-slash (position #\/ string :start (1+ posn))))
208 (setf posn closing-slash)
210 :complaint "no matching closing slash"
211 :control-string string
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))))))
221 (sb!xc:defmacro formatter (control-string)
222 `#',(%formatter control-string))
224 (defun %formatter (control-string)
226 (catch 'need-orig-args
227 (let* ((*simple-args* nil)
228 (*only-simple-args* t)
229 (guts (expand-control-string control-string))
231 (dolist (arg *simple-args*)
235 :complaint "required argument missing"
236 :control-string ,control-string
239 (return `(lambda (stream &optional ,@args &rest 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)
249 (defun expand-control-string (string)
250 (let* ((string (etypecase string
254 (coerce string 'simple-string))))
255 (*default-format-error-control-string* string)
256 (directives (tokenize-control-string string)))
258 ,@(expand-directive-list directives))))
260 (defun expand-directive-list (directives)
262 (remaining-directives directives))
264 (unless remaining-directives
266 (multiple-value-bind (form new-directives)
267 (expand-directive (car remaining-directives)
268 (cdr remaining-directives))
270 (setf remaining-directives new-directives)))
273 (defun expand-directive (directive more-directives)
277 (let ((char (format-directive-character directive)))
280 (aref *format-directive-expanders* (char-code char)))
282 (*default-format-error-offset*
283 (1- (format-directive-end directive))))
284 (declare (type (or null function) expander))
286 (funcall expander directive more-directives)
288 :complaint "unknown directive ~@[(character: ~A)~]"
289 :args (list (char-name (format-directive-character directive)))))))
291 (values `(write-string ,directive stream)
294 (defmacro-mundanely expander-next-arg (string offset)
298 :complaint "no more arguments"
299 :control-string ,string
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*))
312 (defmacro expand-bind-defaults (specs params &body body)
313 (once-only ((params params))
315 (collect ((expander-bindings) (runtime-bindings))
317 (destructuring-bind (var default) spec
318 (let ((symbol (gensym)))
323 (let* ((param-and-offset (pop ,params))
324 (offset (car param-and-offset))
325 (param (cdr param-and-offset)))
327 (:arg `(or ,(expand-next-arg offset)
330 (setf *only-simple-args* nil)
334 `(let ,(expander-bindings)
335 `(let ,(list ,@(runtime-bindings))
340 "too many parameters, expected no more than ~W"
341 :args (list ,(length specs))
342 :offset (caar ,params)))
347 :complaint "too many parameters, expected none"
348 :offset (caar ,params)))
351 ;;;; format directive machinery
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"
359 (directives (if lambda-list (car (last lambda-list)) (gensym))))
361 (defun ,defun-name (,directive ,directives)
363 `((let ,(mapcar (lambda (var)
365 (,(symbolicate "FORMAT-DIRECTIVE-" var)
367 (butlast lambda-list))
369 `((declare (ignore ,directive ,directives))
371 (%set-format-directive-expander ,char #',defun-name))))
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))
377 (body-without-decls body))
379 (let ((form (car body-without-decls)))
380 (unless (and (consp form) (eq (car form) 'declare))
382 (push (pop body-without-decls) declarations)))
383 (setf declarations (reverse declarations))
384 `(def-complex-format-directive ,char (,@lambda-list ,directives)
386 (values (progn ,@body-without-decls)
389 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
391 (defun %set-format-directive-expander (char fn)
392 (setf (aref *format-directive-expanders* (char-code (char-upcase char))) fn)
395 (defun %set-format-directive-interpreter (char fn)
396 (setf (aref *format-directive-interpreters*
397 (char-code (char-upcase char)))
401 (defun find-directive (directives kind stop-at-semi)
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 #\;)))
410 (cdr (flet ((after (char)
411 (member (find-directive (cdr directives)
422 (find-directive (cdr directives) kind stop-at-semi)))))
426 ;;;; format directives for simple output
428 (def-format-directive #\A (colonp atsignp params)
430 (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
433 `(format-princ stream ,(expand-next-arg) ',colonp ',atsignp
434 ,mincol ,colinc ,minpad ,padchar))
436 `(or ,(expand-next-arg) "()")
440 (def-format-directive #\S (colonp atsignp params)
442 (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
445 `(format-prin1 stream ,(expand-next-arg) ,colonp ,atsignp
446 ,mincol ,colinc ,minpad ,padchar)))
448 `(let ((arg ,(expand-next-arg)))
451 (princ "()" stream))))
453 `(prin1 ,(expand-next-arg) stream))))
455 (def-format-directive #\C (colonp atsignp params)
456 (expand-bind-defaults () params
458 `(format-print-named-character ,(expand-next-arg) stream)
460 `(prin1 ,(expand-next-arg) stream)
461 `(write-char ,(expand-next-arg) stream)))))
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)))
469 '((*print-level* nil)
470 (*print-length* nil))))
471 (output-object ,(expand-next-arg) stream))
472 `(output-object ,(expand-next-arg) stream))))
474 ;;;; format directives for integer output
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))
481 `(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
482 ,base ,mincol ,padchar ,commachar
484 `(write ,(expand-next-arg) :stream stream :base ,base :radix nil
487 (def-format-directive #\D (colonp atsignp params)
488 (expand-format-integer 10 colonp atsignp params))
490 (def-format-directive #\B (colonp atsignp params)
491 (expand-format-integer 2 colonp atsignp params))
493 (def-format-directive #\O (colonp atsignp params)
494 (expand-format-integer 8 colonp atsignp params))
496 (def-format-directive #\X (colonp atsignp params)
497 (expand-format-integer 16 colonp atsignp params))
499 (def-format-directive #\R (colonp atsignp params)
500 (expand-bind-defaults
501 ((base nil) (mincol 0) (padchar #\space) (commachar #\,)
504 (let ((n-arg (gensym)))
505 `(let ((,n-arg ,(expand-next-arg)))
507 (format-print-integer stream ,n-arg ,colonp ,atsignp
509 ,padchar ,commachar ,commainterval)
512 `(format-print-old-roman stream ,n-arg)
513 `(format-print-roman stream ,n-arg))
515 `(format-print-ordinal stream ,n-arg)
516 `(format-print-cardinal stream ,n-arg))))))))
518 ;;;; format directive for pluralization
520 (def-format-directive #\P (colonp atsignp params end)
521 (expand-bind-defaults () params
525 (*orig-args-available*
526 `(if (eq orig-args args)
528 :complaint "no previous argument"
530 (do ((arg-ptr orig-args (cdr arg-ptr)))
531 ((eq (cdr arg-ptr) args)
534 (unless *simple-args*
536 :complaint "no previous argument"))
537 (caar *simple-args*))
539 (/show0 "THROWing NEED-ORIG-ARGS from tilde-P")
540 (throw 'need-orig-args nil)))))
542 `(write-string (if (eql ,arg 1) "y" "ies") stream)
543 `(unless (eql ,arg 1) (write-char #\s stream))))))
545 ;;;; format directives for floating point output
547 (def-format-directive #\F (colonp atsignp params)
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)))
555 (def-format-directive #\E (colonp atsignp params)
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))
563 `(format-exponential stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark
566 (def-format-directive #\G (colonp atsignp params)
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))
574 `(format-general stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark ,atsignp)))
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
581 ;;;; format directives for line/page breaks etc.
583 (def-format-directive #\% (colonp atsignp params)
584 (when (or colonp atsignp)
587 "The colon and atsign modifiers cannot be used with this directive."
590 (expand-bind-defaults ((count 1)) params
595 (def-format-directive #\& (colonp atsignp params)
596 (when (or colonp atsignp)
599 "The colon and atsign modifiers cannot be used with this directive."
602 (expand-bind-defaults ((count 1)) params
605 (dotimes (i (1- ,count))
607 '(fresh-line stream)))
609 (def-format-directive #\| (colonp atsignp params)
610 (when (or colonp atsignp)
613 "The colon and atsign modifiers cannot be used with this directive."
616 (expand-bind-defaults ((count 1)) params
618 (write-char (code-char form-feed-char-code) stream)))
619 '(write-char (code-char form-feed-char-code) stream)))
621 (def-format-directive #\~ (colonp atsignp params)
622 (when (or colonp atsignp)
625 "The colon and atsign modifiers cannot be used with this directive."
628 (expand-bind-defaults ((count 1)) params
630 (write-char #\~ stream)))
631 '(write-char #\~ stream)))
633 (def-complex-format-directive #\newline (colonp atsignp params directives)
634 (when (and colonp atsignp)
636 :complaint "both colon and atsign modifiers used simultaneously"))
637 (values (expand-bind-defaults () params
639 '(write-char #\newline stream)
641 (if (and (not colonp)
643 (simple-string-p (car directives)))
644 (cons (string-left-trim *format-whitespace-chars*
649 ;;;; format directives for tabs and simple pretty printing
651 (def-format-directive #\T (colonp atsignp params)
653 (expand-bind-defaults ((n 1) (m 1)) params
654 `(pprint-tab ,(if atsignp :section-relative :section)
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)))))
662 (def-format-directive #\_ (colonp atsignp params)
663 (expand-bind-defaults () params
664 `(pprint-newline ,(if colonp
673 (def-format-directive #\I (colonp atsignp params)
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)))
681 ;;;; format directive for ~*
683 (def-format-directive #\* (colonp atsignp params end)
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))
696 :complaint "Index ~W out of bounds. Should have been ~
698 :args (list ,posn (length orig-args))
699 :offset ,(1- end)))))
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)))
708 (let ((new-posn (- cur-posn ,n)))
709 (if (<= 0 new-posn (length orig-args))
710 (setf args (nthcdr new-posn orig-args))
713 "Index ~W is out of bounds; should have been ~
715 :args (list new-posn (length orig-args))
716 :offset ,(1- end)))))))
718 (expand-bind-defaults ((n 1)) params
719 (setf *only-simple-args* nil)
722 (expand-next-arg)))))
724 ;;;; format directive for indirection
726 (def-format-directive #\? (colonp atsignp params string end)
729 :complaint "cannot use the colon modifier with this directive"))
730 (expand-bind-defaults () params
736 "~A~%while processing indirect format string:"
737 :args (list condition)
739 :control-string ,string
740 :offset ,(1- end)))))
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))))))
747 ;;;; format directives for capitalization
749 (def-complex-format-directive #\( (colonp atsignp params directives)
750 (let ((close (find-directive directives #\) nil)))
753 :complaint "no corresponding close parenthesis"))
754 (let* ((posn (position close directives))
755 (before (subseq directives 0 posn))
756 (after (nthcdr (1+ posn) directives)))
758 (expand-bind-defaults () params
759 `(let ((stream (make-case-frob-stream stream
767 ,@(expand-directive-list before)))
770 (def-complex-format-directive #\) ()
772 :complaint "no corresponding open parenthesis"))
774 ;;;; format directives and support functions for conditionalization
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)
784 "both colon and atsign modifiers used simultaneously")
788 "Can only specify one section")
789 (expand-bind-defaults () params
790 (expand-maybe-conditional (car sublists)))))
792 (if (= (length sublists) 2)
793 (expand-bind-defaults () params
794 (expand-true-false-conditional (car sublists)
798 "must specify exactly two sections"))
799 (expand-bind-defaults ((index nil)) params
800 (setf *only-simple-args* nil)
802 (case `(or ,index ,(expand-next-arg))))
803 (when last-semi-with-colon-p
804 (push `(t ,@(expand-directive-list (pop sublists)))
806 (let ((count (length sublists)))
807 (dolist (sublist sublists)
808 (push `(,(decf count)
809 ,@(expand-directive-list sublist))
811 `(case ,case ,@clauses)))))
814 (defun parse-conditional-directive (directives)
816 (last-semi-with-colon-p nil)
817 (remaining directives))
819 (let ((close-or-semi (find-directive remaining #\] t)))
820 (unless close-or-semi
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) #\])
828 (setf last-semi-with-colon-p
829 (format-directive-colonp close-or-semi)))))
830 (values sublists last-semi-with-colon-p remaining)))
832 (defun expand-maybe-conditional (sublist)
834 `(let ((prev-args args)
835 (arg ,(expand-next-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)
844 (cond ((and new-args (eq *simple-args* (cdr new-args)))
845 (setf *simple-args* new-args)
846 `(when ,(caar new-args)
849 (setf *only-simple-args* nil)
853 (defun expand-true-false-conditional (true false)
854 (let ((arg (expand-next-arg)))
858 ,@(expand-directive-list true))
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)
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)
874 (if (= (length true-args) (length false-args))
878 ,(do ((false false-args (cdr false))
879 (true true-args (cdr true))
880 (bindings nil (cons `(,(caar false) ,(caar true))
882 ((eq true *simple-args*)
883 (setf *simple-args* true-args)
884 (setf *only-simple-args*
885 (and true-simple false-simple))
892 (setf *only-simple-args* nil)
896 (def-complex-format-directive #\; ()
899 "~~; directive not contained within either ~~[...~~] or ~~<...~~>"))
901 (def-complex-format-directive #\] ()
904 "no corresponding open bracket"))
906 ;;;; format directive for up-and-out
908 (def-format-directive #\^ (colonp atsignp params)
911 :complaint "cannot use the at-sign modifier with this directive"))
912 (when (and colonp (not *up-up-and-out-allowed*))
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))
922 (setf *only-simple-args* nil)
925 '(return-from outside-loop nil)
928 ;;;; format directives for iteration
930 (def-complex-format-directive #\{ (colonp atsignp params string end directives)
931 (let ((close (find-directive directives #\} nil)))
934 :complaint "no corresponding close brace"))
935 (let* ((closed-with-colon (format-directive-colonp close))
936 (posn (position close directives)))
940 (if *orig-args-available*
946 "~A~%while processing indirect format string:"
947 :args (list condition)
949 :control-string ,string
950 :offset ,(1- end)))))
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)
958 (setf *only-simple-args* nil))
960 ,@(unless closed-with-colon
964 `((when (and ,count (minusp (decf ,count)))
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))
973 (declare (ignorable orig-args outside-args args))
975 ,@(compute-insides)))))
977 ,@(when closed-with-colon
980 (compute-block (count)
983 ,(compute-loop count))
984 (compute-loop count)))
985 (compute-bindings (count)
987 (compute-block count)
988 `(let* ((orig-args ,(expand-next-arg))
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))))))
996 (expand-bind-defaults ((count nil)) params
998 `(let ((inside-string ,(expand-next-arg)))
999 ,(compute-bindings count))
1000 (compute-bindings count)))
1002 `(let ((inside-string ,(expand-next-arg)))
1003 ,(compute-bindings nil))
1004 (compute-bindings nil)))
1005 (nthcdr (1+ posn) directives))))))
1007 (def-complex-format-directive #\} ()
1008 (error 'format-error
1009 :complaint "no corresponding open brace"))
1011 ;;;; format directives and support functions for justification
1013 (defparameter *illegal-inside-justification*
1014 (mapcar (lambda (x) (parse-directive x 0))
1015 '("~W" "~:W" "~@W" "~:@W"
1016 "~_" "~:_" "~@_" "~:@_"
1018 "~I" "~:I" "~@I" "~:@I"
1021 (defun illegal-inside-justification-p (directive)
1022 (member directive *illegal-inside-justification*
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))))))
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)
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
1040 (let ((count (reduce #'+ (mapcar (lambda (x) (count-if #'illegal-inside-justification-p x)) segments))))
1042 ;; ANSI specifies that "an error is signalled" in this
1044 (error 'format-error
1045 :complaint "~D illegal directive~:P found inside justification block"
1047 :references (list '(:ansi-cl :section (22 3 5 2)))))
1048 (expand-format-justification segments colonp atsignp
1049 first-semi params)))
1052 (def-complex-format-directive #\> ()
1053 (error 'format-error
1054 :complaint "no corresponding open bracket"))
1056 (defun parse-format-logical-block
1057 (segments colonp first-semi close params string end)
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)))
1068 (error 'format-error
1070 "cannot include format directives inside the ~
1071 ~:[suffix~;prefix~] segment of ~~<...~~:>"
1072 :args (list prefix-p)
1073 :offset (1- (format-directive-end directive))
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)
1084 (extract-string (caddr segments) nil)))
1086 (error 'format-error
1087 :complaint "too many segments for ~~<...~~:>")))))
1088 (when (format-directive-atsignp close)
1090 (add-fill-style-newlines insides
1093 (format-directive-end first-semi)
1096 (and first-semi (format-directive-atsignp first-semi))
1100 (defun add-fill-style-newlines (list string offset &optional last-directive)
1103 (let ((directive (car list)))
1105 ((simple-string-p directive)
1106 (let* ((non-space (position #\Space directive :test #'char/=))
1107 (newlinep (and last-directive
1109 (format-directive-character last-directive)
1112 ((and newlinep non-space)
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)))))
1121 (add-fill-style-newlines
1122 (cdr list) string (+ offset (length directive)))))
1124 (nconc (add-fill-style-newlines-aux directive string offset)
1125 (add-fill-style-newlines
1126 (cdr list) string (+ offset (length directive))))))))
1129 (add-fill-style-newlines
1131 (format-directive-end directive) directive))))))
1134 (defun add-fill-style-newlines-aux (literal string offset)
1135 (let ((end (length literal))
1137 (collect ((results))
1139 (let ((blank (position #\space literal :start posn)))
1141 (results (subseq literal posn))
1143 (let ((non-blank (or (position #\space literal :start blank
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))
1156 (defun parse-format-justification (directives)
1157 (let ((first-semi nil)
1159 (remaining directives))
1160 (collect ((segments))
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)
1171 (setf close close-or-semi)
1174 (setf first-semi close-or-semi))))
1175 (values (segments) first-semi close remaining))))
1177 (sb!xc:defmacro expander-pprint-next-arg (string offset)
1180 (error 'format-error
1181 :complaint "no more arguments"
1182 :control-string ,string
1187 (defun expand-format-logical-block (prefix per-line-p insides suffix atsignp)
1188 `(let ((arg ,(if atsignp 'args (expand-next-arg))))
1190 (setf *only-simple-args* nil)
1192 (pprint-logical-block
1194 ,(if per-line-p :per-line-prefix :prefix) ,prefix
1198 `((orig-args arg))))
1199 (declare (ignorable args ,@(unless atsignp '(orig-args))))
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)))))))
1207 (defun expand-format-justification (segments colonp atsignp first-semi params)
1208 (let ((newline-segment-p
1210 (format-directive-colonp first-semi))))
1211 (expand-bind-defaults
1212 ((mincol 0) (colinc 1) (minpad 0) (padchar #\space))
1214 `(let ((segments nil)
1215 ,@(when newline-segment-p
1216 '((newline-segment 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
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))
1234 (format-justification stream
1235 ,@(if newline-segment-p
1236 '(newline-segment extra-space line-len)
1238 segments ,colonp ,atsignp
1239 ,mincol ,colinc ,minpad ,padchar)))))
1241 ;;;; format directive and support function for user-defined method
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
1252 (:arg (expand-next-arg))
1253 (:remaining '(length args))
1256 (,symbol stream ,(expand-next-arg) ,colonp ,atsignp
1257 ,@(param-names))))))
1259 (defun extract-user-fun-name (string start end)
1260 (let ((slash (position #\/ string :start start :end (1- end)
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)))
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)))
1283 ((and second-colon (= second-colon (1+ first-colon)))
1284 (subseq name (1+ second-colon)))
1286 (subseq name (1+ first-colon)))
1290 ;;; compile-time checking for argument mismatch. This code is
1291 ;;; inspired by that of Gerd Moellmann, and comes decorated with
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))
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)
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.
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))
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))
1337 (loop for s in sublists
1339 1 (walk-directive-list s args)))))
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
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))
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)
1378 (let ((c (format-directive-character directive)))
1380 ((find c "ABCDEFGORSWX$/")
1383 (unless (format-directive-colonp directive)
1385 ((or (find c "IT%&|_();>~") (char= c #\Newline)))
1386 ;; FIXME: check correspondence of ~( and ~)
1388 (walk-complex-directive walk-justification))
1390 (walk-complex-directive walk-conditional))
1392 (walk-complex-directive walk-iteration))
1394 ;; FIXME: the argument corresponding to this
1395 ;; directive must be a format control.
1397 ((format-directive-atsignp directive)
1399 (setq max sb!xc:call-arguments-limit))
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)))))))