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)
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 (print-banner :reader format-error-print-banner :initarg :print-banner
22 (:report %print-format-error))
24 (defun %print-format-error (condition stream)
26 "~:[~;error in format: ~]~
28 (format-error-print-banner condition)
29 (format-error-complaint condition)
30 (format-error-args condition)
31 (format-error-control-string condition)
32 (format-error-offset condition)))
34 (def!struct format-directive
35 (string (missing-arg) :type simple-string)
36 (start (missing-arg) :type (and unsigned-byte fixnum))
37 (end (missing-arg) :type (and unsigned-byte fixnum))
38 (character (missing-arg) :type base-char)
39 (colonp nil :type (member t nil))
40 (atsignp nil :type (member t nil))
41 (params nil :type list))
42 (def!method print-object ((x format-directive) stream)
43 (print-unreadable-object (x stream)
44 (write-string (format-directive-string x)
46 :start (format-directive-start x)
47 :end (format-directive-end x))))
49 ;;;; TOKENIZE-CONTROL-STRING
51 (defun tokenize-control-string (string)
52 (declare (simple-string string))
57 (let ((next-directive (or (position #\~ string :start index) end)))
58 (when (> next-directive index)
59 (push (subseq string index next-directive) result))
60 (when (= next-directive end)
62 (let ((directive (parse-directive string next-directive)))
63 (push directive result)
64 (setf index (format-directive-end directive)))))
67 (defun parse-directive (string start)
68 (let ((posn (1+ start)) (params nil) (colonp nil) (atsignp nil)
69 (end (length string)))
73 :complaint "String ended before directive was found."
74 :control-string string
78 (when (or colonp atsignp)
80 :complaint "parameters found after #\\: or #\\@ modifier"
81 :control-string string
84 (let ((char (get-char)))
85 (cond ((or (char<= #\0 char #\9) (char= char #\+) (char= char #\-))
87 (multiple-value-bind (param new-posn)
88 (parse-integer string :start posn :junk-allowed t)
89 (push (cons posn param) params)
100 (push (cons posn :arg) params)
110 (push (cons posn :remaining) params)
121 (push (cons posn (get-char)) params)
123 (unless (char= (get-char) #\,)
127 (push (cons posn nil) params))
131 :complaint "too many colons supplied"
132 :control-string string
138 :complaint "too many #\\@ characters supplied"
139 :control-string string
143 (when (char= (schar string (1- posn)) #\,)
145 (push (cons (1- posn) nil) params))
148 (let ((char (get-char)))
149 (when (char= char #\/)
150 (let ((closing-slash (position #\/ string :start (1+ posn))))
152 (setf posn closing-slash)
154 :complaint "no matching closing slash"
155 :control-string string
157 (make-format-directive
158 :string string :start start :end (1+ posn)
159 :character (char-upcase char)
160 :colonp colonp :atsignp atsignp
161 :params (nreverse params))))))
165 (sb!xc:defmacro formatter (control-string)
166 `#',(%formatter control-string))
168 (defun %formatter (control-string)
170 (catch 'need-orig-args
171 (let* ((*simple-args* nil)
172 (*only-simple-args* t)
173 (guts (expand-control-string control-string))
175 (dolist (arg *simple-args*)
179 :complaint "required argument missing"
180 :control-string ,control-string
183 (return `(lambda (stream &optional ,@args &rest args)
186 (let ((*orig-args-available* t)
187 (*only-simple-args* nil))
188 `(lambda (stream &rest orig-args)
189 (let ((args orig-args))
190 ,(expand-control-string control-string)
193 (defun expand-control-string (string)
194 (let* ((string (etypecase string
198 (coerce string 'simple-string))))
199 (*default-format-error-control-string* string)
200 (directives (tokenize-control-string string)))
202 ,@(expand-directive-list directives))))
204 (defun expand-directive-list (directives)
206 (remaining-directives directives))
208 (unless remaining-directives
210 (multiple-value-bind (form new-directives)
211 (expand-directive (car remaining-directives)
212 (cdr remaining-directives))
214 (setf remaining-directives new-directives)))
217 (defun expand-directive (directive more-directives)
221 (aref *format-directive-expanders*
222 (char-code (format-directive-character directive))))
223 (*default-format-error-offset*
224 (1- (format-directive-end directive))))
225 (declare (type (or null function) expander))
227 (funcall expander directive more-directives)
229 :complaint "unknown directive ~@[(character: ~A)~]"
230 :args (list (char-name (format-directive-character directive)))))))
232 (values `(write-string ,directive stream)
235 (defmacro-mundanely expander-next-arg (string offset)
239 :complaint "no more arguments"
240 :control-string ,string
243 (defun expand-next-arg (&optional offset)
244 (if (or *orig-args-available* (not *only-simple-args*))
245 `(,*expander-next-arg-macro*
246 ,*default-format-error-control-string*
247 ,(or offset *default-format-error-offset*))
248 (let ((symbol (gensym "FORMAT-ARG-")))
249 (push (cons symbol (or offset *default-format-error-offset*))
253 (defmacro expand-bind-defaults (specs params &body body)
254 (once-only ((params params))
256 (collect ((expander-bindings) (runtime-bindings))
258 (destructuring-bind (var default) spec
259 (let ((symbol (gensym)))
264 (let* ((param-and-offset (pop ,params))
265 (offset (car param-and-offset))
266 (param (cdr param-and-offset)))
268 (:arg `(or ,(expand-next-arg offset)
271 (setf *only-simple-args* nil)
275 `(let ,(expander-bindings)
276 `(let ,(list ,@(runtime-bindings))
281 "too many parameters, expected no more than ~W"
282 :args (list ,(length specs))
283 :offset (caar ,params)))
288 :complaint "too many parameters, expected none"
289 :offset (caar ,params)))
292 ;;;; format directive machinery
294 ;;; FIXME: only used in this file, could be SB!XC:DEFMACRO in EVAL-WHEN
295 (defmacro def-complex-format-directive (char lambda-list &body body)
296 (let ((defun-name (intern (format nil
297 "~:@(~:C~)-FORMAT-DIRECTIVE-EXPANDER"
300 (directives (if lambda-list (car (last lambda-list)) (gensym))))
302 (defun ,defun-name (,directive ,directives)
304 `((let ,(mapcar (lambda (var)
306 (,(symbolicate "FORMAT-DIRECTIVE-" var)
308 (butlast lambda-list))
310 `((declare (ignore ,directive ,directives))
312 (%set-format-directive-expander ,char #',defun-name))))
314 ;;; FIXME: only used in this file, could be SB!XC:DEFMACRO in EVAL-WHEN
315 (defmacro def-format-directive (char lambda-list &body body)
316 (let ((directives (gensym))
318 (body-without-decls body))
320 (let ((form (car body-without-decls)))
321 (unless (and (consp form) (eq (car form) 'declare))
323 (push (pop body-without-decls) declarations)))
324 (setf declarations (reverse declarations))
325 `(def-complex-format-directive ,char (,@lambda-list ,directives)
327 (values (progn ,@body-without-decls)
330 (eval-when (:compile-toplevel :load-toplevel :execute)
332 (defun %set-format-directive-expander (char fn)
333 (setf (aref *format-directive-expanders* (char-code (char-upcase char))) fn)
336 (defun %set-format-directive-interpreter (char fn)
337 (setf (aref *format-directive-interpreters*
338 (char-code (char-upcase char)))
342 (defun find-directive (directives kind stop-at-semi)
344 (let ((next (car directives)))
345 (if (format-directive-p next)
346 (let ((char (format-directive-character next)))
347 (if (or (char= kind char)
348 (and stop-at-semi (char= char #\;)))
351 (cdr (flet ((after (char)
352 (member (find-directive (cdr directives)
363 (find-directive (cdr directives) kind stop-at-semi)))))
367 ;;;; format directives for simple output
369 (def-format-directive #\A (colonp atsignp params)
371 (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
374 `(format-princ stream ,(expand-next-arg) ',colonp ',atsignp
375 ,mincol ,colinc ,minpad ,padchar))
377 `(or ,(expand-next-arg) "()")
381 (def-format-directive #\S (colonp atsignp params)
383 (expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
386 `(format-prin1 stream ,(expand-next-arg) ,colonp ,atsignp
387 ,mincol ,colinc ,minpad ,padchar)))
389 `(let ((arg ,(expand-next-arg)))
392 (princ "()" stream))))
394 `(prin1 ,(expand-next-arg) stream))))
396 (def-format-directive #\C (colonp atsignp params)
397 (expand-bind-defaults () params
399 `(format-print-named-character ,(expand-next-arg) stream)
401 `(prin1 ,(expand-next-arg) stream)
402 `(write-char ,(expand-next-arg) stream)))))
404 (def-format-directive #\W (colonp atsignp params)
405 (expand-bind-defaults () params
406 (if (or colonp atsignp)
407 `(let (,@(when colonp
408 '((*print-pretty* t)))
410 '((*print-level* nil)
411 (*print-length* nil))))
412 (output-object ,(expand-next-arg) stream))
413 `(output-object ,(expand-next-arg) stream))))
415 ;;;; format directives for integer output
417 (defun expand-format-integer (base colonp atsignp params)
418 (if (or colonp atsignp params)
419 (expand-bind-defaults
420 ((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
422 `(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
423 ,base ,mincol ,padchar ,commachar
425 `(write ,(expand-next-arg) :stream stream :base ,base :radix nil
428 (def-format-directive #\D (colonp atsignp params)
429 (expand-format-integer 10 colonp atsignp params))
431 (def-format-directive #\B (colonp atsignp params)
432 (expand-format-integer 2 colonp atsignp params))
434 (def-format-directive #\O (colonp atsignp params)
435 (expand-format-integer 8 colonp atsignp params))
437 (def-format-directive #\X (colonp atsignp params)
438 (expand-format-integer 16 colonp atsignp params))
440 (def-format-directive #\R (colonp atsignp params)
442 (expand-bind-defaults
443 ((base 10) (mincol 0) (padchar #\space) (commachar #\,)
446 `(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
448 ,padchar ,commachar ,commainterval))
451 `(format-print-old-roman stream ,(expand-next-arg))
452 `(format-print-roman stream ,(expand-next-arg)))
454 `(format-print-ordinal stream ,(expand-next-arg))
455 `(format-print-cardinal stream ,(expand-next-arg))))))
457 ;;;; format directive for pluralization
459 (def-format-directive #\P (colonp atsignp params end)
460 (expand-bind-defaults () params
464 (*orig-args-available*
465 `(if (eq orig-args args)
467 :complaint "no previous argument"
469 (do ((arg-ptr orig-args (cdr arg-ptr)))
470 ((eq (cdr arg-ptr) args)
473 (unless *simple-args*
475 :complaint "no previous argument"))
476 (caar *simple-args*))
478 (/show0 "THROWing NEED-ORIG-ARGS from tilde-P")
479 (throw 'need-orig-args nil)))))
481 `(write-string (if (eql ,arg 1) "y" "ies") stream)
482 `(unless (eql ,arg 1) (write-char #\s stream))))))
484 ;;;; format directives for floating point output
486 (def-format-directive #\F (colonp atsignp params)
490 "The colon modifier cannot be used with this directive."))
491 (expand-bind-defaults ((w nil) (d nil) (k nil) (ovf nil) (pad #\space)) params
492 `(format-fixed stream ,(expand-next-arg) ,w ,d ,k ,ovf ,pad ,atsignp)))
494 (def-format-directive #\E (colonp atsignp params)
498 "The colon modifier cannot be used with this directive."))
499 (expand-bind-defaults
500 ((w nil) (d nil) (e nil) (k 1) (ovf nil) (pad #\space) (mark nil))
502 `(format-exponential stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark
505 (def-format-directive #\G (colonp atsignp params)
509 "The colon modifier cannot be used with this directive."))
510 (expand-bind-defaults
511 ((w nil) (d nil) (e nil) (k nil) (ovf nil) (pad #\space) (mark nil))
513 `(format-general stream ,(expand-next-arg) ,w ,d ,e ,k ,ovf ,pad ,mark ,atsignp)))
515 (def-format-directive #\$ (colonp atsignp params)
516 (expand-bind-defaults ((d 2) (n 1) (w 0) (pad #\space)) params
517 `(format-dollars stream ,(expand-next-arg) ,d ,n ,w ,pad ,colonp
520 ;;;; format directives for line/page breaks etc.
522 (def-format-directive #\% (colonp atsignp params)
523 (when (or colonp atsignp)
526 "The colon and atsign modifiers cannot be used with this directive."
529 (expand-bind-defaults ((count 1)) params
534 (def-format-directive #\& (colonp atsignp params)
535 (when (or colonp atsignp)
538 "The colon and atsign modifiers cannot be used with this directive."
541 (expand-bind-defaults ((count 1)) params
544 (dotimes (i (1- ,count))
546 '(fresh-line stream)))
548 (def-format-directive #\| (colonp atsignp params)
549 (when (or colonp atsignp)
552 "The colon and atsign modifiers cannot be used with this directive."
555 (expand-bind-defaults ((count 1)) params
557 (write-char (code-char form-feed-char-code) stream)))
558 '(write-char (code-char form-feed-char-code) stream)))
560 (def-format-directive #\~ (colonp atsignp params)
561 (when (or colonp atsignp)
564 "The colon and atsign modifiers cannot be used with this directive."
567 (expand-bind-defaults ((count 1)) params
569 (write-char #\~ stream)))
570 '(write-char #\~ stream)))
572 (def-complex-format-directive #\newline (colonp atsignp params directives)
573 (when (and colonp atsignp)
575 :complaint "both colon and atsign modifiers used simultaneously"))
576 (values (expand-bind-defaults () params
578 '(write-char #\newline stream)
580 (if (and (not colonp)
582 (simple-string-p (car directives)))
583 (cons (string-left-trim *format-whitespace-chars*
588 ;;;; format directives for tabs and simple pretty printing
590 (def-format-directive #\T (colonp atsignp params)
592 (expand-bind-defaults ((n 1) (m 1)) params
593 `(pprint-tab ,(if atsignp :section-relative :section)
596 (expand-bind-defaults ((colrel 1) (colinc 1)) params
597 `(format-relative-tab stream ,colrel ,colinc))
598 (expand-bind-defaults ((colnum 1) (colinc 1)) params
599 `(format-absolute-tab stream ,colnum ,colinc)))))
601 (def-format-directive #\_ (colonp atsignp params)
602 (expand-bind-defaults () params
603 `(pprint-newline ,(if colonp
612 (def-format-directive #\I (colonp atsignp params)
616 "cannot use the at-sign modifier with this directive"))
617 (expand-bind-defaults ((n 0)) params
618 `(pprint-indent ,(if colonp :current :block) ,n stream)))
620 ;;;; format directive for ~*
622 (def-format-directive #\* (colonp atsignp params end)
627 "both colon and atsign modifiers used simultaneously")
628 (expand-bind-defaults ((posn 0)) params
629 (unless *orig-args-available*
630 (/show0 "THROWing NEED-ORIG-ARGS from tilde-@*")
631 (throw 'need-orig-args nil))
632 `(if (<= 0 ,posn (length orig-args))
633 (setf args (nthcdr ,posn orig-args))
635 :complaint "Index ~W out of bounds. Should have been ~
637 :args (list ,posn (length orig-args))
638 :offset ,(1- end)))))
640 (expand-bind-defaults ((n 1)) params
641 (unless *orig-args-available*
642 (/show0 "THROWing NEED-ORIG-ARGS from tilde-:*")
643 (throw 'need-orig-args nil))
644 `(do ((cur-posn 0 (1+ cur-posn))
645 (arg-ptr orig-args (cdr arg-ptr)))
647 (let ((new-posn (- cur-posn ,n)))
648 (if (<= 0 new-posn (length orig-args))
649 (setf args (nthcdr new-posn orig-args))
652 "Index ~W is out of bounds; should have been ~
654 :args (list new-posn (length orig-args))
655 :offset ,(1- end)))))))
657 (expand-bind-defaults ((n 1)) params
658 (setf *only-simple-args* nil)
661 (expand-next-arg)))))
663 ;;;; format directive for indirection
665 (def-format-directive #\? (colonp atsignp params string end)
668 :complaint "cannot use the colon modifier with this directive"))
669 (expand-bind-defaults () params
675 "~A~%while processing indirect format string:"
676 :args (list condition)
678 :control-string ,string
679 :offset ,(1- end)))))
681 (if *orig-args-available*
682 `(setf args (%format stream ,(expand-next-arg) orig-args args))
683 (throw 'need-orig-args nil))
684 `(%format stream ,(expand-next-arg) ,(expand-next-arg))))))
686 ;;;; format directives for capitalization
688 (def-complex-format-directive #\( (colonp atsignp params directives)
689 (let ((close (find-directive directives #\) nil)))
692 :complaint "no corresponding close parenthesis"))
693 (let* ((posn (position close directives))
694 (before (subseq directives 0 posn))
695 (after (nthcdr (1+ posn) directives)))
697 (expand-bind-defaults () params
698 `(let ((stream (make-case-frob-stream stream
706 ,@(expand-directive-list before)))
709 (def-complex-format-directive #\) ()
711 :complaint "no corresponding open parenthesis"))
713 ;;;; format directives and support functions for conditionalization
715 (def-complex-format-directive #\[ (colonp atsignp params directives)
716 (multiple-value-bind (sublists last-semi-with-colon-p remaining)
717 (parse-conditional-directive directives)
723 "both colon and atsign modifiers used simultaneously")
727 "Can only specify one section")
728 (expand-bind-defaults () params
729 (expand-maybe-conditional (car sublists)))))
731 (if (= (length sublists) 2)
732 (expand-bind-defaults () params
733 (expand-true-false-conditional (car sublists)
737 "must specify exactly two sections"))
738 (expand-bind-defaults ((index (expand-next-arg))) params
739 (setf *only-simple-args* nil)
741 (when last-semi-with-colon-p
742 (push `(t ,@(expand-directive-list (pop sublists)))
744 (let ((count (length sublists)))
745 (dolist (sublist sublists)
746 (push `(,(decf count)
747 ,@(expand-directive-list sublist))
749 `(case ,index ,@clauses)))))
752 (defun parse-conditional-directive (directives)
754 (last-semi-with-colon-p nil)
755 (remaining directives))
757 (let ((close-or-semi (find-directive remaining #\] t)))
758 (unless close-or-semi
760 :complaint "no corresponding close bracket"))
761 (let ((posn (position close-or-semi remaining)))
762 (push (subseq remaining 0 posn) sublists)
763 (setf remaining (nthcdr (1+ posn) remaining))
764 (when (char= (format-directive-character close-or-semi) #\])
766 (setf last-semi-with-colon-p
767 (format-directive-colonp close-or-semi)))))
768 (values sublists last-semi-with-colon-p remaining)))
770 (defun expand-maybe-conditional (sublist)
772 `(let ((prev-args args)
773 (arg ,(expand-next-arg)))
775 (setf args prev-args)
776 ,@(expand-directive-list sublist)))))
777 (if *only-simple-args*
778 (multiple-value-bind (guts new-args)
779 (let ((*simple-args* *simple-args*))
780 (values (expand-directive-list sublist)
782 (cond ((eq *simple-args* (cdr new-args))
783 (setf *simple-args* new-args)
784 `(when ,(caar new-args)
787 (setf *only-simple-args* nil)
791 (defun expand-true-false-conditional (true false)
792 (let ((arg (expand-next-arg)))
796 ,@(expand-directive-list true))
798 ,@(expand-directive-list false)))))
799 (if *only-simple-args*
800 (multiple-value-bind (true-guts true-args true-simple)
801 (let ((*simple-args* *simple-args*)
802 (*only-simple-args* t))
803 (values (expand-directive-list true)
806 (multiple-value-bind (false-guts false-args false-simple)
807 (let ((*simple-args* *simple-args*)
808 (*only-simple-args* t))
809 (values (expand-directive-list false)
812 (if (= (length true-args) (length false-args))
816 ,(do ((false false-args (cdr false))
817 (true true-args (cdr true))
818 (bindings nil (cons `(,(caar false) ,(caar true))
820 ((eq true *simple-args*)
821 (setf *simple-args* true-args)
822 (setf *only-simple-args*
823 (and true-simple false-simple))
830 (setf *only-simple-args* nil)
834 (def-complex-format-directive #\; ()
837 "~~; directive not contained within either ~~[...~~] or ~~<...~~>"))
839 (def-complex-format-directive #\] ()
842 "no corresponding open bracket"))
844 ;;;; format directive for up-and-out
846 (def-format-directive #\^ (colonp atsignp params)
849 :complaint "cannot use the at-sign modifier with this directive"))
850 (when (and colonp (not *up-up-and-out-allowed*))
852 :complaint "attempt to use ~~:^ outside a ~~:{...~~} construct"))
853 `(when ,(case (length params)
857 (setf *only-simple-args* nil)
859 (1 (expand-bind-defaults ((count 0)) params
861 (2 (expand-bind-defaults ((arg1 0) (arg2 0)) params
863 (t (expand-bind-defaults ((arg1 0) (arg2 0) (arg3 0)) params
864 `(<= ,arg1 ,arg2 ,arg3))))
866 '(return-from outside-loop nil)
869 ;;;; format directives for iteration
871 (def-complex-format-directive #\{ (colonp atsignp params string end directives)
872 (let ((close (find-directive directives #\} nil)))
875 :complaint "no corresponding close brace"))
876 (let* ((closed-with-colon (format-directive-colonp close))
877 (posn (position close directives)))
881 (if *orig-args-available*
887 "~A~%while processing indirect format string:"
888 :args (list condition)
890 :control-string ,string
891 :offset ,(1- end)))))
893 (%format stream inside-string orig-args args))))
894 (throw 'need-orig-args nil))
895 (let ((*up-up-and-out-allowed* colonp))
896 (expand-directive-list (subseq directives 0 posn)))))
897 (compute-loop-aux (count)
899 (setf *only-simple-args* nil))
901 ,@(unless closed-with-colon
905 `((when (and ,count (minusp (decf ,count)))
908 (let ((*expander-next-arg-macro* 'expander-next-arg)
909 (*only-simple-args* nil)
910 (*orig-args-available* t))
911 `((let* ((orig-args ,(expand-next-arg))
914 (declare (ignorable orig-args outside-args args))
916 ,@(compute-insides)))))
918 ,@(when closed-with-colon
923 (expand-bind-defaults ((count nil)) params
924 (compute-loop-aux count))
925 (compute-loop-aux nil)))
934 `(let* ((orig-args ,(expand-next-arg))
936 (declare (ignorable orig-args args))
937 ,(let ((*expander-next-arg-macro* 'expander-next-arg)
938 (*only-simple-args* nil)
939 (*orig-args-available* t))
941 (values (if (zerop posn)
942 `(let ((inside-string ,(expand-next-arg)))
945 (nthcdr (1+ posn) directives))))))
947 (def-complex-format-directive #\} ()
949 :complaint "no corresponding open brace"))
951 ;;;; format directives and support functions for justification
953 (defparameter *illegal-inside-justification*
954 (mapcar (lambda (x) (parse-directive x 0))
955 '("~W" "~:W" "~@W" "~:@W"
956 "~_" "~:_" "~@_" "~:@_"
958 "~I" "~:I" "~@I" "~:@I"
961 (defun illegal-inside-justification-p (directive)
962 (member directive *illegal-inside-justification*
964 (and (format-directive-p x)
965 (format-directive-p y)
966 (eql (format-directive-character x) (format-directive-character y))
967 (eql (format-directive-colonp x) (format-directive-colonp y))
968 (eql (format-directive-atsignp x) (format-directive-atsignp y))))))
970 (def-complex-format-directive #\< (colonp atsignp params string end directives)
971 (multiple-value-bind (segments first-semi close remaining)
972 (parse-format-justification directives)
974 (if (format-directive-colonp close)
975 (multiple-value-bind (prefix per-line-p insides suffix)
976 (parse-format-logical-block segments colonp first-semi
977 close params string end)
978 (expand-format-logical-block prefix per-line-p insides
980 (let ((count (reduce #'+ (mapcar (lambda (x) (count-if #'illegal-inside-justification-p x)) segments))))
982 ;; ANSI specifies that "an error is signalled" in this
985 :complaint "~D illegal directive~:P found inside justification block"
987 (expand-format-justification segments colonp atsignp
991 (def-complex-format-directive #\> ()
993 :complaint "no corresponding open bracket"))
995 (defun parse-format-logical-block
996 (segments colonp first-semi close params string end)
999 :complaint "No parameters can be supplied with ~~<...~~:>."
1000 :offset (caar params)))
1001 (multiple-value-bind (prefix insides suffix)
1002 (multiple-value-bind (prefix-default suffix-default)
1003 (if colonp (values "(" ")") (values nil ""))
1004 (flet ((extract-string (list prefix-p)
1005 (let ((directive (find-if #'format-directive-p list)))
1007 (error 'format-error
1009 "cannot include format directives inside the ~
1010 ~:[suffix~;prefix~] segment of ~~<...~~:>"
1011 :args (list prefix-p)
1012 :offset (1- (format-directive-end directive)))
1013 (apply #'concatenate 'string list)))))
1014 (case (length segments)
1015 (0 (values prefix-default nil suffix-default))
1016 (1 (values prefix-default (car segments) suffix-default))
1017 (2 (values (extract-string (car segments) t)
1018 (cadr segments) suffix-default))
1019 (3 (values (extract-string (car segments) t)
1021 (extract-string (caddr segments) nil)))
1023 (error 'format-error
1024 :complaint "too many segments for ~~<...~~:>")))))
1025 (when (format-directive-atsignp close)
1027 (add-fill-style-newlines insides
1030 (format-directive-end first-semi)
1033 (and first-semi (format-directive-atsignp first-semi))
1037 (defun add-fill-style-newlines (list string offset)
1039 (let ((directive (car list)))
1040 (if (simple-string-p directive)
1041 (nconc (add-fill-style-newlines-aux directive string offset)
1042 (add-fill-style-newlines (cdr list)
1044 (+ offset (length directive))))
1046 (add-fill-style-newlines (cdr list)
1048 (format-directive-end directive)))))
1051 (defun add-fill-style-newlines-aux (literal string offset)
1052 (let ((end (length literal))
1054 (collect ((results))
1056 (let ((blank (position #\space literal :start posn)))
1058 (results (subseq literal posn))
1060 (let ((non-blank (or (position #\space literal :start blank
1063 (results (subseq literal posn non-blank))
1064 (results (make-format-directive
1065 :string string :character #\_
1066 :start (+ offset non-blank) :end (+ offset non-blank)
1067 :colonp t :atsignp nil :params nil))
1068 (setf posn non-blank))
1073 (defun parse-format-justification (directives)
1074 (let ((first-semi nil)
1076 (remaining directives))
1077 (collect ((segments))
1079 (let ((close-or-semi (find-directive remaining #\> t)))
1080 (unless close-or-semi
1081 (error 'format-error
1082 :complaint "no corresponding close bracket"))
1083 (let ((posn (position close-or-semi remaining)))
1084 (segments (subseq remaining 0 posn))
1085 (setf remaining (nthcdr (1+ posn) remaining)))
1086 (when (char= (format-directive-character close-or-semi)
1088 (setf close close-or-semi)
1091 (setf first-semi close-or-semi))))
1092 (values (segments) first-semi close remaining))))
1094 (sb!xc:defmacro expander-pprint-next-arg (string offset)
1097 (error 'format-error
1098 :complaint "no more arguments"
1099 :control-string ,string
1104 (defun expand-format-logical-block (prefix per-line-p insides suffix atsignp)
1105 `(let ((arg ,(if atsignp 'args (expand-next-arg))))
1107 (setf *only-simple-args* nil)
1109 (pprint-logical-block
1111 ,(if per-line-p :per-line-prefix :prefix) ,prefix
1115 `((orig-args arg))))
1116 (declare (ignorable args ,@(unless atsignp '(orig-args))))
1118 ,@(let ((*expander-next-arg-macro* 'expander-pprint-next-arg)
1119 (*only-simple-args* nil)
1120 (*orig-args-available* t))
1121 (expand-directive-list insides)))))))
1123 (defun expand-format-justification (segments colonp atsignp first-semi params)
1124 (let ((newline-segment-p
1126 (format-directive-colonp first-semi))))
1127 (expand-bind-defaults
1128 ((mincol 0) (colinc 1) (minpad 0) (padchar #\space))
1130 `(let ((segments nil)
1131 ,@(when newline-segment-p
1132 '((newline-segment nil)
1136 ,@(when newline-segment-p
1137 `((setf newline-segment
1138 (with-output-to-string (stream)
1139 ,@(expand-directive-list (pop segments))))
1140 ,(expand-bind-defaults
1142 (line-len '(or (sb!impl::line-length stream) 72)))
1143 (format-directive-params first-semi)
1144 `(setf extra-space ,extra line-len ,line-len))))
1145 ,@(mapcar (lambda (segment)
1146 `(push (with-output-to-string (stream)
1147 ,@(expand-directive-list segment))
1150 (format-justification stream
1151 ,@(if newline-segment-p
1152 '(newline-segment extra-space line-len)
1154 segments ,colonp ,atsignp
1155 ,mincol ,colinc ,minpad ,padchar)))))
1157 ;;;; format directive and support function for user-defined method
1159 (def-format-directive #\/ (string start end colonp atsignp params)
1160 (let ((symbol (extract-user-fun-name string start end)))
1161 (collect ((param-names) (bindings))
1162 (dolist (param-and-offset params)
1163 (let ((param (cdr param-and-offset)))
1164 (let ((param-name (gensym)))
1165 (param-names param-name)
1166 (bindings `(,param-name
1168 (:arg (expand-next-arg))
1169 (:remaining '(length args))
1172 (,symbol stream ,(expand-next-arg) ,colonp ,atsignp
1173 ,@(param-names))))))
1175 (defun extract-user-fun-name (string start end)
1176 (let ((slash (position #\/ string :start start :end (1- end)
1179 (error 'format-error
1180 :complaint "malformed ~~/ directive"))
1181 (let* ((name (string-upcase (let ((foo string))
1182 ;; Hack alert: This is to keep the compiler
1183 ;; quiet about deleting code inside the
1184 ;; subseq expansion.
1185 (subseq foo (1+ slash) (1- end)))))
1186 (first-colon (position #\: name))
1187 (second-colon (if first-colon (position #\: name :start (1+ first-colon))))
1188 (package-name (if first-colon
1189 (subseq name 0 first-colon)
1190 "COMMON-LISP-USER"))
1191 (package (find-package package-name)))
1193 ;; FIXME: should be PACKAGE-ERROR? Could we just use
1194 ;; FIND-UNDELETED-PACKAGE-OR-LOSE?
1195 (error 'format-error
1196 :complaint "no package named ~S"
1197 :args (list package-name)))
1199 ((and second-colon (= second-colon (1+ first-colon)))
1200 (subseq name (1+ second-colon)))
1202 (subseq name (1+ first-colon)))