| Copyright | (c) 2019 Version Cloud |
|---|---|
| License | BSD3 |
| Maintainer | Jorah Gao <jorah@version.cloud> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Text.Format
Description
- Printf is more ligth-weight
Printf is more effective in basic formatting, e.g.:
printf "%s %d %f" "hello" 123 456.789 format "{:s} {:d} {:f}" "hello" 123 456.789Format is more effective in complex formatting, e.g.:
printf "%30s %30d %30f" "hello" 123 456.789 format "{:>30s} {:>30d} {:>30f}" "hello" 123 456.789Printf can only consume args in order, e.g.:
printf "%s %d %f" "hello" 123 456.789 format "{2:s} {1:d} {0:f}" 456.789 123 "hello"Printf can only consume position args, e.g.:
printf "%s %d %f" "hello" 123 456.789 format "{hello:s} {int:d} {float:f}" ("hello" := "hello") ("int" := 123) ("float" := 456.789)Format is easier to implement for a new type, e.g.:
instance FormatArg UTCTime where formatArg x _ fmt = formatTime defaultTimeLocale (fmtSpecs fmt) x format "{:%Y-%m-%d}" $ read "2019-01-01" :: UTCTimedata Student = Student { name :: String , age :: Int , email :: String } deriving Generic instance FormatArg Student format "{0!name:<20s} {0!age:<10d} {0!email:<20s}" $ Student "Jorah Gao" 27 "jorah@version.cloud"
Synopsis
- format :: FormatType r => Format -> r
- format1 :: FormatArg a => Format1 -> a -> String
- type Formatter = ArgKey -> ArgFmt -> String
- class FormatArg a where
- class FormatType t where
- data FmtItem
- newtype Format = Format {}
- newtype Format1 = Format1 {}
- data ArgKey
- data FmtAlign
- data FmtSign
- data FmtNumSep
- data ArgFmt = ArgFmt {}
- formatText :: ArgFmt -> ShowS
- formatNumber :: ArgFmt -> Bool -> Int -> Maybe Char -> ShowS
- data (:=) a = String := a
- ferror :: String -> a
- errorArgFmt :: String -> a
- errorCloseTag :: a
- errorTypeFmt :: String -> String -> a
- errorMissingArg :: a
Documentation
format :: FormatType r => Format -> r Source #
Format a variable number of argument with Python-style formatting string
>>>format "hello {} {}" "world" "!" :: Stringhello world !>>>format "hello {1} {0}" "!" "world" :: Stringhello world !>>>format "hello {to} {bang}" ("to" := "world") ("bang" := "!")hello world !
format1 :: FormatArg a => Format1 -> a -> String Source #
Format argument with Python-style formatting string
>>>:set -XDeriveGeneric>>>data Greeting = Greeting {to :: String, bang :: String} deriving Generic>>>instance FormatArg Greeting>>>format1 "hello {to} {bang}" (Greeting "world" "!")hello world !>>>format "hello {0!to} {0!bang}" (Greeting "world" "!")hello world !
class FormatArg a where Source #
Typeclass of formatable values.
Make an instance for your own data types:
data Coffe = Black | Latte | Other deriving Show instance FormatArg Coffe where formatArg x k fmt = formatArg (show x) k fmt
newtype Big a = Big { unBig :: a}
instance FormatArg a => FormatArg (Big a) where
formatArg (Big x) k fmt = formatArg x k fmt
data Student = Student { name :: String
, age :: Int
, email :: String
} deriving Generic
instance FormatArg Student
data Address = Address { country :: String
, city :: String
, street :: String
}
instance FormatArg Address where
formatArg x k fmt = formatArg result k fmt
where
result :: String
result = format "{:s},{:s},{:s}" (street x) (city x) (country x)
Minimal complete definition
Nothing
Methods
formatArg :: a -> Formatter Source #
formatArg :: (Generic a, GFormatArg (Rep a)) => a -> Formatter Source #
Instances
| FormatArg Char Source # | |
| FormatArg Double Source # | |
| FormatArg Float Source # | |
| FormatArg Int Source # | |
| FormatArg Int8 Source # | |
| FormatArg Int16 Source # | |
| FormatArg Int32 Source # | |
| FormatArg Int64 Source # | |
| FormatArg Integer Source # | |
| FormatArg Natural Source # | |
| FormatArg Word Source # | |
| FormatArg Word8 Source # | |
| FormatArg Word16 Source # | |
| FormatArg Word32 Source # | |
| FormatArg Word64 Source # | |
| FormatTime t => FormatArg t Source # | |
| FormatArg String Source # | |
| FormatArg a => FormatArg [a] Source # | |
| FormatArg a => FormatArg ((:=) a) Source # | |
| FormatArg a => FormatArg (Map Int a) Source # | |
| FormatArg a => FormatArg (Map String a) Source # | |
class FormatType t where Source #
A typeclass provides the variable arguments magic for format
Format is a list of FmtItem
A format contains a variet of literal chars and arguments to be replaced, argument sytax is as follows:
{[key][:fmt]}- {} means it must be wraped in a pair of braces,
- [] means an optional field (or field group),
- key is argument's key, see
ArgKey, - fmt (must leading with a colon) is argument's format, see
ArgFmt.
If you need to include a brace character in the literal text, it can be escaped by doubling: {{ and }}.
if key is ommited, it means an automically positioned argument.
Examples:
>>>unFormat "a left brace {{"[Lit "a left brace {"]
>>>unFormat "hello {}"[Lit "hello ", Arg (Index 0) (ArgFmt ...)]
>>>unFormat "{} {}"[Arg (Index 0) (ArgFmt ...), Arg (Index 1) (ArgFmt ...)]
>>>unFormat "{1} {0}"[Arg (Index 1) (ArgFmt ...), Arg (Index 0) (ArgFmt ...)]
>>>unFormat "{gender} {age}"[Arg (Name "gender") (ArgFmt ...), Arg (Name "age") (ArgFmt ...)]
>>>unFormat "{0!gender}"[Arg (Nest (Index 0) (Name "gender")) (ArgFmt ..)]
>>>unFormat "{:<30s}"[Arg (Index 0) (ArgFmt { fmtAlgin = AlignLeft, fmtWidth = Left 30, ...})]
>>>unFormat "{:<{width}s}"[Arg (Index 0) (ArgFmt {fmtWidth = Right (Name "width"), ...})]
A variant of Format,
it transforms all argument's key to Nest (Index 0) key
ArgKey indicates a key of format argument
There are two kinds of basic key, named and indexed, and a composed key indicates a key which is a attribute of an argument.
When read from a String, the sytax is as followings:
- if all chars are digits, it means an indexed key,
- if there is a "!", it means a nested key, the chars before "!" is parent key, and the chars after are child key,
- if you want to use literal "!" in the key, you can write it doublely, "!!",
- if there are not all digits, it's a named key.
Examples:
>>>read "country" :: ArgKeyName "country"
>>>read "123" :: ArgKeyIndex 123
>>>read "country!name" :: ArgKeyNest (Name "country") (Name "name")
>>>read "country!cities!10" :: ArgKeyNest (Name "country") (Nest (Name "cities") (Index 10))
>>>read "coun!!try" :: ArgKeyName "coun!try"
Constructors
| AlignNone | alignment is not specified |
| AlignLeft | pad chars before argument |
| AlignRight | pad chars before argument |
| AlignCenter | pad chars before and after argument |
| AlignSign | number specified, pad between sign and digits |
Number separator
Constructors
| NumSepNone | don't seprate |
| NumSepDash | seprate by '_' |
| NumSepComma | seprate by ',' |
Description of argument format options
When read from string, the sytax is as follows:
[[pad]align][sign][#][0][width][separator][.precision][specs]
- [] means an optional field (or filed group)
- pad means char to be used for padding, it should be a literal
Char, default is space - align means align option
< AlignLeft
> AlignRight
^ AlignCenter
= AlignSign
empty AlignNone
- sign means number sign option
+ SignPlus
- SignMinus
space SignSpace
empty SignNone
- # means number alternate form option
- 0 preceding width option means sign-aware as well as zero-padding
number AlignNone & sign aware = AlignSign & pad '0'
other types means nothing
- width means minimum argument width,
it may be an
ArgKeyindicates it's value from another integer argument
integer minimum width
empty no minimum widht constrain
- separator number separator option
_ NumSepDash
, NumSepComma
empty NumSepNone
- precision (must leading with a dot)
number preceding or maximum with option
it may be an
ArgKeyindicates it's value from another integer argument
for number (floating point) types number precision
for non-number types maximum widht
- specs type specified options, it determines how data should be presented, see available type presentions below
String presentions
s explicitly specified string type empty implicitly specified string type
Integer presentions
b binary format integer c char point (Charwill be trasformed byordfirst) d decimal format integer o octal format integer x hex format integer (use lower-case letters) X hex format integer (use upper-case letters) empty same as "d"
Floating point number presentions
e exponent notation, seeshowEFloatE same as "e", but use upper-caseEas separator f fixed-point notation seeshowFFloatF same as "f", but converts nan to NAN and inf to INF g general format, seeshowGFloatG same as "g", but use upper-caseEas separator and converts nan to NAN and inf to INF % percentage, same as "f" except multiplies 100 first and followed by a percent sign empty same as "g"
Examples
>>>read "*<30s" :: ArgFmt>>>read "<10.20s" :: ArgFmt>>>read "0=10_.20d" :: ArgFmt>>>read "#010_.20b" :: ArgFmt
Constructors
| ArgFmt | |
formatText :: ArgFmt -> ShowS Source #
A type represent a named ArgKey and an another data
errorArgFmt :: String -> a Source #
errorCloseTag :: a Source #
errorTypeFmt :: String -> String -> a Source #
errorMissingArg :: a Source #