Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- (+|) :: FromBuilder b => Builder -> Builder -> b
- (|+) :: (Buildable a, FromBuilder b) => a -> Builder -> b
- (+||) :: FromBuilder b => Builder -> Builder -> b
- (||+) :: (Show a, FromBuilder b) => a -> Builder -> b
- (|++|) :: (Buildable a, FromBuilder b) => a -> Builder -> b
- (||++||) :: (Show a, FromBuilder b) => a -> Builder -> b
- (|++||) :: (Show a, FromBuilder b) => a -> Builder -> b
- (||++|) :: (Buildable a, FromBuilder b) => a -> Builder -> b
- format :: (HasCallStack, FormatType r) => Format -> r
- formatLn :: (HasCallStack, FormatType r) => Format -> r
- data Format
- fmt :: FromBuilder b => Builder -> b
- fmtLn :: FromBuilder b => Builder -> b
- pretty :: (Buildable a, FromBuilder b) => a -> b
- prettyLn :: (Buildable a, FromBuilder b) => a -> b
- data Builder
- class Buildable p where
- module Fmt.Time
- indentF :: Int -> Builder -> Builder
- indentF' :: Int -> Text -> Builder -> Builder
- nameF :: Builder -> Builder -> Builder
- unwordsF :: (Foldable f, Buildable a) => f a -> Builder
- unlinesF :: (Foldable f, Buildable a) => f a -> Builder
- listF :: (Foldable f, Buildable a) => f a -> Builder
- listF' :: Foldable f => (a -> Builder) -> f a -> Builder
- blockListF :: forall f a. (Foldable f, Buildable a) => f a -> Builder
- blockListF' :: forall f a. Foldable f => Text -> (a -> Builder) -> f a -> Builder
- jsonListF :: forall f a. (Foldable f, Buildable a) => f a -> Builder
- jsonListF' :: forall f a. Foldable f => (a -> Builder) -> f a -> Builder
- mapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder
- mapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder
- blockMapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder
- blockMapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder
- jsonMapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder
- jsonMapF' :: forall t k v. (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder
- tupleF :: TupleF a => a -> Builder
- maybeF :: Buildable a => Maybe a -> Builder
- eitherF :: (Buildable a, Buildable b) => Either a b -> Builder
- prefixF :: Buildable a => Int -> a -> Builder
- suffixF :: Buildable a => Int -> a -> Builder
- padLeftF :: Buildable a => Int -> Char -> a -> Builder
- padRightF :: Buildable a => Int -> Char -> a -> Builder
- padBothF :: Buildable a => Int -> Char -> a -> Builder
- hexF :: FormatAsHex a => a -> Builder
- base64F :: FormatAsBase64 a => a -> Builder
- base64UrlF :: FormatAsBase64 a => a -> Builder
- ordinalF :: (Buildable a, Integral a) => a -> Builder
- commaizeF :: (Buildable a, Integral a) => a -> Builder
- octF :: Integral a => a -> Builder
- binF :: Integral a => a -> Builder
- baseF :: (HasCallStack, Integral a) => Int -> a -> Builder
- floatF :: Real a => a -> Builder
- exptF :: Real a => Int -> a -> Builder
- fixedF :: Real a => Int -> a -> Builder
- whenF :: Bool -> Builder -> Builder
- unlessF :: Bool -> Builder -> Builder
- genericF :: (Generic a, GBuildable (Rep a)) => a -> Builder
Overloaded strings
You need OverloadedStrings
enabled to use this library. There are three
ways to do it:
- In GHCi: do
:set -XOverloadedStrings
. - In a module: add
{-# LANGUAGE OverloadedStrings #-}
to the beginning of your module. - In a project: add
OverloadedStrings
to thedefault-extensions
section of your.cabal
file.
Examples
Here's a bunch of examples because some people learn better by looking at examples.
Insert some variables into a string:
>>>
let (a, b, n) = ("foo", "bar", 25)
>>>
("Here are some words: "+|a|+", "+|b|+"\nAlso a number: "+|n|+"") :: String
"Here are some words: foo, bar\nAlso a number: 25"
Print it:
>>>
fmtLn ("Here are some words: "+|a|+", "+|b|+"\nAlso a number: "+|n|+"")
Here are some words: foo, bar Also a number: 25
Format a list in various ways:
>>>
let xs = ["John", "Bob"]
>>>
fmtLn ("Using show: "+||xs||+"\nUsing listF: "+|listF xs|+"")
Using show: ["John","Bob"] Using listF: [John, Bob]
>>>
fmt ("YAML-like:\n"+|blockListF xs|+"")
YAML-like: - John - Bob
>>>
fmt ("JSON-like: "+|jsonListF xs|+"")
JSON-like: [ John , Bob ]
Migration guide from formatting
Instead of using %
, surround variables with +|
and |+
. You don't have
to use sformat
or anything else, and also where you were using build
,
int
, text
, etc in formatting
, you don't have to use anything in fmt
:
formatting sformat ("Foo: "%build%", bar: "%int) foo bar fmt "Foo: "+|foo|+", bar: "+|bar|+""
The resulting formatted string is polymorphic and can be used as String
,
Text
, Builder
or even IO
(i.e. the string will be printed to the
screen). However, when printing it is recommended to use fmt
or fmtLn
for clarity.
fmt
provides lots of formatters (which are simply functions that produce
Builder
):
formatting sformat ("Got another byte ("%hex%")") x fmt "Got another byte ("+|hexF x|+")"
Instead of the shown
formatter, either just use show
or double brackets:
formatting sformat ("This uses Show: "%shown%") foo fmt #1 "This uses Show: "+|show foo|+"" fmt #2 "This uses Show: "+||foo||+""
Many formatters from formatting
have the same names in fmt
, but with
added “F”: hexF
, exptF
, etc. Some have been renamed, though:
Cutting: fitLeft ->prefixF
fitRight ->suffixF
Padding: left ->padLeftF
right ->padRightF
center ->padBothF
Stuff with numbers: ords ->ordinalF
commas ->commaizeF
Also, some formatters from formatting
haven't been added to fmt
yet. Specifically:
plural
andasInt
(but instead ofasInt
you can usefromEnum
)prefixBin
,prefixOrd
,prefixHex
, andbytes
- formatters that use
Scientific
(sci
andscifmt
)
They will be added later. (On the other hand, fmt
provides some useful
formatters not available in formatting
, such as listF
, mapF
, tupleF
and so on.)
Basic formatting
To format strings, put variables between (+|
) and (|+
):
>>>
let name = "Alice" :: String
>>>
"Meet "+|name|+"!" :: String
"Meet Alice!"
Of course, Text
is supported as well:
>>>
"Meet "+|name|+"!" :: Text
"Meet Alice!"
You don't actually need any type signatures; however, if you're toying with
this library in GHCi, it's recommended to either add a type signature or use
fmtLn
:
>>>
fmtLn ("Meet "+|name|+"!")
Meet Alice!
Otherwise the type of the formatted string would be resolved to IO ()
and
printed without a newline, which is not very convenient when you're in GHCi.
On the other hand, it's useful for quick-and-dirty scripts:
main = do [fin, fout] <- words <$> getArgs "Reading data from "+|fin|+"\n" xs <- readFile fin "Writing processed data to "+|fout|+"\n" writeFile fout (show (process xs))
Anyway, let's proceed. Anything Buildable
, including numbers, booleans,
characters and dates, can be put between (+|
) and (|+
):
>>>
let starCount = "173"
>>>
fmtLn ("Meet "+|name|+"! She's got "+|starCount|+" stars on Github.")
Meet Alice! She's got 173 stars on Github.
Since the only thing (+|
) and (|+
) do is concatenate strings and do
conversion, you can use any functions you want inside them. In this case,
length
:
>>>
fmtLn (""+|name|+"'s name has "+|length name|+" letters")
Alice's name has 5 letters
If something isn't Buildable
, just use show
on it:
>>>
let pos = (3, 5)
>>>
fmtLn ("Character's position: "+|show pos|+"")
Character's position: (3,5)
Or one of many formatters provided by this library – for instance, for tuples
of various sizes there's tupleF
:
>>>
fmtLn ("Character's position: "+|tupleF pos|+"")
Character's position: (3, 5)
Finally, for convenience there's the (|++|
) operator, which can be used if
you've got one variable following the other:
>>>
let (a, op, b, res) = (2, "*", 2, 4)
>>>
fmtLn (""+|a|++|op|++|b|+" = "+|res|+"")
2*2 = 4
Also, since in some codebases there are lots of types which aren't
Buildable
, there are operators (+||
) and (||+
), which use show
instead of build
:
(""+|show foo|++|show bar|+"") == (""+||foo||++||bar||+"")
Ordinary brackets
Operators for the operators god!
(|+) :: (Buildable a, FromBuilder b) => a -> Builder -> b infixr 1 Source #
build
and concatenate, then convert.
Show
brackets
More operators for the operators god!
(||+) :: (Show a, FromBuilder b) => a -> Builder -> b infixr 1 Source #
show
and concatenate, then convert.
Combinations
Z̸͠A̵̕͟͠L̡̀́͠G̶̛O͝ ̴͏̀ I͞S̸̸̢͠ ̢̛͘͢C̷͟͡Ó̧̨̧͞M̡͘͟͞I̷͜N̷̕G̷̀̕
(Though you can just use ""
between +| |+
instead of using these
operators, and Show
-brackets don't have to be used at all because there's
show
available.)
Old-style formatting
format :: (HasCallStack, FormatType r) => Format -> r Source #
An old-style formatting function taken from text-format
(see
Data.Text.Format). Unlike format
from
Data.Text.Format, it can produce String
and strict Text
as well (and
print to console too). Also it's polyvariadic:
>>>
format "{} + {} = {}" 2 2 4
2 + 2 = 4
You can use arbitrary formatters:
>>>
format "0x{} + 0x{} = 0x{}" (hexF 130) (hexF 270) (hexF (130+270))
0x82 + 0x10e = 0x190
formatLn :: (HasCallStack, FormatType r) => Format -> r Source #
Like format
, but adds a newline.
A format string. This is intentionally incompatible with other string types, to make it difficult to construct a format string by concatenating string fragments (a very common way to accidentally make code vulnerable to malicious data).
This type is an instance of IsString
, so the easiest way to
construct a query is to enable the OverloadedStrings
language
extension and then simply write the query in double quotes.
{-# LANGUAGE OverloadedStrings #-} import Fmt f :: Format f = "hello {}"
The underlying type is Text
, so literal Haskell strings that
contain Unicode characters will be correctly handled.
Helper functions
fmt :: FromBuilder b => Builder -> b Source #
fmt
converts things to String
, Text
, ByteString
or Builder
.
Most of the time you won't need it, as strings produced with (+|
) and
(|+
) can already be used as String
, Text
, etc. However, combinators
like listF
can only produce Builder
(for better type inference), and you
need to use fmt
on them.
Also, fmt
can do printing:
>>>
fmt "Hello world!\n"
Hello world!
pretty :: (Buildable a, FromBuilder b) => a -> b Source #
A Builder
is an efficient way to build lazy Text
values.
There are several functions for constructing builders, but only one
to inspect them: to extract any data, you have to turn them into
lazy Text
values using toLazyText
.
Internally, a builder constructs a lazy Text
by filling arrays
piece by piece. As each buffer is filled, it is 'popped' off, to
become a new chunk of the resulting lazy Text
. All this is
hidden from the user of the Builder
.
Instances
Eq Builder | |
Ord Builder | |
Show Builder | |
IsString Builder | |
Defined in Data.Text.Internal.Builder fromString :: String -> Builder # | |
Semigroup Builder | |
Monoid Builder | |
Buildable Builder | |
Defined in Formatting.Buildable | |
FromBuilder Builder Source # | |
Defined in Fmt.Internal.Core fromBuilder :: Builder -> Builder Source # | |
TupleF [Builder] Source # | |
The class of types that can be rendered to a Builder
.
Instances
Formatters
Time
module Fmt.Time
Text
indentF :: Int -> Builder -> Builder Source #
Indent a block of text.
>>>
fmt $ "This is a list:\n" <> indentF 4 (blockListF [1,2,3])
This is a list: - 1 - 2 - 3
The output will always end with a newline, even when the input doesn't.
indentF' :: Int -> Text -> Builder -> Builder Source #
Add a prefix to the first line, and indent all lines but the first one.
The output will always end with a newline, even when the input doesn't.
nameF :: Builder -> Builder -> Builder Source #
Attach a name to anything:
>>>
fmt $ nameF "clients" $ blockListF ["Alice", "Bob", "Zalgo"]
clients: - Alice - Bob - Zalgo
unwordsF :: (Foldable f, Buildable a) => f a -> Builder Source #
Put spaces between elements.
>>>
fmt $ unwordsF ["hello", "world"]
hello world
Of course, it works on anything Buildable
:
>>>
fmt $ unwordsF [1, 2]
1 2
unlinesF :: (Foldable f, Buildable a) => f a -> Builder Source #
Arrange elements on separate lines.
>>>
fmt $ unlinesF ["hello", "world"]
hello world
Lists
listF :: (Foldable f, Buildable a) => f a -> Builder Source #
A simple comma-separated list formatter.
>>>
listF ["hello", "world"]
"[hello, world]"
For multiline output, use jsonListF
.
listF' :: Foldable f => (a -> Builder) -> f a -> Builder Source #
A version of listF
that lets you supply your own building function for
list elements.
For instance, to format a list of numbers as hex:
>>>
listF' hexF [1234, 5678]
"[4d2, 162e]"
blockListF :: forall f a. (Foldable f, Buildable a) => f a -> Builder Source #
A multiline formatter for lists.
>>>
fmt $ blockListF [1,2,3]
- 1 - 2 - 3
Multi-line elements are indented correctly:
>>>
fmt $ blockListF ["hello\nworld", "foo\nbar\nquix"]
- hello world - foo bar quix
:: Foldable f | |
=> Text | Bullet |
-> (a -> Builder) | Builder for elements |
-> f a | Structure with elements |
-> Builder |
A version of blockListF
that lets you supply your own building function
for list elements (instead of build
) and choose the bullet character
(instead of "-"
).
jsonListF :: forall f a. (Foldable f, Buildable a) => f a -> Builder Source #
A JSON-style formatter for lists.
>>>
fmt $ jsonListF [1,2,3]
[ 1 , 2 , 3 ]
Like blockListF
, it handles multiline elements well:
>>>
fmt $ jsonListF ["hello\nworld", "foo\nbar\nquix"]
[ hello world , foo bar quix ]
jsonListF' :: forall f a. Foldable f => (a -> Builder) -> f a -> Builder Source #
A version of jsonListF
that lets you supply your own building function
for list elements.
Maps
mapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder Source #
A simple JSON-like map formatter; works for Map, HashMap, etc, as well as ordinary lists of pairs.
>>>
mapF [("a", 1), ("b", 4)]
"{a: 1, b: 4}"
For multiline output, use jsonMapF
.
mapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder Source #
A version of mapF
that lets you supply your own building function for
keys and values.
blockMapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder Source #
A YAML-like map formatter:
>>>
fmt $ blockMapF [("Odds", blockListF [1,3]), ("Evens", blockListF [2,4])]
Odds: - 1 - 3 Evens: - 2 - 4
blockMapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder Source #
A version of blockMapF
that lets you supply your own building function
for keys and values.
jsonMapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder Source #
A JSON-like map formatter (unlike mapF
, always multiline):
>>>
fmt $ jsonMapF [("Odds", jsonListF [1,3]), ("Evens", jsonListF [2,4])]
{ Odds: [ 1 , 3 ] , Evens: [ 2 , 4 ] }
jsonMapF' :: forall t k v. (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder Source #
A version of jsonMapF
that lets you supply your own building function
for keys and values.
Tuples
tupleF :: TupleF a => a -> Builder Source #
Format a tuple (of up to 8 elements):
>>>
tupleF (1,2,"hi")
"(1, 2, hi)"
If any of the elements takes several lines, an alternate format is used:
>>>
fmt $ tupleF ("test","foo\nbar","more test")
( test , foo bar , more test )
You can also use tupleF
on lists to get tuple-like formatting.
ADTs
eitherF :: (Buildable a, Buildable b) => Either a b -> Builder Source #
Format an Either
:
>>>
eitherF (Right 1 :: Either Bool Int)
"<Right: 1>"
Padding/trimming
prefixF :: Buildable a => Int -> a -> Builder Source #
Take the first N characters:
>>>
prefixF 3 "hello"
"hel"
suffixF :: Buildable a => Int -> a -> Builder Source #
Take the last N characters:
>>>
suffixF 3 "hello"
"llo"
padLeftF :: Buildable a => Int -> Char -> a -> Builder Source #
padLeftF n c
pads the string with character c
from the left side until it
becomes n
characters wide (and does nothing if the string is already that
long, or longer):
>>>
padLeftF 5 '0' 12
"00012">>>
padLeftF 5 '0' 123456
"123456"
padRightF :: Buildable a => Int -> Char -> a -> Builder Source #
padRightF n c
pads the string with character c
from the right side until
it becomes n
characters wide (and does nothing if the string is already
that long, or longer):
>>>
padRightF 5 ' ' "foo"
"foo ">>>
padRightF 5 ' ' "foobar"
"foobar"
padBothF :: Buildable a => Int -> Char -> a -> Builder Source #
padBothF n c
pads the string with character c
from both sides until
it becomes n
characters wide (and does nothing if the string is already
that long, or longer):
>>>
padBothF 5 '=' "foo"
"=foo=">>>
padBothF 5 '=' "foobar"
"foobar"
When padding can't be distributed equally, the left side is preferred:
>>>
padBothF 8 '=' "foo"
"===foo=="
Hex
hexF :: FormatAsHex a => a -> Builder Source #
Format a number or bytestring as hex:
>>>
hexF 3635
"e33">>>
hexF ("\0\50\63\80" :: BS.ByteString)
"00323f50"
Bytestrings
base64F :: FormatAsBase64 a => a -> Builder Source #
Convert a bytestring to base64:
>>>
base64F ("\0\50\63\80" :: BS.ByteString)
"ADI/UA=="
base64UrlF :: FormatAsBase64 a => a -> Builder Source #
Convert a bytestring to base64url (a variant of base64 which omits /
and
thus can be used in URLs):
>>>
base64UrlF ("\0\50\63\80" :: BS.ByteString)
"ADI_UA=="
Integers
ordinalF :: (Buildable a, Integral a) => a -> Builder Source #
Add an ordinal suffix to a number:
>>>
ordinalF 15
"15th">>>
ordinalF 22
"22nd"
commaizeF :: (Buildable a, Integral a) => a -> Builder Source #
Break digits in a number:
>>>
commaizeF 15830000
"15,830,000"
Base conversion
octF :: Integral a => a -> Builder Source #
Format a number as octal:
>>>
listF' octF [7,8,9,10]
"[7, 10, 11, 12]"
binF :: Integral a => a -> Builder Source #
Format a number as binary:
>>>
listF' binF [7,8,9,10]
"[111, 1000, 1001, 1010]"
baseF :: (HasCallStack, Integral a) => Int -> a -> Builder Source #
Format a number in arbitrary base (up to 36):
>>>
baseF 3 10000
"111201101">>>
baseF 7 10000
"41104">>>
baseF 36 10000
"7ps"
Floating-point
floatF :: Real a => a -> Builder Source #
Format a floating-point number:
>>>
floatF 3.1415
"3.1415"
Numbers smaller than 1e-6 or bigger-or-equal to 1e21 will be displayed using scientific notation:
>>>
listF' floatF [1e-6,9e-7]
"[0.000001, 9.0e-7]">>>
listF' floatF [9e20,1e21]
"[900000000000000000000.0, 1.0e21]"
exptF :: Real a => Int -> a -> Builder Source #
Format a floating-point number using scientific notation, with the given amount of decimal places.
>>>
listF' (exptF 5) [pi,0.1,10]
"[3.14159e0, 1.00000e-1, 1.00000e1]"
fixedF :: Real a => Int -> a -> Builder Source #
Format a floating-point number without scientific notation:
>>>
listF' (fixedF 5) [pi,0.1,10]
"[3.14159, 0.10000, 10.00000]"
Conditional formatting
unlessF :: Bool -> Builder -> Builder Source #
Display something only if the condition is False
(empty string
otherwise).
Generic formatting
genericF :: (Generic a, GBuildable (Rep a)) => a -> Builder Source #
Format an arbitrary value without requiring a Buildable
instance:
>>>
data Foo = Foo { x :: Bool, y :: [Int] } deriving Generic
>>>
fmt (genericF (Foo True [1,2,3]))
Foo: x: True y: [1, 2, 3]
It works for non-record constructors too:
>>>
data Bar = Bar Bool [Int] deriving Generic
>>>
fmtLn (genericF (Bar True [1,2,3]))
<Bar: True, [1, 2, 3]>
Any fields inside the type must either be Buildable
or one of the following
types:
The exact format of genericF
might change in future versions, so don't rely
on it. It's merely a convenience function.