Newer
Older
;;; -*- Package: FORMAT -*-
;;;
;;; **********************************************************************
;;; This code was written as part of the CMU Common Lisp project at
;;; Carnegie Mellon University, and has been placed in the public domain.
;;;
(ext:file-comment
"$Header: /Volumes/share2/src/cmucl/cvs2git/cvsroot/src/code/format.lisp,v 1.35 1997/04/20 21:31:26 pw Exp $")
;;; **********************************************************************
;;;
;;; Functions to implement FORMAT and FORMATTER for CMU Common Lisp.
;;; Written by William Lott, with lots of stuff stolen from the previous
;;; version by David Adam and later rewritten by Bill Maddox.
;;;
(in-package "FORMAT")
(use-package "EXT")
(in-package "LISP")
(export '(format formatter))
(in-package "FORMAT")
(defstruct (format-directive
(:print-function %print-format-directive))
(string (required-argument) :type simple-string)
(start (required-argument) :type (and unsigned-byte fixnum))
(end (required-argument) :type (and unsigned-byte fixnum))
(colonp nil :type (member t nil))
(atsignp nil :type (member t nil))
(params nil :type list))
(defun %print-format-directive (struct stream depth)
(declare (ignore depth))
(print-unreadable-object (struct stream)
(write-string (format-directive-string struct) stream
:start (format-directive-start struct)
:end (format-directive-end struct))))
(defvar *format-directive-expanders*
(make-array char-code-limit :initial-element nil))
(defvar *format-directive-interpreters*
(make-array char-code-limit :initial-element nil))
(defun %print-format-error (condition stream)
(cl:format stream
"~:[~;Error in format: ~]~
~?~@[~% ~A~% ~V@T^~]"
(format-error-print-banner condition)
(format-error-complaint condition)
(format-error-arguments condition)
(format-error-control-string condition)
(format-error-offset condition)))
(defvar *default-format-error-control-string* nil)
(defvar *default-format-error-offset* nil)
(define-condition format-error (error)
((complaint :reader format-error-complaint :initarg :complaint)
(arguments :reader format-error-arguments :initarg :arguments :initform nil)
(control-string :reader format-error-control-string
:initarg :control-string
:initform *default-format-error-control-string*)
(offset :reader format-error-offset :initarg :offset
:initform *default-format-error-offset*)
(print-banner :reader format-error-print-banner :initarg :print-banner
:initform t))
(:report %print-format-error))
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
;;;; TOKENIZE-CONTROL-STRING
(defun tokenize-control-string (string)
(declare (simple-string string))
(let ((index 0)
(end (length string))
(result nil))
(loop
(let ((next-directive (or (position #\~ string :start index) end)))
(when (> next-directive index)
(push (subseq string index next-directive) result))
(when (= next-directive end)
(return))
(let ((directive (parse-directive string next-directive)))
(push directive result)
(setf index (format-directive-end directive)))))
(nreverse result)))
(defun parse-directive (string start)
(let ((posn (1+ start)) (params nil) (colonp nil) (atsignp nil)
(end (length string)))
(flet ((get-char ()
(if (= posn end)
(error 'format-error
:complaint "String ended before directive was found."
:control-string string
:offset start)
(schar string posn))))
(loop
(let ((char (get-char)))
(cond ((or (char<= #\0 char #\9) (char= char #\+) (char= char #\-))
(multiple-value-bind
(param new-posn)
(parse-integer string :start posn :junk-allowed t)
(push (cons posn param) params)
(setf posn new-posn)
(case (get-char)
(#\,)
((#\: #\@)
(decf posn))
(t
(return)))))
((or (char= char #\v) (char= char #\V))
(push (cons posn :arg) params)
(incf posn)
(case (get-char)
(#\,)
((#\: #\@)
(decf posn))
(t
(return))))
((char= char #\#)
(push (cons posn :remaining) params)
(incf posn)
(case (get-char)
(#\,)
((#\: #\@)
(decf posn))
(t
(return))))
((char= char #\')
(incf posn)
(push (cons posn (get-char)) params)
(incf posn)
(unless (char= (get-char) #\,)
(decf posn)))
((char= char #\,)
((char= char #\:)
(if colonp
(error 'format-error
:complaint "Too many colons supplied."
:control-string string
:offset posn)
(setf colonp t)))
((char= char #\@)
(if atsignp
(error 'format-error
:complaint "Too many at-signs supplied."
:control-string string
:offset posn)
(setf atsignp t)))
(t
(when (char= (schar string (1- posn)) #\,)
(push (cons (1- posn) nil) params))
(return))))
(incf posn))
(let ((char (get-char)))
(when (char= char #\/)
(let ((closing-slash (position #\/ string :start (1+ posn))))
(if closing-slash
(setf posn closing-slash)
(error 'format-error
:complaint "No matching closing slash."
:control-string string
:offset posn))))
(make-format-directive
:string string :start start :end (1+ posn)
:character (char-upcase char)
:colonp colonp :atsignp atsignp
:params (nreverse params))))))
;;;; Specials used to communicate information.
;;; *UP-UP-AND-OUT-ALLOWED* -- internal.
;;;
;;; Used both by the expansion stuff and the interpreter stuff. When it is
;;; non-NIL, up-up-and-out (~:^) is allowed. Otherwise, ~:^ isn't allowed.
;;;
(defvar *up-up-and-out-allowed* nil)
;;; *LOGICAL-BLOCK-POPPER* -- internal.
;;;
;;; Used by the interpreter stuff. When it non-NIL, its a function that will
;;; invoke PPRINT-POP in the right lexical environemnt.
;;;
(defvar *logical-block-popper* nil)
;;; *EXPANDER-NEXT-ARG-MACRO* -- internal.
;;; Used by the expander stuff. This is bindable so that ~<...~:>
;;; can change it.
;;;
(defvar *expander-next-arg-macro* 'expander-next-arg)
;;; *ONLY-SIMPLE-ARGS* -- internal.
;;;
;;; Used by the expander stuff. Initially starts as T, and gets set to NIL
;;; if someone needs to do something strange with the arg list (like use
;;; the rest, or something).
;;;
(defvar *only-simple-args*)
;;; *ORIG-ARGS-AVAILABLE* -- internal.
;;;
;;; Used by the expander stuff. We do an initial pass with this as NIL.
;;; If someone doesn't like this, they (throw 'need-orig-args nil) and we try
;;; again with it bound to T. If this is T, we don't try to do anything
;;; fancy with args.
;;;
(defvar *orig-args-available* nil)
;;; *SIMPLE-ARGS* -- internal.
;;;
;;; Used by the expander stuff. List of (symbol . offset) for simple args.
;;;
(defvar *simple-args*)
;;;; FORMAT
(defun format (destination control-string &rest format-arguments)
"Provides various facilities for formatting output.
CONTROL-STRING contains a string to be output, possibly with embedded
directives, which are flagged with the escape character \"~\". Directives
generally expand into additional text to be output, usually consuming one
or more of the FORMAT-ARGUMENTS in the process. A few useful directives
are:
~A or ~nA Prints one argument as if by PRINC
~S or ~nS Prints one argument as if by PRIN1
~D or ~nD Prints one argument as a decimal integer
~% Does a TERPRI
~& Does a FRESH-LINE
where n is the width of the field in which the object is printed.
DESTINATION controls where the result will go. If DESTINATION is T, then
the output is sent to the standard output stream. If it is NIL, then the
output is returned in a string as the value of the call. Otherwise,
DESTINATION must be a stream to which the output will be sent.
Example: (FORMAT NIL \"The answer is ~D.\" 10) => \"The answer is 10.\"
FORMAT has many additional capabilities not described here. Consult the
manual for details."
(etypecase destination
(null
(with-output-to-string (stream)
(%format stream control-string format-arguments)))
(string
(with-output-to-string (stream destination)
(%format stream control-string format-arguments)))
((member t)
(%format *standard-output* control-string format-arguments)
nil)
(stream
(%format destination control-string format-arguments)
nil)))
(defun %format (stream string-or-fun orig-args &optional (args orig-args))
(if (functionp string-or-fun)
(apply string-or-fun stream args)
(catch 'up-and-out
(let* ((string (etypecase string-or-fun
(simple-string
string-or-fun)
(string
(coerce string-or-fun 'simple-string))))
(*default-format-error-control-string* string)
(*logical-block-popper* nil))
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
(interpret-directive-list stream (tokenize-control-string string)
orig-args args)))))
(defun interpret-directive-list (stream directives orig-args args)
(if directives
(let ((directive (car directives)))
(etypecase directive
(simple-string
(write-string directive stream)
(interpret-directive-list stream (cdr directives) orig-args args))
(format-directive
(multiple-value-bind
(new-directives new-args)
(let ((function
(svref *format-directive-interpreters*
(char-code (format-directive-character
directive))))
(*default-format-error-offset*
(1- (format-directive-end directive))))
(unless function
(error 'format-error
:complaint "Unknown format directive."))
(multiple-value-bind
(new-directives new-args)
(funcall function stream directive
(cdr directives) orig-args args)
(values new-directives new-args)))
(interpret-directive-list stream new-directives
orig-args new-args)))))
args))
;;;; FORMATTER
(defmacro formatter (control-string)
`#',(%formatter control-string))
(defun %formatter (control-string)
(block nil
(catch 'need-orig-args
(let* ((*simple-args* nil)
(*only-simple-args* t)
(guts (expand-control-string control-string))
(args nil))
(dolist (arg *simple-args*)
(push `(,(car arg)
(error
'format-error
:complaint "Required argument missing"
:control-string ,control-string
:offset ,(cdr arg)))
args))
(return `(lambda (stream &optional ,@args &rest args)
,guts
args))))
(let ((*orig-args-available* t)
(*only-simple-args* nil))
`(lambda (stream &rest orig-args)
(let ((args orig-args))
,(expand-control-string control-string)
args)))))
(defun expand-control-string (string)
(let* ((string (etypecase string
(simple-string
(string
(coerce string 'simple-string))))
(*default-format-error-control-string* string)
(directives (tokenize-control-string string)))
`(block nil
,@(expand-directive-list directives))))
(defun expand-directive-list (directives)
(let ((results nil)
(remaining-directives directives))
(loop
(unless remaining-directives
(return))
(form new-directives)
(expand-directive (car remaining-directives)
(cdr remaining-directives))
(push form results)
(setf remaining-directives new-directives)))
(reverse results)))
(defun expand-directive (directive more-directives)
(etypecase directive
(format-directive
(let ((expander
(aref *format-directive-expanders*
(char-code (format-directive-character directive))))
(*default-format-error-offset*
(1- (format-directive-end directive))))
(if expander
(funcall expander directive more-directives)
(error 'format-error
(simple-string
(values `(write-string ,directive stream)
more-directives))))
(defun expand-next-arg (&optional offset)
(if (or *orig-args-available* (not *only-simple-args*))
`(,*expander-next-arg-macro*
,*default-format-error-control-string*
,(or offset *default-format-error-offset*))
(let ((symbol (gensym "FORMAT-ARG-")))
(push (cons symbol (or offset *default-format-error-offset*))
*simple-args*)
symbol)))
(defun need-hairy-args ()
(when *only-simple-args*
))
;;;; Format directive definition macros and runtime support.
(defmacro expander-next-arg (string offset)
`(if args
(pop args)
(error 'format-error
:complaint "No more arguments."
:control-string ,string
:offset ,offset)))
(defmacro expander-pprint-next-arg (string offset)
`(progn
(when (null args)
(error 'format-error
:complaint "No more arguments."
:control-string ,string
:offset ,offset))
(pprint-pop)
(pop args)))
(eval-when (compile eval)
;;; NEXT-ARG -- internal.
;;;
;;; This macro is used to extract the next argument from the current arg list.
;;; This is the version used by format directive interpreters.
;;;
(defmacro next-arg (&optional offset)
(error 'format-error
:complaint "No more arguments."
,@(when offset
`(:offset ,offset))))
(when *logical-block-popper*
(funcall *logical-block-popper*))
(pop args)))
(defmacro def-complex-format-directive (char lambda-list &body body)
(let ((defun-name (intern (cl:format nil
"~:@(~:C~)-FORMAT-DIRECTIVE-EXPANDER"
char)))
(directive (gensym))
(directives (if lambda-list (car (last lambda-list)) (gensym))))
`(progn
(defun ,defun-name (,directive ,directives)
,@(if lambda-list
`((let ,(mapcar #'(lambda (var)
`(,var
(,(intern (concatenate
'string
"FORMAT-DIRECTIVE-"
(symbol-name var))
(symbol-package 'foo))
,directive)))
(butlast lambda-list))
,@body))
`((declare (ignore ,directive ,directives))
,@body)))
(%set-format-directive-expander ,char #',defun-name))))
(defmacro def-format-directive (char lambda-list &body body)
(let ((directives (gensym))
(declarations nil)
(body-without-decls body))
(loop
(let ((form (car body-without-decls)))
(unless (and (consp form) (eq (car form) 'declare))
(return))
(push (pop body-without-decls) declarations)))
(setf declarations (reverse declarations))
`(def-complex-format-directive ,char (,@lambda-list ,directives)
,@declarations
(values (progn ,@body-without-decls)
,directives))))
(defmacro expand-bind-defaults (specs params &body body)
(once-only ((params params))
(if specs
(collect ((expander-bindings) (runtime-bindings))
(dolist (spec specs)
(destructuring-bind (var default) spec
(let ((symbol (gensym)))
(expander-bindings
`(,var ',symbol))
(runtime-bindings
`(list ',symbol
(let* ((param-and-offset (pop ,params))
(offset (car param-and-offset))
(param (cdr param-and-offset)))
(case param
(:arg `(or ,(expand-next-arg offset)
,,default))
(:remaining
(setf *only-simple-args* nil)
'(length args))
((nil) ,default)
(t param))))))))
`(let ,(expander-bindings)
`(let ,(list ,@(runtime-bindings))
,@(if ,params
(error 'format-error
:complaint
"Too many parameters, expected no more than ~D"
:arguments (list ,(length specs))
:offset (caar ,params)))
,,@body)))
`(progn
(when ,params
(error 'format-error
:complaint "Too many parameters, expected no more than 0"
:offset (caar ,params)))
,@body))))
(defmacro def-complex-format-interpreter (char lambda-list &body body)
(let ((defun-name
(intern (cl:format nil "~:@(~:C~)-FORMAT-DIRECTIVE-INTERPRETER"
char)))
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
(directive (gensym))
(directives (if lambda-list (car (last lambda-list)) (gensym))))
`(progn
(defun ,defun-name (stream ,directive ,directives orig-args args)
(declare (ignorable stream orig-args args))
,@(if lambda-list
`((let ,(mapcar #'(lambda (var)
`(,var
(,(intern (concatenate
'string
"FORMAT-DIRECTIVE-"
(symbol-name var))
(symbol-package 'foo))
,directive)))
(butlast lambda-list))
(values (progn ,@body) args)))
`((declare (ignore ,directive ,directives))
,@body)))
(%set-format-directive-interpreter ,char #',defun-name))))
(defmacro def-format-interpreter (char lambda-list &body body)
(let ((directives (gensym)))
`(def-complex-format-interpreter ,char (,@lambda-list ,directives)
,@body
,directives)))
(defmacro interpret-bind-defaults (specs params &body body)
(once-only ((params params))
(collect ((bindings))
(dolist (spec specs)
(destructuring-bind (var default) spec
(bindings `(,var (let* ((param-and-offset (pop ,params))
(offset (car param-and-offset))
(param (cdr param-and-offset)))
(case param
(:arg (next-arg offset))
(:remaining (length args))
((nil) ,default)
(t param)))))))
`(let* ,(bindings)
(when ,params
(error 'format-error
:complaint
"Too many parameters, expected no more than ~D"
:arguments (list ,(length specs))
:offset (caar ,params)))
,@body))))
); eval-when
(defun %set-format-directive-expander (char fn)
(setf (aref *format-directive-expanders* (char-code (char-upcase char))) fn)
char)
(defun %set-format-directive-interpreter (char fn)
(setf (aref *format-directive-interpreters*
(char-code (char-upcase char)))
fn)
char)
(defun find-directive (directives kind stop-at-semi)
(if directives
(let ((next (car directives)))
(if (format-directive-p next)
(let ((char (format-directive-character next)))
(if (or (char= kind char)
(and stop-at-semi (char= char #\;)))
(car directives)
(find-directive
(cdr (flet ((after (char)
(member (find-directive (cdr directives)
char
nil)
directives)))
(case char
(#\( (after #\)))
(#\< (after #\>))
(#\[ (after #\]))
(#\{ (after #\}))
(t directives))))
kind stop-at-semi)))
(find-directive (cdr directives) kind stop-at-semi)))))
;;;; Simple outputting noise.
(defun format-write-field (stream string mincol colinc minpad padchar padleft)
(unless padleft
(write-string string stream))
(dotimes (i minpad)
(write-char padchar stream))
(do ((chars (+ (length string) minpad) (+ chars colinc)))
((>= chars mincol))
(dotimes (i colinc)
(write-char padchar stream)))
(when padleft
(write-string string stream)))
(defun format-princ (stream arg colonp atsignp mincol colinc minpad padchar)
(format-write-field stream
(if (or arg (not colonp))
(princ-to-string arg)
"()")
mincol colinc minpad padchar atsignp))
(def-format-directive #\A (colonp atsignp params)
(if params
(expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
(padchar #\space))
`(format-princ stream ,(expand-next-arg) ',colonp ',atsignp
,mincol ,colinc ,minpad ,padchar))
`(princ ,(if colonp
`(or ,(expand-next-arg) "()")
(expand-next-arg))
stream)))
(def-format-interpreter #\A (colonp atsignp params)
(if params
(interpret-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
(padchar #\space))
params
(format-princ stream (next-arg) colonp atsignp
mincol colinc minpad padchar))
(princ (if colonp (or (next-arg) "()") (next-arg)) stream)))
(defun format-prin1 (stream arg colonp atsignp mincol colinc minpad padchar)
(format-write-field stream
(if (or arg (not colonp))
(prin1-to-string arg)
"()")
mincol colinc minpad padchar atsignp))
(def-format-directive #\S (colonp atsignp params)
(cond (params
(expand-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
(padchar #\space))
`(format-prin1 stream ,(expand-next-arg) ,colonp ,atsignp
,mincol ,colinc ,minpad ,padchar)))
(colonp
(if arg
(prin1 arg stream)
(princ "()" stream))))
(t
`(prin1 ,(expand-next-arg) stream))))
(def-format-interpreter #\S (colonp atsignp params)
(cond (params
(interpret-bind-defaults ((mincol 0) (colinc 1) (minpad 0)
(padchar #\space))
params
(format-prin1 stream (next-arg) colonp atsignp
mincol colinc minpad padchar)))
(colonp
(let ((arg (next-arg)))
(if arg
(prin1 arg stream)
(princ "()" stream))))
(t
(prin1 (next-arg) stream))))
(def-format-directive #\C (colonp atsignp params)
(expand-bind-defaults () params
(if colonp
`(format-print-named-character ,(expand-next-arg) stream)
(if atsignp
`(prin1 ,(expand-next-arg) stream)
`(write-char ,(expand-next-arg) stream)))))
(def-format-interpreter #\C (colonp atsignp params)
(interpret-bind-defaults () params
(if colonp
(format-print-named-character (next-arg) stream)
(if atsignp
(prin1 (next-arg) stream)
(write-char (next-arg) stream)))))
(defun format-print-named-character (char stream)
(let* ((name (char-name char)))
(cond (name
(write-string (string-capitalize name) stream))
((<= 0 (char-code char) 31)
;; Print control characters as "^"<char>
(write-char #\^ stream)
(write-char (code-char (+ 64 (char-code char))) stream))
(t
(write-char char stream)))))
(def-format-directive #\W (colonp atsignp params)
(expand-bind-defaults () params
(if (or colonp atsignp)
`(let (,@(when colonp
'((*print-pretty* t)))
,@(when atsignp
'((*print-level* nil)
(*print-length* nil))))
(output-object ,(expand-next-arg) stream))
`(output-object ,(expand-next-arg) stream))))
(def-format-interpreter #\W (colonp atsignp params)
(interpret-bind-defaults () params
(let ((*print-pretty* (or colonp *print-pretty*))
(*print-level* (and atsignp *print-level*))
(*print-length* (and atsignp *print-length*)))
(output-object (next-arg) stream))))
;;;; Integer outputting.
;;; FORMAT-PRINT-NUMBER does most of the work for the numeric printing
;;; directives. The parameters are interpreted as defined for ~D.
(defun format-print-integer (stream number print-commas-p print-sign-p
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
radix mincol padchar commachar commainterval)
(let ((*print-base* radix)
(*print-radix* nil))
(if (integerp number)
(let* ((text (princ-to-string (abs number)))
(commaed (if print-commas-p
(format-add-commas text commachar commainterval)
text))
(signed (cond ((minusp number)
(concatenate 'string "-" commaed))
(print-sign-p
(concatenate 'string "+" commaed))
(t commaed))))
;; colinc = 1, minpad = 0, padleft = t
(format-write-field stream signed mincol 1 0 padchar t))
(princ number))))
(defun format-add-commas (string commachar commainterval)
(let ((length (length string)))
(multiple-value-bind (commas extra)
(truncate (1- length) commainterval)
(let ((new-string (make-string (+ length commas)))
(first-comma (1+ extra)))
(replace new-string string :end1 first-comma :end2 first-comma)
(do ((src first-comma (+ src commainterval))
(dst first-comma (+ dst commainterval 1)))
((= src length))
(setf (schar new-string dst) commachar)
(replace new-string string :start1 (1+ dst)
:start2 src :end2 (+ src commainterval)))
new-string))))
(defun expand-format-integer (base colonp atsignp params)
(if (or colonp atsignp params)
(expand-bind-defaults
((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
params
`(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
,base ,mincol ,padchar ,commachar
,commainterval))
`(write ,(expand-next-arg) :stream stream :base ,base :radix nil
:escape nil)))
(defmacro interpret-format-integer (base)
`(if (or colonp atsignp params)
(interpret-bind-defaults
((mincol 0) (padchar #\space) (commachar #\,) (commainterval 3))
params
(format-print-integer stream (next-arg) colonp atsignp ,base mincol
padchar commachar commainterval))
(write (next-arg) :stream stream :base ,base :radix nil :escape nil)))
(def-format-directive #\D (colonp atsignp params)
(expand-format-integer 10 colonp atsignp params))
(def-format-interpreter #\D (colonp atsignp params)
(interpret-format-integer 10))
(def-format-directive #\B (colonp atsignp params)
(expand-format-integer 2 colonp atsignp params))
(def-format-interpreter #\B (colonp atsignp params)
(interpret-format-integer 2))
(def-format-directive #\O (colonp atsignp params)
(expand-format-integer 8 colonp atsignp params))
(def-format-interpreter #\O (colonp atsignp params)
(interpret-format-integer 8))
(def-format-directive #\X (colonp atsignp params)
(expand-format-integer 16 colonp atsignp params))
(def-format-interpreter #\X (colonp atsignp params)
(interpret-format-integer 16))
(def-format-directive #\R (colonp atsignp params)
(if params
(expand-bind-defaults
((base 10) (mincol 0) (padchar #\space) (commachar #\,)
(commainterval 3))
params
`(format-print-integer stream ,(expand-next-arg) ,colonp ,atsignp
,base ,mincol
,padchar ,commachar ,commainterval))
(if atsignp
(if colonp
`(format-print-old-roman stream ,(expand-next-arg))
`(format-print-roman stream ,(expand-next-arg)))
(if colonp
`(format-print-ordinal stream ,(expand-next-arg))
`(format-print-cardinal stream ,(expand-next-arg))))))
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
(def-format-interpreter #\R (colonp atsignp params)
(if params
(interpret-bind-defaults
((base 10) (mincol 0) (padchar #\space) (commachar #\,)
(commainterval 3))
params
(format-print-integer stream (next-arg) colonp atsignp base mincol
padchar commachar commainterval))
(if atsignp
(if colonp
(format-print-old-roman stream (next-arg))
(format-print-roman stream (next-arg)))
(if colonp
(format-print-ordinal stream (next-arg))
(format-print-cardinal stream (next-arg))))))
(defconstant cardinal-ones
#(nil "one" "two" "three" "four" "five" "six" "seven" "eight" "nine"))
(defconstant cardinal-tens
#(nil nil "twenty" "thirty" "forty"
"fifty" "sixty" "seventy" "eighty" "ninety"))
(defconstant cardinal-teens
#("ten" "eleven" "twelve" "thirteen" "fourteen" ;;; RAD
"fifteen" "sixteen" "seventeen" "eighteen" "nineteen"))
(defconstant cardinal-periods
#("" " thousand" " million" " billion" " trillion" " quadrillion"
" quintillion" " sextillion" " septillion" " octillion" " nonillion"
" decillion" " undecillion" " duodecillion" " tredecillion"
" quattuordecillion" " quindecillion" " sexdecillion" " septendecillion"
" octodecillion" " novemdecillion" " vigintillion"))
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
(defconstant ordinal-ones
#(nil "first" "second" "third" "fourth"
"fifth" "sixth" "seventh" "eighth" "ninth")
"Table of ordinal ones-place digits in English")
(defconstant ordinal-tens
#(nil "tenth" "twentieth" "thirtieth" "fortieth"
"fiftieth" "sixtieth" "seventieth" "eightieth" "ninetieth")
"Table of ordinal tens-place digits in English")
(defun format-print-small-cardinal (stream n)
(multiple-value-bind
(hundreds rem) (truncate n 100)
(when (plusp hundreds)
(write-string (svref cardinal-ones hundreds) stream)
(write-string " hundred" stream)
(when (plusp rem)
(write-char #\space stream)))
(when (plusp rem)
(multiple-value-bind (tens ones)
(truncate rem 10)
(cond ((< 1 tens)
(write-string (svref cardinal-tens tens) stream)
(when (plusp ones)
(write-char #\- stream)
(write-string (svref cardinal-ones ones) stream)))
((= tens 1)
(write-string (svref cardinal-teens ones) stream))
((plusp ones)
(write-string (svref cardinal-ones ones) stream)))))))
(defun format-print-cardinal (stream n)
(cond ((minusp n)
(write-string "negative " stream)
(format-print-cardinal-aux stream (- n) 0 n))
((zerop n)
(write-string "zero" stream))
(t
(format-print-cardinal-aux stream n 0 n))))
(defun format-print-cardinal-aux (stream n period err)
(multiple-value-bind (beyond here) (truncate n 1000)
(unless (<= period 20)
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
(error "Number too large to print in English: ~:D" err))
(unless (zerop beyond)
(format-print-cardinal-aux stream beyond (1+ period) err))
(unless (zerop here)
(unless (zerop beyond)
(write-char #\space stream))
(format-print-small-cardinal stream here)
(write-string (svref cardinal-periods period) stream))))
(defun format-print-ordinal (stream n)
(when (minusp n)
(write-string "negative " stream))
(let ((number (abs n)))
(multiple-value-bind
(top bot) (truncate number 100)
(unless (zerop top)
(format-print-cardinal stream (- number bot)))
(when (and (plusp top) (plusp bot))
(write-char #\space stream))
(multiple-value-bind
(tens ones) (truncate bot 10)
(cond ((= bot 12) (write-string "twelfth" stream))
((= tens 1)
(write-string (svref cardinal-teens ones) stream);;;RAD
(write-string "th" stream))
((and (zerop tens) (plusp ones))
(write-string (svref ordinal-ones ones) stream))
((and (zerop ones)(plusp tens))
(write-string (svref ordinal-tens tens) stream))
((plusp bot)
(write-string (svref cardinal-tens tens) stream)
(write-char #\- stream)
(write-string (svref ordinal-ones ones) stream))
((plusp number)
(write-string "th" stream))
(t
(write-string "zeroeth" stream)))))))
;;; Print Roman numerals
(defun format-print-old-roman (stream n)
(unless (< 0 n 5000)
(error "Number too large to print in old Roman numerals: ~:D" n))
(do ((char-list '(#\D #\C #\L #\X #\V #\I) (cdr char-list))
(val-list '(500 100 50 10 5 1) (cdr val-list))
(cur-char #\M (car char-list))
(cur-val 1000 (car val-list))
(start n (do ((i start (progn
(write-char cur-char stream)
(- i cur-val))))
((< i cur-val) i))))
((zerop start))))
(defun format-print-roman (stream n)
(unless (< 0 n 4000)
(error "Number too large to print in Roman numerals: ~:D" n))
(do ((char-list '(#\D #\C #\L #\X #\V #\I) (cdr char-list))
(val-list '(500 100 50 10 5 1) (cdr val-list))
(sub-chars '(#\C #\X #\X #\I #\I) (cdr sub-chars))
(sub-val '(100 10 10 1 1 0) (cdr sub-val))
(cur-char #\M (car char-list))
(cur-val 1000 (car val-list))
(cur-sub-char #\C (car sub-chars))
(cur-sub-val 100 (car sub-val))
(start n (do ((i start (progn
(write-char cur-char stream)
(- i cur-val))))
((< i cur-val)
(cond ((<= (- cur-val cur-sub-val) i)
(write-char cur-sub-char stream)
(write-char cur-char stream)
(- i (- cur-val cur-sub-val)))
(t i))))))
((zerop start))))
;;;; Plural.
(def-format-directive #\P (colonp atsignp params end)
(expand-bind-defaults () params
(let ((arg (cond
((not colonp)
(expand-next-arg))
(*orig-args-available*
`(if (eq orig-args args)
(error 'format-error
:complaint "No previous argument."
:offset ,(1- end))
(do ((arg-ptr orig-args (cdr arg-ptr)))
((eq (cdr arg-ptr) args)
(car arg-ptr)))))
(*only-simple-args*
(unless *simple-args*
(error 'format-error
:complaint "No previous argument."))
(caar *simple-args*))
(t
(throw 'need-orig-args nil)))))
(if atsignp
`(write-string (if (eql ,arg 1) "y" "ies") stream)
`(unless (eql ,arg 1) (write-char #\s stream))))))