Copyright | (c) Lennart Augustsson and Bart Massey 2013 |
---|---|
License | BSD-style (see the file LICENSE in this distribution) |
Maintainer | Bart Massey <bart@cs.pdx.edu> |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
A C printf(3)
-like formatter. This version has been
extended by Bart Massey as per the recommendations of
John Meacham and Simon Marlow
<http://comments.gmane.org/gmane.comp.lang.haskell.libraries/4726>
to support extensible formatting for new datatypes. It
has also been extended to support almost all C
printf(3)
syntax.
- printf :: PrintfType r => String -> r
- hPrintf :: HPrintfType r => Handle -> String -> r
- class PrintfArg a where
- formatArg :: a -> FieldFormatter
- parseFormat :: a -> ModifierParser
- type FieldFormatter = FieldFormat -> ShowS
- data FieldFormat = FieldFormat {}
- data FormatAdjustment
- data FormatSign
- vFmt :: Char -> FieldFormat -> FieldFormat
- type ModifierParser = String -> FormatParse
- data FormatParse = FormatParse {}
- formatString :: IsChar a => [a] -> FieldFormatter
- formatChar :: Char -> FieldFormatter
- formatInt :: (Integral a, Bounded a) => a -> FieldFormatter
- formatInteger :: Integer -> FieldFormatter
- formatRealFloat :: RealFloat a => a -> FieldFormatter
- errorBadFormat :: Char -> a
- errorShortFormat :: a
- errorMissingArgument :: a
- errorBadArgument :: a
- perror :: String -> a
- class PrintfType t
- class HPrintfType t
- class IsChar c where
Printing Functions
printf :: PrintfType r => String -> r Source
Format a variable number of arguments with the C-style formatting string.
The return value is either String
or (
(which
should be IO
a)(
, but Haskell's type system
makes this hard).IO
'()')
The format string consists of ordinary characters and
conversion specifications, which specify how to format
one of the arguments to printf
in the output string. A
format specification is introduced by the %
character;
this character can be self-escaped into the format string
using %%
. A format specification ends with a /format
character/ that provides the primary information about
how to format the value. The rest of the conversion
specification is optional. In order, one may have flag
characters, a width specifier, a precision specifier, and
type-specific modifier characters.
Unlike C printf(3)
, the formatting of this printf
is driven by the argument type; formatting is type specific. The
types formatted by printf
"out of the box" are:
printf
is also extensible to support other types: see below.
A conversion specification begins with the
character %
, followed by zero or more of the following flags:
- left adjust (default is right adjust) + always use a sign (+ or -) for signed conversions space leading space for positive numbers in signed conversions 0 pad with zeros rather than spaces # use an \"alternate form\": see below
When both flags are given, -
overrides 0
and +
overrides space.
A negative width specifier in a *
conversion is treated as
positive but implies the left adjust flag.
The "alternate form" for unsigned radix conversions is
as in C printf(3)
:
%o prefix with a leading 0 if needed %x prefix with a leading 0x if nonzero %X prefix with a leading 0X if nonzero %b prefix with a leading 0b if nonzero %[eEfFgG] ensure that the number contains a decimal point
Any flags are followed optionally by a field width:
num field width * as num, but taken from argument list
The field width is a minimum, not a maximum: it will be expanded as needed to avoid mutilating a value.
Any field width is followed optionally by a precision:
.num precision . same as .0 .* as num, but taken from argument list
Negative precision is taken as 0. The meaning of the precision depends on the conversion type.
Integral minimum number of digits to show RealFloat number of digits after the decimal point String maximum number of characters
The precision for Integral types is accomplished by zero-padding. If both precision and zero-pad are given for an Integral field, the zero-pad is ignored.
Any precision is followed optionally for Integral types by a width modifier; the only use of this modifier being to set the implicit size of the operand for conversion of a negative operand to unsigned:
hh Int8 h Int16 l Int32 ll Int64 L Int64
The specification ends with a format character:
c character Integral d decimal Integral o octal Integral x hexadecimal Integral X hexadecimal Integral b binary Integral u unsigned decimal Integral f floating point RealFloat F floating point RealFloat g general format float RealFloat G general format float RealFloat e exponent format float RealFloat E exponent format float RealFloat s string String v default format any type
The "%v" specifier is provided for all built-in types, and should be provided for user-defined type formatters as well. It picks a "best" representation for the given type. For the built-in types the "%v" specifier is converted as follows:
c Char u other unsigned Integral d other signed Integral g RealFloat s String
Mismatch between the argument types and the format string, as well as any other syntactic or semantic errors in the format string, will cause an exception to be thrown at runtime.
Note that the formatting for RealFloat
types is
currently a bit different from that of C printf(3)
,
conforming instead to showEFloat
,
showFFloat
and showGFloat
(and their
alternate versions showFFloatAlt
and
showGFloatAlt
). This is hard to fix: the fixed
versions would format in a backward-incompatible way.
In any case the Haskell behavior is generally more
sensible than the C behavior. A brief summary of some
key differences:
- Haskell
printf
never uses the default "6-digit" precision used by C printf. - Haskell
printf
treats the "precision" specifier as indicating the number of digits after the decimal point. - Haskell
printf
prints the exponent of e-format numbers without a gratuitous plus sign, and with the minimum possible number of digits. - Haskell
printf
will place a zero after a decimal point when possible.
Examples:
> printf "%d\n" (23::Int) 23 > printf "%s %s\n" "Hello" "World" Hello World > printf "%.2f\n" pi 3.14
hPrintf :: HPrintfType r => Handle -> String -> r Source
Extending To New Types
This printf
can be extended to format types
other than those provided for by default. This
is done by instancing PrintfArg
and providing
a formatArg
for the type. It is possible to
provide a parseFormat
to process type-specific
modifiers, but the default instance is usually
the best choice.
For example:
instance PrintfArg () where formatArg x fmt | fmtChar (vFmt 'U' fmt) == 'U' = formatString "()" (fmt { fmtChar = 's', fmtPrecision = Nothing }) formatArg _ fmt = errorBadFormat $ fmtChar fmt main :: IO () main = printf "[%-3.1U]\n" ()
prints "[() ]
". Note the use of formatString
to
take care of field formatting specifications in a convenient
way.
class PrintfArg a where Source
Typeclass of printf
-formattable values. The formatArg
method
takes a value and a field format descriptor and either fails due
to a bad descriptor or produces a ShowS
as the result. The
default parseFormat
expects no modifiers: this is the normal
case. Minimal instance: formatArg
.
formatArg :: a -> FieldFormatter Source
Since: 4.7.0.0
parseFormat :: a -> ModifierParser Source
Since: 4.7.0.0
type FieldFormatter = FieldFormat -> ShowS Source
This is the type of a field formatter reified over its argument.
Since: 4.7.0.0
data FieldFormat Source
Description of field formatting for formatArg
. See UNIX printf
(3)
for a description of how field formatting works.
Since: 4.7.0.0
FieldFormat | |
|
data FormatAdjustment Source
Whether to left-adjust or zero-pad a field. These are
mutually exclusive, with LeftAdjust
taking precedence.
Since: 4.7.0.0
data FormatSign Source
How to handle the sign of a numeric field. These are
mutually exclusive, with SignPlus
taking precedence.
Since: 4.7.0.0
vFmt :: Char -> FieldFormat -> FieldFormat Source
Substitute a 'v' format character with the given
default format character in the FieldFormat
. A
convenience for user-implemented types, which should
support "%v".
Since: 4.7.0.0
Handling Type-specific Modifiers
In the unlikely case that modifier characters of
some kind are desirable for a user-provided type,
a ModifierParser
can be provided to process these
characters. The resulting modifiers will appear in
the FieldFormat
for use by the type-specific formatter.
type ModifierParser = String -> FormatParse Source
Type of a function that will parse modifier characters from the format string.
Since: 4.7.0.0
data FormatParse Source
The "format parser" walks over argument-type-specific modifier characters to find the primary format character. This is the type of its result.
Since: 4.7.0.0
Standard Formatters
These formatters for standard types are provided for
convenience in writting new type-specific formatters:
a common pattern is to throw to formatString
or
formatInteger
to do most of the format handling for
a new type.
formatString :: IsChar a => [a] -> FieldFormatter Source
Formatter for String
values.
Since: 4.7.0.0
formatChar :: Char -> FieldFormatter Source
Formatter for Char
values.
Since: 4.7.0.0
formatInt :: (Integral a, Bounded a) => a -> FieldFormatter Source
Formatter for Int
values.
Since: 4.7.0.0
formatInteger :: Integer -> FieldFormatter Source
Formatter for Integer
values.
Since: 4.7.0.0
formatRealFloat :: RealFloat a => a -> FieldFormatter Source
Formatter for RealFloat
values.
Since: 4.7.0.0
Raising Errors
These functions are used internally to raise various errors, and are exported for use by new type-specific formatters.
errorBadFormat :: Char -> a Source
Calls perror
to indicate an unknown format letter for
a given type.
Since: 4.7.0.0
errorShortFormat :: a Source
Calls perror
to indicate that the format string ended
early.
Since: 4.7.0.0
errorMissingArgument :: a Source
Calls perror
to indicate that there is a missing
argument in the argument list.
Since: 4.7.0.0
errorBadArgument :: a Source
Calls perror
to indicate that there is a type
error or similar in the given argument.
Since: 4.7.0.0
Raises an error
with a printf-specific prefix on the
message string.
Since: 4.7.0.0
Implementation Internals
These types are needed for implementing processing
variable numbers of arguments to printf
and hPrintf
.
Their implementation is intentionally not visible from
this module. If you attempt to pass an argument of a type
which is not an instance of the appropriate class to
printf
or hPrintf
, then the compiler will report it
as a missing instance of PrintfArg
. (All PrintfArg
instances are PrintfType
instances.)
class PrintfType t Source
The PrintfType
class provides the variable argument magic for
printf
. Its implementation is intentionally not visible from
this module. If you attempt to pass an argument of a type which
is not an instance of this class to printf
or hPrintf
, then
the compiler will report it as a missing instance of PrintfArg
.
spr
IsChar c => PrintfType [c] | |
(~) * a () => PrintfType (IO a) | |
(PrintfArg a, PrintfType r) => PrintfType (a -> r) |
class HPrintfType t Source
The HPrintfType
class provides the variable argument magic for
hPrintf
. Its implementation is intentionally not visible from
this module.
hspr
(~) * a () => HPrintfType (IO a) | |
(PrintfArg a, HPrintfType r) => HPrintfType (a -> r) |
This class is needed as a Haskell98 compatibility workaround for the lack of FlexibleInstances.