format package:vformat

Format a variable number of arguments with Python-style format string
>>> format "{:s}, {:d}, {:.4f}" "hello" 123 pi
"hello, 123, 3.1416"

>>> format "{1:s}, {0:d}, {2:.4f}" 123 "hello" pi
"hello, 123, 3.1416"

>>> format "{:s} {:d} {pi:.4f}" "hello" 123 ("pi" := pi)
"hello, 123, 3.1416"
See Format to learn more about format string syntax. See FormatArg to learn how to derive FormatArg for your own data types.
This library is inspired by Python's str.format and Haskell's Text.Printf, and most of the features are copied from these two libraries.
A data type indicates a format string Format string contains "replacement fields" surrounded by curly braces {}. Anything that is not contained in braces is considered literal text, which is copied unchanged to the output. If you need to include a brace character in the literal text, it can be escaped by doubling {{ and }}.

Format string syntax

format -> {chars | ("{" [key][":"fmt] "}")}
key    -> <see ArgKey>
fmt    -> <see ArgFmt>

Note: This library use a description language to describe syntax, see next section. Note: A key can be omitted only if there is no explict index key before it, it will be automatically caculated and inserted to the format string according to its position in the omitted key sequence. Examples
>>> "I like {coffee}, I drink it everyday." :: Format

>>> "{no:<20}    {name:<20}    {age}" :: Format

>>> "{{\"no\": {no}, \"name\": \"{name}\"}}" :: Format

Syntax description language

A syntax expr may contain a list of fields as followings
identifier                       identifier of an expr
<description>                    use natural language as an expr
->                               use right hand expr to describe identifier
()                               a required field, may be omitted
[]                               an optional field
{}                               repeat any times of the field
|                                logical or, choice between left and right
""                               literal text

Built-in exprs
char  -> <any character>
chars -> {char}
int   -> <integer without sign>

A variant of format, it takes only one positional argument
>>> :set -XDeriveGeneric

>>> import GHC.Generics

>>> data Triple = Triple String Int Double deriving Generic

>>> instance FormatArg Triple

>>> format "{0!0:s} {0!1:d} {0!2:.4f}" $ Triple "hello" 123 pi
"hello, 123, 3.1416"

>>> format1 "{0:s} {1:d} {2:.4f}" $ Triple "hello" 123 pi
"hello, 123, 3.1416"
Formatter for Char values
Formatter for Int values
Formatter for Integer values
Formatter for RealFloat values
Formatter for string values
Formatter for Word values
Same as formatQQ, but for Format1.
A QuasiQuoter for Format with which you can write multi-line Format. Note: ">>>" after "[formatQQ|" means starting from the next line, "<<<" before "|]" means ending from the previous line.

Example

>>> :set -XTemplateHaskell

>>> :set -XQuasiQuotes

>>> import     Text.Format

>>> import     Text.Format.TH

>>> :{
fmt1 :: Format
fmt1 = [formatQQ|>>>
first line {hi}
newline {words}
last line {bye}
<<<|]
fmt2 :: Format
fmt2 = [formatQQ|first line {hi}
newline {words}
last line {bye}|]
fmt3 :: Format
fmt3 = "first line {hi}\nnewline {words}\nlast line {bye}"
:}

>>> format fmt1 ("hi" := "hi") ("words"  := "say something") ("bye" := "bye")
"first line hi\nnewline say something\nlast line bye"

>>> format fmt2 ("hi" := "hi") ("words"  := "say something") ("bye" := "bye")
"first line hi\nnewline say something\nlast line bye"

>>> format fmt3 ("hi" := "hi") ("words"  := "say something") ("bye" := "bye")
"first line hi\nnewline say something\nlast line bye"
A variant of Format, it transforms all argument's key to Nest (Index 0) key
Typeclass of formatable values. The formatArg method takes a value, a key and a field format descriptor and either fails due to a ArgError or produce a string as the result. There is a default formatArg for Generic instances, which applies defaultOptions to genericFormatArg. There are two reasons may cause formatting fail
  1. Can not find argument for the given key.
  2. The field format descriptor does not match the argument.

Extending to new types

Those format functions can be extended to format types other than those provided by default. This is done by instantiating FormatArg. Examples
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}

import           Control.Exception
import           GHC.Generics
import           Text.Format

-- Manually extend to ()
instance FormatArg () where
formatArg x k fmt@(ArgFmt{fmtSpecs="U"}) =
let fmt' = fmt{fmtSpecs = ""}
in  formatArg (show x) k fmt'
formatArg _ _ _ = Left $ toException ArgFmtError

-- Use default generic implementation for type with nullary data constructors.
data Color = Red | Yellow | Blue deriving Generic

instance FormatArg Color

-- Use default generic implementation for type with non-nullary data constructor.
data Triple = Triple String Int Double deriving Generic

instance FormatArg Triple

-- Use default generic implementation for type using record syntax.
data Student = Student { no   :: Int
, name :: String
, age  :: Int
} deriving Generic

instance FormatArg Student

-- Customize field names
data Book = Book { bookName   :: String
, bookAuthor :: String
, bookPrice  :: Double
}

instance FormatArg Book where
formatArg x k fmt
| k == mempty = return $ format1 "{name} {author} {price:.2f}" x
| k == Name "name" = formatArg (bookName x) mempty fmt
| k == Name "author" = formatArg (bookAuthor x) mempty fmt
| k == Name "price" = formatArg (bookPrice x) mempty fmt
| otherwise = Left $ toException $ ArgKeyError

-- A better way to customize field names
-- instance FormatArg Book where
--   formatArg = genericFormatArg $
--     defaultOptions { fieldLabelModifier = drop 4 }

main :: IO ()
main = do
putStrLn $ format "A unit {:U}" ()
putStrLn $ format "I like {}." Blue
putStrLn $ format "Triple {0!0} {0!1} {0!2}" $ Triple "Hello" 123 pi
putStrLn $ format1 "Student: {no} {name} {age}" $ Student 1 "neo" 30
putStrLn $ format "A book: {}" $ Book "Math" "nobody" 99.99
putStrLn $ format1 "Book: {name}, Author: {author}, Price: {price:.2f}" $
Book "Math" "nobody" 99.99
Note: Since v0.12.0, FormatTime instance has been remove, use vformat-time instead.
A typeclass provides the variable arguments magic for format
A Python str.format() like formatter Please see the http://hackage.haskell.org/package/vformat
A configurable generic Formatter creator.