guile-devel
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

doc ice-9 format


From: Kevin Ryde
Subject: doc ice-9 format
Date: Mon, 19 Jul 2004 09:14:02 +1000
User-agent: Gnus/5.110003 (No Gnus v0.3) Emacs/21.3 (gnu/linux)

This is a big revision of the ice-9 format node, trying to actually
describe all the features.

There's lots of examples rather than too many words, which I think
will be good for cut and paste programming, and I think with so many
options and stuff that examples are almost the only way to show what's
meant.

I looked at the old slib fmtdoc.txi, the common lisp spec, and the
code, and tried to make sure they all agreed before describing
something.

I struck a few bits of apparent dodginess, where the code doesn't
quite agree with my reading of the CL spec.  See the FIXMEs in the
texi at the end.  If I'm right that there's some problems then they're
probably fixable, but it might not be easy since the code is nice and
hairy.




1.1 Formatted Output
====================

The `format' function is a powerful way to print numbers, strings and
other objects together with literal text under the control of a format
string.  This function is available from

     (use-modules (ice-9 format))

   A format string is generally more compact and easier than using just
the standard procedures like `display', `write' and `newline'.
Parameters in the output string allow for flexibility in output style,
and parameters taken from the arguments allow runtime flexibility.

   `format' is similar to the Common Lisp procedure of the same name,
but it's not identical and doesn't have quite all the features found in
Common Lisp.

   C programmers will note the similarity between `format' and
`printf', though escape sequences are marked with ~ instead of %, and
are more powerful.


 -- Scheme Procedure: format dest fmt [args...]
     Write output specified by the FMT string to DEST.  DEST can be an
     output port, `#t' for `current-output-port' (*note Default
     Ports::), any number for `current-error-port', or `#f' to return
     the output as a string.

     FMT can contain literal text to be output, and ~ escapes.  Each
     escape has the form

          ~ [param [, param...] [:] address@hidden code

     code is a character determining the escape sequence.  The : and @
     characters are optional modifiers, one or both of which change the
     way various codes operate.  Optional parameters are accepted by
     some codes too.  Parameters have the following forms,

    [+/-] number
          An integer, with optional + or -.

    '  (apostrophe)
          The following character in the format string, for instance 'z
          for z.

    v
          The next function argument as the parameter.  v stands for
          "variable", a parameter can be calculated at runtime and
          included in the arguments.  v is not case sensitive, upper
          case V can be used too.

    #
          The number of arguments remaining.  (See ~* below for some
          usages.)

     Parameters are separated by commas (,).  A parameter can be left
     empty to keep its default value when supplying later parameters.


     The following escape codes are available.  The code letters are not
     case-sensitive, upper and lower case are the same.

    ~a
    ~s
          Object output.  Parameters: MINWIDTH, PADINC, MINPAD, PADCHAR.

          ~a outputs an argument like `display', ~s outputs an argument
          like `write' (*note Writing::).

               (format #t "~a" "foo") -| foo
               (format #t "~s" "foo") -| "foo"

          With the : modifier, objects which don't have an external
          representation are put in quotes like a string.

               (format #t "~:a" car) -| "#<primitive-procedure car>"

          If the output is less than MINWIDTH characters (default 0),
          it's padded on the right with PADCHAR (default space).  The @
          modifier puts the padding on the left instead.

               (format #f "~5a" 'abc)       => "abc  "
               (format #f "~5,,,'address@hidden" 'abc) => "--abc"

          MINPAD is a minimum for the padding then plus a multiple of
          PADINC.  Ie. the padding is MINPAD + N * PADINC, where N is
          the smallest integer making the total object plus padding
          greater than or equal to MINWIDTH.  The default MINPAD is 0
          and the default PADINC is 1 (imposing no minimum or multiple).

               (format #f "~5,1,4a" 'abc) => "abc    "

    ~c
          Character.  Parameter: CHARNUM.

          Output a character.  The default is to simply output, as per
          `write-char' (*note Writing::).  With the @ modifier output
          is in `write' style.  Or with the : modifier control
          characters (ASCII 0 to 31) are printed in ^X form.

               (format #t "~c" #\z)        -| z
               (format #t "address@hidden" #\z)       -| #\z
               (format #t "~:c" #\newline) -| ^J

          If the CHARNUM parameter is given an argument is not taken but
          instead the character output is `(integer->char CHARNUM)'
          (*note Characters::).  This can be used for instance to output
          characters given by their ASCII code.

               (format #t "~65c")  -| A

    ~d
    ~x
    ~o
    ~b
          Integer.  Parameters: MINWIDTH, PADCHAR, COMMACHAR,
          COMMAWIDTH.

          Output an integer argument as a decimal, hexadecimal, octal
          or binary integer (respectively).

               (format #t "~d" 123) -| 123

          With the @ modifier, a + sign is shown on positive numbers
          (not on zero).

               (format #t "address@hidden" 12) -| +1100

          If the output is less than the MINWIDTH parameter, it's padded
          on the left with the PADCHAR parameter (default space).

               (format #t "~5,'*d" 12)   -| ***12
               (format #t "~5,'0d" 12)   -| 00012
               (format #t "~3d"    1234) -| 1234

          The : modifier adds commas (or the COMMACHAR parameter) every
          three digits (or the COMMAWIDTH parameter many).

               (format #t "~:d" 1234567)         -| 1,234,567
               (format #t "~10,'*,'/,2:d" 12345) -| ***1/23/45

          Hexadecimal ~x output is in lower case, but the ~( and ~)
          case conversion directives described below can be used to get
          upper case.

               (format #t "~x"       65261) -| feed
               (format #t "~:@(~x~)" 65261) -| FEED

    ~r
          Integer in words, roman numerals, or a specified radix.
          Parameters: RADIX, MINWIDTH, PADCHAR, COMMACHAR, COMMAWIDTH.

          With no parameters output is in words as a cardinal like
          "ten", or with the : modifier as an ordinal like "tenth".

               (format #t "~r" 9)  -| nine        ;; cardinal
               (format #t "~r" -9) -| minus nine  ;; cardinal
               (format #t "~:r" 9) -| ninth       ;; ordinal

          And also with no parameters, the @ modifier gives roman
          numerals and @ and : together give old roman numerals.  In
          old roman numerals there's no "subtraction", so 9 is VIIII
          instead of IX.  In both cases only positive numbers can be
          output.

               (format #t "address@hidden" 89)  -| LXXXIX     ;; roman
               (format #t "~@:r" 89) -| LXXXVIIII  ;; old roman

          When a parameter is given it means numeric output in the
          specified RADIX.  The modifiers and parameters following the
          radix are the same as described for ~d etc above.

               (format #f "~3r" 27)   => "1000"    ;; base 3
               (format #f "~3,5r" 26) => "  222"   ;; base 3 width 5

    ~f
          Fixed-point float.  Parameters: WIDTH, DECIMALS, SCALE,
          OVERFLOWCHAR, PADCHAR.

          Output a number or number string in fixed-point format, ie.
          with a decimal point.

               (format #t "~f" 5)      -| 5.0
               (format #t "~f" "123")  -| 123.0
               (format #t "~f" "1e-1") -| 0.1

          With the @ modifier a + sign is shown on non-negative numbers
          (including zero).

               (format #t "address@hidden" 0) -| +0.0

          If the output is less than WIDTH characters it's padded on the
          left with PADCHAR (space by default).  If the output equals or
          exceeds WIDTH then there's no padding.  The default for WIDTH
          is no padding.

               (format #f "~6f" -1.5)      => "  -1.5"
               (format #f "~6,,,,'*f" 23)  => "**23.0"
               (format #f "~6f" 1234567.0) => "1234567.0"

          DECIMALS is how many digits to print after the decimal point,
          the value is rounded or padded with zeros as necessary.  (The
          default is to output as many decimals as required.)

               (format #t "~1,2f" 3.125) -| 3.13
               (format #t "~1,2f" 1.5)   -| 1.50

          SCALE is a power of 10 applied to the value, moving the
          decimal point that many places.  A positive SCALE increases
          the value shown, a negative decreases it.

               (format #t "~,,2f" 1234)  -| 123400.0
               (format #t "~,,-2f" 1234) -| 12.34

          If OVERFLOWCHAR and WIDTH are both given and if the output
          would exceed WIDTH, then that many OVERFLOWCHARs are printed
          instead of the value.

               (format #t "~5,,,'xf" 12345) -| 12345
               (format #t "~4,,,'xf" 12345) -| xxxx

    ~e
          Exponential float.  Parameters: WIDTH, MANTDIGITS, EXPDIGITS,
          INTDIGITS, OVERFLOWCHAR, PADCHAR, EXPCHAR.

          Output a number or number string in exponential notation.

               (format #t "~e" 5000.25) -| 5.00025E+3
               (format #t "~e" "123.4") -| 1.234E+2
               (format #t "~e" "1e4")   -| 1.0E+4

          With the @ modifier a + sign is shown on non-negative numbers
          (including zero).  (This is for the mantissa, a + or - sign
          is always shown on the exponent.)

               (format #t "address@hidden" 5000.0) -| +5.0E+3

          If the output is less than WIDTH characters it's padded on the
          left with PADCHAR (space by default).  The default WIDTH is
          to output with no padding.

               (format #f "~10e" 1234.0)     => "  1.234E+3"
               (format #f "~10,,,,,'*e" 0.5) => "****5.0E-1"

          MANTDIGITS is the number of digits shown in the mantissa after
          the decimal point.  The value is rounded or trailing zeros
          are added as necessary.  The default MANTDIGITS is to show as
          much as needed by the value.

               (format #f "~,3e" 11111.0) => "1.111E+4"
               (format #f "~,8e" 123.0)   => "1.23000000E+2"

          EXPDIGITS is the minimum number of digits shown for the
          exponent, with leading zeros added if necessary.  The default
          for EXPDIGITS is to show only as many digits as required.  At
          least 1 digit is always shown.

               (format #f "~,,1e" 1.0e99) => "1.0E+99"
               (format #f "~,,6e" 1.0e99) => "1.0E+000099"

          INTDIGITS (default 1) is the number of digits to show before
          the decimal point in the mantissa.  INTDIGITS can be zero, in
          which case the integer part is a single 0, or it can be
          negative, in which case leading zeros are shown after the
          decimal point.

               (format #t "~,,,3e" 12345.0)  -| 123.45E+2
               (format #t "~,,,0e" 12345.0)  -| 0.12345E+5
               (format #t "~,,,-3e" 12345.0) -| 0.00012345E+8

          If OVERFLOWCHAR is given then WIDTH is a hard limit.  If the
          output would exceed WIDTH then instead that many
          OVERFLOWCHARs are printed.

               (format #f "~6,,,,'xe" 100.0) => "1.0E+2"
               (format #f "~3,,,,'xe" 100.0) => "xxx"

          EXPCHAR is the exponent marker character, the default is E.

               (format #t "~,,,,,,'ee" 100.0) -| 1.0e+2

    ~g
          General float.  Parameters: WIDTH, MANTDIGITS, EXPDIGITS,
          INTDIGITS, OVERFLOWCHAR, PADCHAR, EXPCHAR.

          Output a number or number string in either exponential format
          the same as ~e, or fixed-point format like ~f but aligned
          where the mantissa would have been and followed by padding
          where the exponent would have been.

          Fixed-point is used when the absolute value is 0.1 or more
          and it takes no more space than the mantissa in exponential
          format, ie.  basically up to MANTDIGITS digits.

               (format #f "~12,4,2g" 999.0)    => "   999.0    "
               (format #f "~12,4,2g" "100000") => "  1.0000E+05"

          The parameters are interpreted as per ~e above.  When
          fixed-point is used, the DECIMALS parameter to ~f is
          established from MANTDIGITS, so as to give a total
          MANTDIGITS+1

    ~$
          Monetary style fixed-point float.  Parameters: DECIMALS,
          INTDIGITS, WIDTH, PADCHAR.

          Output a number or number string in fixed-point format, ie.
          with a decimal point.  DECIMALS is the number of decimal
          places to show, default 2.

               (format #t "~$" 5)       -| 5.00
               (format #t "~4$" "2.25") -| 2.2500
               (format #t "~4$" "1e-2") -| 0.0100

          With the @ modifier a + sign is shown on non-negative numbers
          (including zero).

               (format #t "address@hidden" 0) -| +0.00

          INTDIGITS is a minimum number of digits to show in the integer
          part of the value (default 1).

               (format #t "~,3$" 9.5)   -| 009.50
               (format #t "~,0$" 0.125) -| .13

          If the output is less than WIDTH characters (default 0), it's
          padded on the left with PADCHAR (default space).  With the :
          modifier the padding is output after the sign.

               (format #f "~,,8$" -1.5)   => "   -1.50"
               (format #f "~,,8:$" -1.5)  => "-   1.50"
               (format #f "~,,8,'.@:$" 3) => "+...3.00"

          Note that floating point for dollar amounts is generally not
          a good idea, because a cent 0.01 cannot be represented
          exactly in the binary floating point Guile uses, which leads
          to slowly accumulating rounding errors.  Keeping values as
          cents (or fractions of a cent) in integers then printing with
          the scale option in ~f may be a better approach.

    ~i
          Complex fixed-point float.  Parameters: WIDTH, DECIMALS,
          SCALE, OVERFLOWCHAR, PADCHAR.

          Output the argument as a complex number, with both real and
          imaginary part shown (even if one or both are zero).

          The parameters and modifiers are the same as for fixed-point
          ~f described above.  The real and imaginary parts are both
          output with the same given parameters and modifiers, except
          that for the imaginary part the @ modifier is always enabled,
          so as to print a + sign between the real and imaginary parts.

               (format #t "~i" 1)  -| 1.0+0.0i

    ~p
          Plural.  No parameters.

          Output nothing if the argument is 1, or `s' for any other
          value.

               (format #t "enter name~p" 1) -| enter name
               (format #t "enter name~p" 2) -| enter names

          With the @ modifier, the output is `y' for 1 or `ies'
          otherwise.

               (format #t "address@hidden" 1) -| puppy
               (format #t "address@hidden" 2) -| puppies

          The : modifier means re-use the preceding argument instead of
          taking a new one, which can be convenient when printing some
          sort of count.

               (format #t "~d cat~:p" 9) -| 9 cats

    ~y
          Pretty print.  No parameters.

          Output an argument with `pretty-print' (*note Pretty
          Printing::).

    ~?
    ~k
          Sub-format.  No parameters.

          Take a format string argument and a second argument which is
          a list of arguments for it, and output the result.  With the @
          modifier, the arguments for the sub-format are taken directly
          rather than from a list.

               (format #t "~?"     "~d ~d" '(1 2))    -| 1 2
               (format #t "address@hidden ~s" "~d ~d" 1 2 "foo") -| 1 2 "foo"

          ~? and ~k are the same, ~k is provided for T-Scheme
          compatibility.

    ~*
          Argument jumping.  Parameter: N.

          Move forward N arguments (default 1) in the argument list.
          With the : modifier move backwards.  N can be negative to
          move backwards too.

               (format #f "~d ~:*~d" 6) => "6 6"

          With the @ modifier, move to argument number N, with the
          first argument being number 0 (the default for N).

               (format #f "~d~d again address@hidden" 1 2) => "12 again 12"
               (format #f "~d~d~d address@hidden" 1 2 3)  => "123 23"

          At the end of the format string the last argument must have
          been consumed, or a "too many arguments" error results.  If
          the last argument is not the last to be printed, then a move
          to skip the remaining must be given.  This can be done with
          the # parameter (count of remaining arguments).

               (format #t "~2*~d"    1 2 3 4)  ;; error
               (format #t "~2*~d~#*" 1 2 3 4)  => 3

          A # move to the end followed by a : modifier move back can be
          used for an absolute position relative to the end of the
          argument list, a reverse of what the @ modifier does.

    ~t
          Advance to a column position.  Parameters: COLNUM, COLINC,
          PADCHAR.

          Output PADCHAR (space by default) to move to the given COLNUM
          column.  The start of the line is column 0, the default for
          COLNUM is 1.

               (format #f "~tX")  => " X"
               (format #f "~3tX") => "   X"

          If the current column is already past COLNUM, then the move is
          to there plus a multiple of COLINC, ie. column COLNUM + N *
          COLINC for the smallest N which makes that value greater than
          or equal to the current column.  The default COLINC is 1
          (which means no further move).

               (format #f "abcd~2,5,'.tx") => "abcd...x"

          With the @ modifier, COLNUM is relative to the current
          column.  COLNUM many padding characters are output, then
          further padding to make the current column a multiple of
          COLINC, if it isn't already so.

               (format #f "a~3,5'address@hidden") => "a****x"

    ~~
          Tilde character.  Parameter: N.

          Output a tilde character ~, or N many if a parameter is
          given.  Normally ~ introduces an escape sequence, ~~ is the
          way to output a literal tilde.

    ~%
          Newline.  Parameter: N.

          Output a newline character, or N many if a parameter is given.
          A newline (or a few newlines) can of course be output just by
          including them in the format string.

    ~&
          Start a new line.  Parameter: N.

          Output a newline if not already at the start of a line.  With
          a parameter, output that many newlines, but with the first
          only if not already at the start of a line.  So for instance
          3 would be a newline if not already at the start of a line,
          and 2 further newlines.

    ~_
          Space character.  Parameter: N.

          Output a space character, or N many if a parameter is given.

          With a variable parameter this is one way to insert runtime
          calculated padding (~t or the various field widths can do
          similar things).

               (format #f "~v_foo" 4) => "    foo"

    ~/
          Tab character.  Parameter: N.

          Output a tab character, or N many if a parameter is given.

    ~|
          Formfeed character.  Parameter: N.

          Output a formfeed character, or N many if a parameter is
          given.

    ~!
          Force output.  No parameters.

          At the end of output, call `force-output' to flush any
          buffers on the destination (*note Writing::).  ~! can occur
          anywhere in the format string, but the force is done at the
          end of output.

          When output is to a string (destination `#f'), ~! does
          nothing.

    ~newline  (ie. newline character)
          Continuation line.  No parameters.

          Skip this newline and any following whitespace in the format
          string, don't send it to the output.  With the : modifier the
          newline is not output but any further following whitespace
          is.  With the @ modifier the newline is output but not any
          following whitespace.

          This escape can be used to break up a long format string into
          multiple lines for readability, but supress that extra
          whitespace.

               (format #f "abc~
                           ~d def~
                           ~d" 1 2) => "abc1 def2"

    ~( ~)
          Case conversion.  Between ~( and ~) the case of all output is
          changed.  The modifiers on ~( control the conversion.

               no modifiers -- lower case.

               : and @ together -- upper case.

          For example,

               (format #t "~(Hello~)")   -| hello
               (format #t "~@:(Hello~)") -| HELLO

          In the future it's intended the modifiers : and @ alone will
          capitalize the first letters of words, as per Common Lisp
          `format', but the current implementation of this is flawed and
          not recommended for use.

          Case conversions do not nest, currently.  This might change
          in the future, but if it does then it will be to Common Lisp
          style where the outermost conversion has priority, overriding
          inner ones (and making those fairly pointless).

    ~{ ~}
          Iteration.  Parameter: MAXREPS (for ~{).

          The format between ~{ and ~} is iterated.  The modifiers to
          ~{ determine how arguments are taken.  The default is a list
          argument with each iteration successively consuming elements
          from it.  This is a convenient way to output a whole list.

               (format #t "~{~d~}"     '(1 2 3))       -| 123
               (format #t "~{~s=~d ~}" '("x" 1 "y" 2)) -| "x"=1 "y"=2

          With the : modifier a list of lists argument is taken, each
          of those lists gives the arguments for the iterated format.

               (format #t "~:{~dx~d ~}" '((1 2) (3 4) (5 6))) -| 1x2 3x4 5x6

          With the @ modifier, the remaining arguments are used, each
          iteration successively consuming elements.

               (format #t "address@hidden"     1 2 3)       -| 123
               (format #t "address@hidden ~}" "x" 1 "y" 2) -| "x"=1 "y"=2

          With both : and @ modifiers, the remaining arguments are
          used, each is a list of arguments for the format.

               (format #t "~:@{~dx~d ~}" '(1 2) '(3 4) '(5 6)) -| 1x2 3x4 5x6

          Iteration stops when there are no more arguments or when the
          MAXREPS parameter to ~{ is reached (default no maximum).

               (format #t "~2{~d~}" '(1 2 3 4)) -| 12

          If the format between ~{ and ~} is empty, then a format
          string argument is taken (before iteration argument(s)) and
          used instead.  This allows a sub-format (like ~? above) to be
          iterated.

               (format #t "~{~}" "~d" '(1 2 3)) -| 123

          Iterations can be nested, an inner iteration operates in the
          same way as described, but of course on the arguments the
          outer iteration provides it.  This can be used to work into
          nested list structures.  For example in the following the
          inner ~{~d~}x is applied to `(1 2)' then `(3 4 5)' etc.

               (format #t "~{~{~d~}x~}" '((1 2) (3 4 5))) -| 12x345x

    ~[ ~; ~]
          Conditional.  Parameter: SELECTOR.

          A conditional block is delimited by ~[ and ~], and ~;
          separates clauses within the block.  ~[ takes an integer
          argument and that number clause is used.  The first clause is
          number 0.

               (format #f "~[peach~;banana~;mango~]" 1)  => "banana"

          The SELECTOR parameter can be used for the clause number,
          instead of taking an argument.

               (format #f "~2[peach~;banana~;mango~]") => "mango"

          If the clause number is out of range then nothing is output.
          Or if the last ~; has the : modifier it's the default for a
          number out of range.

               (format #f "~[banana~;mango~]"         99) => ""
               (format #f "~[banana~;mango~:;fruit~]" 99) => "fruit"

          The : modifier to ~[ treats the argument as a flag, and
          expects two clauses.  The first used if the argument is `#f'
          or the second otherwise.

               (format #f "~:[false~;not false~]" #f)   => "false"
               (format #f "~:[false~;not false~]" 'abc) => "not false"

               (let ((n 3))
                 (format #t "~d gnu~:[s are~; is~] here" n (= 1 n)))
               -| 3 gnus are here

          The @ modifier to ~[ also treats the argument as a flag, and
          expects one clause.  If the argument is `#f' then no output
          is produced and the argument is consumed, otherwise the clause
          is used and the argument is not consumed by ~[, it's left for
          the clause.  This can be used for instance to suppress output
          if `#f' means something not available.

               (format #f "address@hidden" 27) => "temperature=27"
               (format #f "address@hidden" #f) => ""

    ~^
          Escape.  Parameters: VAL1, VAL2, VAL3.

          Stop formatting if there are no more arguments.  This can be
          used for instance to let a format string adapt to a variable
          number of arguments.

               (format #t "~d~^ ~d" 1)   -| 1
               (format #t "~d~^ ~d" 1 2) -| 1 2

          Within a ~{ ~} iteration, ~^ stops the current iteration step
          if there are no more arguments to that step, continuing with
          possible further steps (in the case of the : modifier to ~{)
          and the rest of the format.

               (format #f "~{~d~^/~} go"    '(1 2 3))     => "1/2/3 go"
               (format #f "~:{ ~d~^~d~} go" '((1) (2 3))) => " 1 23 go"

          Within a ~? or ~k sub-format, ~^ operates just within that
          sub-format.  If it terminates the sub-format then the
          originating format will still continue.

               (format #t "~? items" "~d~^ ~d" '(1))   -| 1 items
               (format #t "~? items" "~d~^ ~d" '(1 2)) -| 1 2 items

          The parameters to ~^ (which are numbers) change the condition
          used to terminate.  For a single parameter, termination is
          when that value is zero (notice this makes plain ~^
          equivalent to ~#^).  For two parameters, termination is when
          those two are equal.  For three parameters, termination is
          when VAL1 <= VAL2 and VAL2 <= VAL3.

    ~q
          Inquiry message.  Insert a copyright message into the output.
          With the : modifier insert the format implementation version.


     It's an error if there are too many or not enough arguments for the
     escapes in the format string.  (Unwanted arguments can be skipped
     with an argument jump ~#* described above if desired.)

     Iterations ~{ ~} and conditionals ~[ ~; ~] can be nested, but must
     be properly nested, meaning the inner form must be entirely within
     the outer form.  So it's not possible, for instance, to try to
     conditionalize the endpoint of an iteration.

          (format #t "~{ ~[ ... ~] ~}" ...)       ;; good
          (format #t "~{ ~[ ... ~} ... ~]" ...)   ;; bad

     The same applies to case conversions ~( ~), they must properly
     nest with respect to iterations and conditionals (though currently
     a case conversion cannot nest within another case conversion).

     When a sub-format (~?) is used, that sub-format string must be
     self-contained.  It cannot for instance give a ~{ to begin an
     iteration form and have the ~} up in the originating format, or
     similar.


   Guile contains a `format' procedure even when the module `(ice-9
format)' is not loaded.  The default `format' is `simple-format' (*note
Writing::), it doesn't support all escape sequences documented in this
section, and will signal an error if you try to use one of them.  The
reason for two versions is that the full `format' is fairly large and
requires some time to load.  `simple-format' is often adequate too.











@node Formatted Output,  , The Guile License, The Guile License
@section Formatted Output
@cindex formatted output

@c  For reference, in this section escapes like ~a are given in
@c  @nicode, to give code font in TeX etc, but leave them unadorned in
@c  Info.
@c
@c  The idea is to reduce clutter around what's shown, and avoid any
@c  possible confusion over whether the ` ' quotes are part of what
@c  should be entered.  (In particular for instance of course ' is
@c  meaningful in a format string, introducing a char parameter).

@c  @nicodeiterationbegin{} and @nicodeiterationend are @address@hidden
@c  and @address@hidden, but done as separate macros because makeinfo
@c  (version 4.7) doesn't like @nicode used with @{ and @} as
@c  arguments.
@ifinfo
@macro nicodeiterationbegin {}
address@hidden
@end macro
@end ifinfo
@ifnotinfo
@macro nicodeiterationbegin {}
@address@hidden
@end macro
@end ifnotinfo

@ifinfo
@macro nicodeiterationend {}
address@hidden
@end macro
@end ifinfo
@ifnotinfo
@macro nicodeiterationend {}
@address@hidden
@end macro
@end ifnotinfo

The @code{format} function is a powerful way to print numbers, strings
and other objects together with literal text under the control of a
format string.  This function is available from

@example
(use-modules (ice-9 format))
@end example

A format string is generally more compact and easier than using just
the standard procedures like @code{display}, @code{write} and
@code{newline}.  Parameters in the output string allow for flexibility
in output style, and parameters taken from the arguments allow runtime
flexibility.

@code{format} is similar to the Common Lisp procedure of the same
name, but it's not identical and doesn't have quite all the features
found in Common Lisp.

C programmers will note the similarity between @code{format} and
@code{printf}, though escape sequences are marked with @nicode{~}
instead of @nicode{%}, and are more powerful.

@sp 1
@deffn {Scheme Procedure} format dest fmt address@hidden
Write output specified by the @var{fmt} string to @var{dest}.
@var{dest} can be an output port, @code{#t} for
@code{current-output-port} (@pxref{Default Ports}), any number for
@code{current-error-port}, or @code{#f} to return the output as a
string.

@var{fmt} can contain literal text to be output, and @nicode{~}
escapes.  Each escape has the form

@example
~ [param [, address@hidden [:] [@@] code
@end example

@nicode{code} is a character determining the escape sequence.  The
@nicode{:} and @nicode{@@} characters are optional modifiers, one or
both of which change the way various codes operate.  Optional
parameters are accepted by some codes too.  Parameters have the
following forms,

@table @asis
@item @nicode{[+/-] number}
An integer, with optional @nicode{+} or @nicode{-}.
@item @nicode{'}  (apostrophe)
The following character in the format string, for instance @nicode{'z}
for @nicode{z}.
@item @nicode{v}
The next function argument as the parameter.  @nicode{v} stands for
``variable'', a parameter can be calculated at runtime and included in
the arguments.  @nicode{v} is not case sensitive, upper case
@nicode{V} can be used too.
@item @nicode{#}
The number of arguments remaining.  (See @nicode{~*} below for some
usages.)
@end table

Parameters are separated by commas (@nicode{,}).  A parameter can be
left empty to keep its default value when supplying later parameters.

@sp 1
The following escape codes are available.  The code letters are not
case-sensitive, upper and lower case are the same.

@table @asis
@item @nicode{~a}
@itemx @nicode{~s}
Object output.  Parameters: @var{minwidth}, @var{padinc},
@var{minpad}, @var{padchar}.

@nicode{~a} outputs an argument like @code{display}, @nicode{~s}
outputs an argument like @code{write} (@pxref{Writing}).  

@example
(format #t "~a" "foo") @print{} foo
(format #t "~s" "foo") @print{} "foo"
@end example

With the @nicode{:} modifier, objects which don't have an external
representation are put in quotes like a string.

@example
(format #t "~:a" car) @print{} "#<primitive-procedure car>"
@end example

If the output is less than @var{minwidth} characters (default 0), it's
padded on the right with @var{padchar} (default space).  The
@nicode{@@} modifier puts the padding on the left instead.

@example
(format #f "~5a" 'abc)       @result{} "abc  "
(format #f "~5,,,'-@@a" 'abc) @result{} "--abc"
@end example

@var{minpad} is a minimum for the padding then plus a multiple of
@var{padinc}.  Ie.@: the padding is @address@hidden + @var{N} *
@var{padinc}}, where @var{n} is the smallest integer making the total
object plus padding greater than or equal to @var{minwidth}.  The
default @var{minpad} is 0 and the default @var{padinc} is 1 (imposing
no minimum or multiple).

@example
(format #f "~5,1,4a" 'abc) @result{} "abc    "
@end example

@item @nicode{~c}
Character.  Parameter: @var{charnum}.

Output a character.  The default is to simply output, as per
@code{write-char} (@pxref{Writing}).  With the @nicode{@@} modifier
output is in @code{write} style.  Or with the @nicode{:} modifier
control characters (ASCII 0 to 31) are printed in @nicode{^X} form.

@example
(format #t "~c" #\z)        @print{} z
(format #t "~@@c" #\z)       @print{} #\z
(format #t "~:c" #\newline) @print{} ^J
@end example

If the @var{charnum} parameter is given an argument is not taken but
instead the character output is @code{(integer->char @var{charnum})}
(@pxref{Characters}).  This can be used for instance to output
characters given by their ASCII code.

@example
(format #t "~65c")  @print{} A
@end example

@item @nicode{~d}
@itemx @nicode{~x}
@itemx @nicode{~o}
@itemx @nicode{~b}
Integer.  Parameters: @var{minwidth}, @var{padchar}, @var{commachar},
@var{commawidth}.

Output an integer argument as a decimal, hexadecimal, octal or binary
integer (respectively).

@example
(format #t "~d" 123) @print{} 123
@end example

With the @nicode{@@} modifier, a @nicode{+} sign is shown on positive
numbers (not on zero).

@example
(format #t "~@@b" 12) @print{} +1100
@end example

If the output is less than the @var{minwidth} parameter, it's padded
on the left with the @var{padchar} parameter (default space).

@example
(format #t "~5,'*d" 12)   @print{} ***12
(format #t "~5,'0d" 12)   @print{} 00012
(format #t "~3d"    1234) @print{} 1234
@end example

The @nicode{:} modifier adds commas (or the @var{commachar} parameter)
every three digits (or the @var{commawidth} parameter many).

@example
(format #t "~:d" 1234567)         @print{} 1,234,567
(format #t "~10,'*,'/,2:d" 12345) @print{} ***1/23/45
@end example

Hexadecimal @nicode{~x} output is in lower case, but the @nicode{~(}
and @nicode{~)} case conversion directives described below can be used
to get upper case.

@example
(format #t "~x"       65261) @print{} feed
(format #t "~:@@(~x~)" 65261) @print{} FEED
@end example

@item @nicode{~r}
Integer in words, roman numerals, or a specified radix.  Parameters:
@var{radix}, @var{minwidth}, @var{padchar}, @var{commachar},
@var{commawidth}.

With no parameters output is in words as a cardinal like ``ten'', or
with the @nicode{:} modifier as an ordinal like ``tenth''.

@example
(format #t "~r" 9)  @print{} nine        ;; cardinal
(format #t "~r" -9) @print{} minus nine  ;; cardinal
(format #t "~:r" 9) @print{} ninth       ;; ordinal
@end example

And also with no parameters, the @nicode{@@} modifier gives roman
numerals and @nicode{@@} and @nicode{:} together give old roman
numerals.  In old roman numerals there's no ``subtraction'', so 9 is
@nicode{VIIII} instead of @nicode{IX}.  In both cases only positive
numbers can be output.

@example
(format #t "~@@r" 89)  @print{} LXXXIX     ;; roman
(format #t "~@@:r" 89) @print{} LXXXVIIII  ;; old roman
@end example

When a parameter is given it means numeric output in the specified
@var{radix}.  The modifiers and parameters following the radix are the
same as described for @nicode{~d} etc above.

@example
(format #f "~3r" 27)   @result{} "1000"    ;; base 3
(format #f "~3,5r" 26) @result{} "  222"   ;; base 3 width 5
@end example

@item @nicode{~f}
Fixed-point float.  Parameters: @var{width}, @var{decimals},
@var{scale}, @var{overflowchar}, @var{padchar}.

Output a number or number string in fixed-point format, ie.@: with a
decimal point.

@example
(format #t "~f" 5)      @print{} 5.0
(format #t "~f" "123")  @print{} 123.0
(format #t "~f" "1e-1") @print{} 0.1
@end example

With the @nicode{@@} modifier a @nicode{+} sign is shown on
non-negative numbers (including zero).

@example
(format #t "~@@f" 0) @print{} +0.0
@end example

If the output is less than @var{width} characters it's padded on the
left with @var{padchar} (space by default).  If the output equals or
exceeds @var{width} then there's no padding.  The default for
@var{width} is no padding.

@example
(format #f "~6f" -1.5)      @result{} "  -1.5"
(format #f "~6,,,,'*f" 23)  @result{} "**23.0"
(format #f "~6f" 1234567.0) @result{} "1234567.0"
@end example

@var{decimals} is how many digits to print after the decimal point,
the value is rounded or padded with zeros as necessary.  (The default
is to output as many decimals as required.)

@example
(format #t "~1,2f" 3.125) @print{} 3.13
(format #t "~1,2f" 1.5)   @print{} 1.50
@end example

@var{scale} is a power of 10 applied to the value, moving the decimal
point that many places.  A positive @var{scale} increases the value
shown, a negative decreases it.

@example
(format #t "~,,2f" 1234)  @print{} 123400.0
(format #t "~,,-2f" 1234) @print{} 12.34
@end example

If @var{overflowchar} and @var{width} are both given and if the output
would exceed @var{width}, then that many @var{overflowchar}s are
printed instead of the value.

@example
(format #t "~5,,,'xf" 12345) @print{} 12345
(format #t "~4,,,'xf" 12345) @print{} xxxx
@end example

@item @nicode{~e}
Exponential float.  Parameters: @var{width}, @var{mantdigits},
@var{expdigits}, @var{intdigits}, @var{overflowchar}, @var{padchar},
@var{expchar}.

Output a number or number string in exponential notation.

@example
(format #t "~e" 5000.25) @print{} 5.00025E+3
(format #t "~e" "123.4") @print{} 1.234E+2
(format #t "~e" "1e4")   @print{} 1.0E+4
@end example

With the @nicode{@@} modifier a @nicode{+} sign is shown on
non-negative numbers (including zero).  (This is for the mantissa, a
@nicode{+} or @nicode{-} sign is always shown on the exponent.)

@example
(format #t "~@@e" 5000.0) @print{} +5.0E+3
@end example

If the output is less than @var{width} characters it's padded on the
left with @var{padchar} (space by default).  The default @var{width}
is to output with no padding.

@example
(format #f "~10e" 1234.0)     @result{} "  1.234E+3"
(format #f "~10,,,,,'*e" 0.5) @result{} "****5.0E-1"
@end example

@c  FIXME: Describe what happens when the number is bigger than WIDTH.
@c  There seems to be a bit of dodginess about this, or some deviation
@c  from Common Lisp.

@var{mantdigits} is the number of digits shown in the mantissa after
the decimal point.  The value is rounded or trailing zeros are added
as necessary.  The default @var{mantdigits} is to show as much as
needed by the value.

@example
(format #f "~,3e" 11111.0) @result{} "1.111E+4"
(format #f "~,8e" 123.0)   @result{} "1.23000000E+2"
@end example

@var{expdigits} is the minimum number of digits shown for the
exponent, with leading zeros added if necessary.  The default for
@var{expdigits} is to show only as many digits as required.  At least
1 digit is always shown.

@example
(format #f "~,,1e" 1.0e99) @result{} "1.0E+99"
(format #f "~,,6e" 1.0e99) @result{} "1.0E+000099"
@end example

@var{intdigits} (default 1) is the number of digits to show before the
decimal point in the mantissa.  @var{intdigits} can be zero, in which
case the integer part is a single @nicode{0}, or it can be negative,
in which case leading zeros are shown after the decimal point.

@c  FIXME: When INTDIGITS is 0, Common Lisp format apparently only
@c  shows the single 0 digit if it fits in WIDTH.  format.scm seems to
@c  show it always.  Is it meant to?

@example
(format #t "~,,,3e" 12345.0)  @print{} 123.45E+2
(format #t "~,,,0e" 12345.0)  @print{} 0.12345E+5
(format #t "~,,,-3e" 12345.0) @print{} 0.00012345E+8
@end example

@c  FIXME: MANTDIGITS with negative INTDIGITS doesn't match CL spec,
@c  believe the spec says it ought to still show mantdigits+1 sig
@c  figures, ie. leading zeros don't count towards MANTDIGITS, but it
@c  seems to just treat MANTDIGITS as how many digits after the
@c  decimal point.

If @var{overflowchar} is given then @var{width} is a hard limit.  If
the output would exceed @var{width} then instead that many
@var{overflowchar}s are printed.

@example
(format #f "~6,,,,'xe" 100.0) @result{} "1.0E+2"
(format #f "~3,,,,'xe" 100.0) @result{} "xxx"
@end example

@var{expchar} is the exponent marker character, the default is
@nicode{E}.

@example
(format #t "~,,,,,,'ee" 100.0) @print{} 1.0e+2
@end example

@item @nicode{~g}
General float.  Parameters: @var{width}, @var{mantdigits},
@var{expdigits}, @var{intdigits}, @var{overflowchar}, @var{padchar},
@var{expchar}.

Output a number or number string in either exponential format the same
as @nicode{~e}, or fixed-point format like @nicode{~f} but aligned
where the mantissa would have been and followed by padding where the
exponent would have been.

@c  FIXME: The default MANTDIGITS is apparently max(needed,min(n,7))
@c  where 10^(n-1)<=abs(x)<=10^n.  But the Common Lisp spec seems to
@c  ask for "needed" to be without leading or trailing zeros, whereas
@c  format.scm seems to include trailing zeros, ending up with it
@c  using fixed format for bigger values than it should.

Fixed-point is used when the absolute value is 0.1 or more and it
takes no more space than the mantissa in exponential format, ie.@:
basically up to @var{mantdigits} digits.

@example
(format #f "~12,4,2g" 999.0)    @result{} "   999.0    "
(format #f "~12,4,2g" "100000") @result{} "  1.0000E+05"
@end example

The parameters are interpreted as per @nicode{~e} above.  When
fixed-point is used, the @var{decimals} parameter to @nicode{~f} is
established from @var{mantdigits}, so as to give a total
@address@hidden

@item @nicode{~$}
Monetary style fixed-point float.  Parameters: @var{decimals},
@var{intdigits}, @var{width}, @var{padchar}.

@c  For reference, fmtdoc.txi from past versions of slib showed the
@c  INTDIGITS parameter as SCALE.  That looks like a typo, in the code
@c  and in the Common Lisp spec it's a minimum digits for the integer
@c  part, it isn't a power of 10 like in ~f.

Output a number or number string in fixed-point format, ie.@: with a
decimal point.  @var{decimals} is the number of decimal places to
show, default 2.

@example
(format #t "~$" 5)       @print{} 5.00
(format #t "~4$" "2.25") @print{} 2.2500
(format #t "~4$" "1e-2") @print{} 0.0100
@end example

With the @nicode{@@} modifier a @nicode{+} sign is shown on
non-negative numbers (including zero).

@example
(format #t "~@@$" 0) @print{} +0.00
@end example

@var{intdigits} is a minimum number of digits to show in the integer
part of the value (default 1).

@example
(format #t "~,3$" 9.5)   @print{} 009.50
(format #t "~,0$" 0.125) @print{} .13
@end example

If the output is less than @var{width} characters (default 0), it's
padded on the left with @var{padchar} (default space).  With the
@nicode{:} modifier the padding is output after the sign.

@example
(format #f "~,,8$" -1.5)   @result{} "   -1.50"
(format #f "~,,8:$" -1.5)  @result{} "-   1.50"
(format #f "~,,8,'.@@:$" 3) @result{} "+...3.00"
@end example

Note that floating point for dollar amounts is generally not a good
idea, because a cent @math{0.01} cannot be represented exactly in the
binary floating point Guile uses, which leads to slowly accumulating
rounding errors.  Keeping values as cents (or fractions of a cent) in
integers then printing with the scale option in @nicode{~f} may be a
better approach.

@c  For reference, fractions don't work with ~$ (or any of the float
@c  conversions) currently.  If they did work then we could perhaps
@c  suggest keeping dollar amounts as rationals, which would of course
@c  give exact cents.  An integer as cents is probably still a better
@c  recommendation though, since it forces one to think about where
@c  and when rounding can or should occur.

@item @nicode{~i}
Complex fixed-point float.  Parameters: @var{width}, @var{decimals},
@var{scale}, @var{overflowchar}, @var{padchar}.

@c  For reference, in Common Lisp ~i is an indent, but slib fmtdoc.txi
@c  described it as complex number output, so we keep that.

Output the argument as a complex number, with both real and imaginary
part shown (even if one or both are zero).

The parameters and modifiers are the same as for fixed-point
@nicode{~f} described above.  The real and imaginary parts are both
output with the same given parameters and modifiers, except that for
the imaginary part the @nicode{@@} modifier is always enabled, so as
to print a @nicode{+} sign between the real and imaginary parts.

@example
(format #t "~i" 1)  @print{} 1.0+0.0i
@end example

@item @nicode{~p}
Plural.  No parameters.

Output nothing if the argument is 1, or @samp{s} for any other
value.

@example
(format #t "enter name~p" 1) @print{} enter name
(format #t "enter name~p" 2) @print{} enter names
@end example

With the @nicode{@@} modifier, the output is @samp{y} for 1 or
@samp{ies} otherwise.

@example
(format #t "pupp~@@p" 1) @print{} puppy
(format #t "pupp~@@p" 2) @print{} puppies
@end example

The @nicode{:} modifier means re-use the preceding argument instead of
taking a new one, which can be convenient when printing some sort of
count.

@example
(format #t "~d cat~:p" 9) @print{} 9 cats
@end example

@item @nicode{~y}
Pretty print.  No parameters.

Output an argument with @code{pretty-print} (@pxref{Pretty Printing}).

@item @nicode{~?}
@itemx @nicode{~k}
Sub-format.  No parameters.

Take a format string argument and a second argument which is a list of
arguments for it, and output the result.  With the @nicode{@@}
modifier, the arguments for the sub-format are taken directly rather
than from a list.

@example
(format #t "~?"     "~d ~d" '(1 2))    @print{} 1 2
(format #t "~@@? ~s" "~d ~d" 1 2 "foo") @print{} 1 2 "foo"
@end example

@nicode{~?} and @nicode{~k} are the same, @nicode{~k} is provided for
T-Scheme compatibility.

@item @nicode{~*}
Argument jumping.  Parameter: @var{N}.

Move forward @var{N} arguments (default 1) in the argument list.  With
the @nicode{:} modifier move backwards.  @var{N} can be negative to
move backwards too.

@example
(format #f "~d ~:*~d" 6) @result{} "6 6"
@end example

With the @nicode{@@} modifier, move to argument number @var{N}, with
the first argument being number 0 (the default for @var{N}).

@example
(format #f "~d~d again ~@@*~d~d" 1 2) @result{} "12 again 12"
(format #f "~d~d~d ~1@@*~d~d" 1 2 3)  @result{} "123 23"
@end example

At the end of the format string the last argument must have been
consumed, or a ``too many arguments'' error results.  If the last
argument is not the last to be printed, then a move to skip the
remaining must be given.  This can be done with the @nicode{#}
parameter (count of remaining arguments).

@example
(format #t "~2*~d"    1 2 3 4)  ;; error
(format #t "~2*~d~#*" 1 2 3 4)  @result{} 3
@end example

A @nicode{#} move to the end followed by a @nicode{:} modifier move
back can be used for an absolute position relative to the end of the
argument list, a reverse of what the @nicode{@@} modifier does.

@item @nicode{~t}
Advance to a column position.  Parameters: @var{colnum}, @var{colinc},
@var{padchar}.

Output @var{padchar} (space by default) to move to the given
@var{colnum} column.  The start of the line is column 0, the default
for @var{colnum} is 1.

@example
(format #f "~tX")  @result{} " X"
(format #f "~3tX") @result{} "   X"
@end example

If the current column is already past @var{colnum}, then the move is
to there plus a multiple of @var{colinc}, ie.@: column
@address@hidden + @var{N} * @var{colinc}} for the smallest @var{N}
which makes that value greater than or equal to the current column.
The default @var{colinc} is 1 (which means no further move).

@example
(format #f "abcd~2,5,'.tx") @result{} "abcd...x"
@end example

With the @nicode{@@} modifier, @var{colnum} is relative to the current
column.  @var{colnum} many padding characters are output, then further
padding to make the current column a multiple of @var{colinc}, if it
isn't already so.

@example
(format #f "a~3,5'*@@tx") @result{} "a****x"
@end example

@item @nicode{~~}
Tilde character.  Parameter: @var{n}.

Output a tilde character @nicode{~}, or @var{n} many if a parameter is
given.  Normally @nicode{~} introduces an escape sequence, @nicode{~~}
is the way to output a literal tilde.

@item @nicode{~%}
Newline.  Parameter: @var{n}.

Output a newline character, or @var{n} many if a parameter is given.
A newline (or a few newlines) can of course be output just by
including them in the format string.

@item @nicode{~&}
Start a new line.  Parameter: @var{n}.

Output a newline if not already at the start of a line.  With a
parameter, output that many newlines, but with the first only if not
already at the start of a line.  So for instance 3 would be a newline
if not already at the start of a line, and 2 further newlines.

@item @nicode{~_}
Space character.  Parameter: @var{n}.

@c  For reference, in Common Lisp ~_ is a conditional newline, but
@c  slib fmtdoc.txi described it as a space, so we keep that.

Output a space character, or @var{n} many if a parameter is given.

With a variable parameter this is one way to insert runtime calculated
padding (@nicode{~t} or the various field widths can do similar
things).

@example
(format #f "~v_foo" 4) @result{} "    foo"
@end example

@item @nicode{~/}
Tab character.  Parameter: @var{n}.

Output a tab character, or @var{n} many if a parameter is given.

@item @nicode{~|}
Formfeed character.  Parameter: @var{n}.

Output a formfeed character, or @var{n} many if a parameter is given.

@item @nicode{~!}
Force output.  No parameters.

At the end of output, call @code{force-output} to flush any buffers on
the destination (@pxref{Writing}).  @nicode{~!} can occur anywhere in
the format string, but the force is done at the end of output.

When output is to a string (destination @code{#f}), @nicode{~!} does
nothing.

@item @nicode{~newline}  (ie.@: newline character)
Continuation line.  No parameters.

Skip this newline and any following whitespace in the format string,
don't send it to the output.  With the @nicode{:} modifier the newline
is not output but any further following whitespace is.  With the
@nicode{@@} modifier the newline is output but not any following
whitespace.

This escape can be used to break up a long format string into multiple
lines for readability, but supress that extra whitespace.

@example
(format #f "abc~
            ~d def~
            ~d" 1 2) @result{} "abc1 def2"
@end example

@item @nicode{~(} @nicode{~)}
Case conversion.  Between @nicode{~(} and @nicode{~)} the case of all
output is changed.  The modifiers on @nicode{~(} control the
conversion.

@itemize @w
@item
no modifiers --- lower case.
@c
@c  FIXME: The : and @ modifiers are not yet documented because the
@c  code applies string-capitalize and string-capitalize-first to each
@c  separate format:out-str call, which has various subtly doubtful
@c  effects.  And worse they're applied to individual characters,
@c  including literal characters in the format string, which has the
@c  silly effect of being always an upcase.
@c
@c  The Common Lisp spec is apparently for the capitalization to be
@c  applied in one hit to the whole of the output between ~( and ~).
@c  (This can no doubt be implemented without accumulating all that
@c  text, just by keeping a state or the previous char to tell whether
@c  within a word.)
@c
@c  @item
@c  @nicode{:} --- first letter of each word upper case, the rest lower
@c  case, as per the @code{string-capitalize} function (@pxref{Alphabetic
@c  Case Mapping}).
@c  @item
@c  @nicode{@@} --- first letter of just the first word upper case, the
@c  rest lower case.
@c
@item
@nicode{:} and @nicode{@@} together --- upper case.
@end itemize

For example,

@example
(format #t "~(Hello~)")   @print{} hello
(format #t "~@@:(Hello~)") @print{} HELLO
@end example

In the future it's intended the modifiers @nicode{:} and @nicode{@@}
alone will capitalize the first letters of words, as per Common Lisp
@code{format}, but the current implementation of this is flawed and
not recommended for use.

Case conversions do not nest, currently.  This might change in the
future, but if it does then it will be to Common Lisp style where the
outermost conversion has priority, overriding inner ones (and making
those fairly pointless).

@item @nicodeiterationbegin{} @nicodeiterationend{}
Iteration.  Parameter: @var{maxreps} (for @nicodeiterationbegin{}).

The format between @nicodeiterationbegin{} and @nicodeiterationend{}
is iterated.  The modifiers to @nicodeiterationbegin{} determine how
arguments are taken.  The default is a list argument with each
iteration successively consuming elements from it.  This is a
convenient way to output a whole list.

@example
(format #t "address@hidden@}"     '(1 2 3))       @print{} 123
(format #t "address@hidden address@hidden" '("x" 1 "y" 2)) @print{} "x"=1 "y"=2
@end example

With the @nicode{:} modifier a list of lists argument is taken, each
of those lists gives the arguments for the iterated format.

@example
(format #t "~:@{~dx~d address@hidden" '((1 2) (3 4) (5 6))) @print{} 1x2 3x4 5x6
@end example

With the @nicode{@@} modifier, the remaining arguments are used, each
iteration successively consuming elements.

@example
(format #t "~@@@address@hidden"     1 2 3)       @print{} 123
(format #t "~@@@{~s=~d address@hidden" "x" 1 "y" 2) @print{} "x"=1 "y"=2
@end example

With both @nicode{:} and @nicode{@@} modifiers, the remaining
arguments are used, each is a list of arguments for the format.

@example
(format #t "~:@@@{~dx~d address@hidden" '(1 2) '(3 4) '(5 6)) @print{} 1x2 3x4 
5x6
@end example

Iteration stops when there are no more arguments or when the
@var{maxreps} parameter to @nicodeiterationbegin{} is reached (default
no maximum).

@example
(format #t "address@hidden@}" '(1 2 3 4)) @print{} 12
@end example

If the format between @nicodeiterationbegin{} and
@nicodeiterationend{} is empty, then a format string argument is taken
(before iteration argument(s)) and used instead.  This allows a
sub-format (like @nicode{~?} above) to be iterated.

@example
(format #t "address@hidden@}" "~d" '(1 2 3)) @print{} 123
@end example

@c  FIXME: What is the @nicode{:} modifier to ~} meant to do?  The
@c  Common Lisp spec says it's a minimum of 1 iteration, but the
@c  format.scm code seems to merely make it have MAXREPS default to 1.

Iterations can be nested, an inner iteration operates in the same way
as described, but of course on the arguments the outer iteration
provides it.  This can be used to work into nested list structures.
For example in the following the inner @address@hidden@}x} is applied
to @code{(1 2)} then @code{(3 4 5)} etc.

@example
(format #t "address@hidden@address@hidden@}" '((1 2) (3 4 5))) @print{} 12x345x
@end example

@item @nicode{~[} @nicode{~;} @nicode{~]}
Conditional.  Parameter: @var{selector}.

A conditional block is delimited by @nicode{~[} and @nicode{~]}, and
@nicode{~;} separates clauses within the block.  @nicode{~[} takes an
integer argument and that number clause is used.  The first clause is
number 0.

@example
(format #f "~[peach~;banana~;mango~]" 1)  @result{} "banana"
@end example

The @var{selector} parameter can be used for the clause number,
instead of taking an argument.

@example
(format #f "~2[peach~;banana~;mango~]") @result{} "mango"
@end example

If the clause number is out of range then nothing is output.  Or if
the last @nicode{~;} has the @nicode{:} modifier it's the default for
a number out of range.

@example
(format #f "~[banana~;mango~]"         99) @result{} ""
(format #f "~[banana~;mango~:;fruit~]" 99) @result{} "fruit"
@end example

The @nicode{:} modifier to @nicode{~[} treats the argument as a flag,
and expects two clauses.  The first used if the argument is @code{#f}
or the second otherwise.

@example
(format #f "~:[false~;not false~]" #f)   @result{} "false"
(format #f "~:[false~;not false~]" 'abc) @result{} "not false"

(let ((n 3))
  (format #t "~d gnu~:[s are~; is~] here" n (= 1 n)))
@print{} 3 gnus are here
@end example

The @nicode{@@} modifier to @nicode{~[} also treats the argument as a
flag, and expects one clause.  If the argument is @code{#f} then no
output is produced and the argument is consumed, otherwise the clause
is used and the argument is not consumed by @nicode{~[}, it's left for
the clause.  This can be used for instance to suppress output if
@code{#f} means something not available.

@example
(format #f "~@@[temperature=~d~]" 27) @result{} "temperature=27"
(format #f "~@@[temperature=~d~]" #f) @result{} ""
@end example

@item @nicode{~^}
Escape.  Parameters: @var{val1}, @var{val2}, @var{val3}.

Stop formatting if there are no more arguments.  This can be used for
instance to let a format string adapt to a variable number of
arguments.

@example
(format #t "~d~^ ~d" 1)   @print{} 1
(format #t "~d~^ ~d" 1 2) @print{} 1 2
@end example

Within a @nicodeiterationbegin{} @nicodeiterationend{} iteration,
@nicode{~^} stops the current iteration step if there are no more
arguments to that step, continuing with possible further steps (in the
case of the @nicode{:} modifier to @nicodeiterationbegin{}) and the
rest of the format.

@example
(format #f "address@hidden/address@hidden go"    '(1 2 3))     @result{} "1/2/3 
go"
(format #f "~:@{ address@hidden go" '((1) (2 3))) @result{} " 1 23 go"
@end example

@c  For reference, format.scm doesn't implement that Common Lisp ~:^
@c  modifier which stops the entire iterating of ~:{ or ~@:{.

@c  FIXME: Believe the Common Lisp spec is for ~^ within ~[ ~]
@c  conditional to terminate the whole format (or iteration step if in
@c  an iteration).  But format.scm seems to terminate just the
@c  conditional form.
@c
@c      (format #f "~[abc~^def~;ghi~] blah" 0)
@c      @result{} "abc blah"                    ;; looks wrong

@c  FIXME: Believe the Common Lisp spec is for ~^ within ~( ~) to end
@c  that case conversion and then also terminate the whole format (or
@c  iteration step if in an iteration).  But format.scm doesn't seem
@c  to do that quite right.
@c
@c      (format #f "~d ~^ ~d" 1)      @result{} "1 "
@c      (format #f "~(~d ~^ ~d~)" 1)  @result{} ERROR

Within a @nicode{~?} or @nicode{~k} sub-format, @nicode{~^} operates
just within that sub-format.  If it terminates the sub-format then the
originating format will still continue.

@example
(format #t "~? items" "~d~^ ~d" '(1))   @print{} 1 items
(format #t "~? items" "~d~^ ~d" '(1 2)) @print{} 1 2 items
@end example

The parameters to @nicode{~^} (which are numbers) change the condition
used to terminate.  For a single parameter, termination is when that
value is zero (notice this makes plain @nicode{~^} equivalent to
@nicode{~#^}).  For two parameters, termination is when those two are
equal.  For three parameters, termination is when @address@hidden
@le{} @var{val2}} and @address@hidden @le{} @var{val3}}.

@c  FIXME: Good examples of these?

@item @nicode{~q}
Inquiry message.  Insert a copyright message into the output.  With
the @nicode{:} modifier insert the format implementation version.
@end table

@sp 1
It's an error if there are too many or not enough arguments for the
escapes in the format string.  (Unwanted arguments can be skipped with
an argument jump @nicode{~#*} described above if desired.)

Iterations @nicodeiterationbegin{} @nicodeiterationend{} and
conditionals @nicode{~[} @nicode{~;} @nicode{~]} can be nested, but
must be properly nested, meaning the inner form must be entirely
within the outer form.  So it's not possible, for instance, to try to
conditionalize the endpoint of an iteration.

@example
(format #t "address@hidden ~[ ... ~] address@hidden" ...)       ;; good
(format #t "address@hidden ~[ ... address@hidden ... ~]" ...)   ;; bad
@end example

The same applies to case conversions @nicode{~(} @nicode{~)}, they
must properly nest with respect to iterations and conditionals (though
currently a case conversion cannot nest within another case
conversion).

When a sub-format (@nicode{~?}) is used, that sub-format string must
be self-contained.  It cannot for instance give a
@nicodeiterationbegin{} to begin an iteration form and have the
@nicodeiterationend{} up in the originating format, or similar.
@end deffn

@sp 1
Guile contains a @code{format} procedure even when the module
@code{(ice-9 format)} is not loaded.  The default @code{format} is
@code{simple-format} (@pxref{Writing}), it doesn't support all escape
sequences documented in this section, and will signal an error if you
try to use one of them.  The reason for two versions is that the full
@code{format} is fairly large and requires some time to load.
@code{simple-format} is often adequate too.




reply via email to

[Prev in Thread] Current Thread [Next in Thread]