| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Text.Enum.RIO.Fmt
Contents
Synopsis
- type TBuilder = Builder
- newtype UsingBuildable a = UsingBuildable {
- _UsingBuildable :: a
- newtype UsingDisplay a = UsingDisplay {
- _UsingDisplay :: a
- module Text.Enum.Text
- secondsF :: RealFrac n => Int -> n -> Builder
- minutesF :: RealFrac n => Int -> n -> Builder
- hoursF :: RealFrac n => Int -> n -> Builder
- daysF :: RealFrac n => Int -> n -> Builder
- yearsF :: RealFrac n => Int -> n -> Builder
- diffF :: RealFrac n => Bool -> n -> Builder
- weekOfYearMonF :: FormatTime a => a -> Builder
- dayOfWeekFromZeroF :: FormatTime a => a -> Builder
- weekFromZeroF :: FormatTime a => a -> Builder
- dayNameF :: FormatTime a => a -> Builder
- dayNameShortF :: FormatTime a => a -> Builder
- dayOfWeekF :: FormatTime a => a -> Builder
- weekF :: FormatTime a => a -> Builder
- weekCenturyF :: FormatTime a => a -> Builder
- weekYYF :: FormatTime a => a -> Builder
- weekYearF :: FormatTime a => a -> Builder
- dayF :: FormatTime a => a -> Builder
- dayOfMonthSF :: FormatTime a => a -> Builder
- dayOfMonthOrdF :: FormatTime a => a -> Builder
- dayOfMonthF :: FormatTime a => a -> Builder
- monthF :: FormatTime a => a -> Builder
- monthNameShortF :: FormatTime a => a -> Builder
- monthNameF :: FormatTime a => a -> Builder
- centuryF :: FormatTime a => a -> Builder
- yyF :: FormatTime a => a -> Builder
- yearF :: FormatTime a => a -> Builder
- dateSlashLF :: FormatTime a => a -> Builder
- dateDashF :: FormatTime a => a -> Builder
- dateSlashF :: FormatTime a => a -> Builder
- epochF :: FormatTime a => a -> Builder
- subsecondF :: FormatTime a => a -> Builder
- picosecondF :: FormatTime a => a -> Builder
- secondF :: FormatTime a => a -> Builder
- minuteF :: FormatTime a => a -> Builder
- hour12SF :: FormatTime a => a -> Builder
- hour24SF :: FormatTime a => a -> Builder
- hour12F :: FormatTime a => a -> Builder
- hour24F :: FormatTime a => a -> Builder
- dayHalfUF :: FormatTime a => a -> Builder
- dayHalfF :: FormatTime a => a -> Builder
- hmsPLF :: FormatTime a => a -> Builder
- hmsLF :: FormatTime a => a -> Builder
- hmsF :: FormatTime a => a -> Builder
- hmF :: FormatTime a => a -> Builder
- dateTimeF :: FormatTime a => a -> Builder
- tzNameF :: FormatTime a => a -> Builder
- tzF :: FormatTime a => a -> Builder
- timeF :: FormatTime a => Text -> a -> Builder
- hexF :: FormatAsHex a => a -> Builder
- base64F :: FormatAsBase64 a => a -> Builder
- base64UrlF :: FormatAsBase64 a => a -> Builder
- genericF :: (Generic a, GBuildable (Rep a)) => a -> Builder
- tupleF :: TupleF a => a -> Builder
- formatLn :: (HasCallStack, FormatType r) => Format -> r
- format :: (HasCallStack, FormatType r) => Format -> r
- data Format
- ordinalF :: (Buildable a, Integral a) => a -> Builder
- commaizeF :: (Buildable a, Integral a) => a -> Builder
- fixedF :: Real a => Int -> a -> Builder
- exptF :: Real a => Int -> a -> Builder
- floatF :: Real a => a -> Builder
- baseF :: (HasCallStack, Integral a) => Int -> a -> Builder
- binF :: Integral a => a -> Builder
- octF :: Integral a => a -> Builder
- unlessF :: Bool -> Builder -> Builder
- whenF :: Bool -> Builder -> Builder
- padBothF :: Buildable a => Int -> Char -> a -> Builder
- padRightF :: Buildable a => Int -> Char -> a -> Builder
- padLeftF :: Buildable a => Int -> Char -> a -> Builder
- suffixF :: Buildable a => Int -> a -> Builder
- prefixF :: Buildable a => Int -> a -> Builder
- eitherF :: (Buildable a, Buildable b) => Either a b -> Builder
- maybeF :: Buildable a => Maybe a -> Builder
- jsonMapF' :: (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
- blockMapF' :: (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
- mapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder
- mapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder
- jsonListF' :: Foldable f => (a -> Builder) -> f a -> Builder
- jsonListF :: (Foldable f, Buildable a) => f a -> Builder
- blockListF' :: Foldable f => Text -> (a -> Builder) -> f a -> Builder
- blockListF :: (Foldable f, Buildable a) => f a -> Builder
- listF' :: Foldable f => (a -> Builder) -> f a -> Builder
- listF :: (Foldable f, Buildable a) => f a -> Builder
- unlinesF :: (Foldable f, Buildable a) => f a -> Builder
- unwordsF :: (Foldable f, Buildable a) => f a -> Builder
- nameF :: Builder -> Builder -> Builder
- indentF' :: Int -> Text -> Builder -> Builder
- indentF :: Int -> Builder -> Builder
- prettyLn :: (Buildable a, FromBuilder b) => a -> b
- pretty :: (Buildable a, FromBuilder b) => a -> b
- fmtLn :: FromBuilder b => Builder -> b
- fmt :: FromBuilder b => Builder -> b
- (|++||) :: (Show a, FromBuilder b) => a -> Builder -> b
- (||++|) :: (Buildable a, FromBuilder b) => a -> Builder -> b
- (||++||) :: (Show a, FromBuilder b) => a -> Builder -> b
- (|++|) :: (Buildable a, FromBuilder b) => a -> Builder -> b
- (||+) :: (Show a, FromBuilder b) => a -> Builder -> b
- (+||) :: FromBuilder b => Builder -> Builder -> b
- (|+) :: (Buildable a, FromBuilder b) => a -> Builder -> b
- (+|) :: FromBuilder b => Builder -> Builder -> b
- class Buildable p where
Overview
If you want to use fmt with rio, preparing Utf8Builder log messages with
fmt and so forth then you can just import this module along side RIO.
See the demo program for a working example.
EnumText, Display Types
To place an EnumText type in Display (with the Buildable and
TextParsable instance reqiored by EnumText) you can do something like this:
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE NoImplicitPrelude #-}
import RIO
import Text.Enum.RIO.Fmt
data Foo = FOO_bar | FOO_bar_baz
deriving (Bounded,Enum,EnumText,Eq,Ord,Show)
deriving (Buildable,Display,TextParsable) via UsingEnumText Foo
TBuilder
type TBuilder = Builder Source #
RIO export Builder as the ByteString builder so we have to hide it and
provide this in its stead.
UsingBuildable and UsingDisplay
newtype UsingBuildable a Source #
Constructors
| UsingBuildable | |
Fields
| |
Instances
| Buildable a => Display (UsingBuildable a) Source # | |
Defined in Text.Enum.RIO.Fmt | |
newtype UsingDisplay a Source #
derive via this type if you have a Display type and want to derive a
corresponding Buildable instance
Constructors
| UsingDisplay | |
Fields
| |
Instances
| Display a => Buildable (UsingDisplay a) Source # | |
Defined in Text.Enum.RIO.Fmt Methods build :: UsingDisplay a -> Builder # | |
Text.Enum.Text
module Text.Enum.Text
Fmt
Display the absolute value time span in seconds.
>>>secondsF 3 100"100.000"
Display the absolute value time span in minutes.
>>>minutesF 3 150"2.500"
Display the absolute value time span in hours.
>>>hoursF 3 3600"1.000"
Display the absolute value time span in days.
>>>daysF 3 1518646845"17576.931"
Display the absolute value time span in years.
>>>epochF t -- time passed since Jan 1, 1970"1518646845">>>yearsF 3 1518646845"48.156"
Arguments
| :: RealFrac n | |
| => Bool | Whether to display the |
| -> n | Example: |
| -> Builder |
Display a time span as one time relative to another. Input is assumed to
be seconds. Typical inputs are NominalDiffTime and DiffTime.
>>>diffF False 100"a minute">>>diffF True 100"in a minute"
weekOfYearMonF :: FormatTime a => a -> Builder #
Week number of year, where weeks start on Monday (as
mondayStartWeek), 00 - 53.
>>>weekOfYearMonF t"07"
dayOfWeekFromZeroF :: FormatTime a => a -> Builder #
Day of week number, 0 (= Sunday) - 6 (= Saturday).
>>>dayOfWeekFromZeroF t"3"
weekFromZeroF :: FormatTime a => a -> Builder #
Week number of year, where weeks start on Sunday (as
sundayStartWeek), 00 - 53.
>>>weekFromZeroF t"06"
dayNameF :: FormatTime a => a -> Builder #
dayNameShortF :: FormatTime a => a -> Builder #
dayOfWeekF :: FormatTime a => a -> Builder #
Day for Week Date format, 1 - 7.
>>>dayOfWeekF t"3"
weekF :: FormatTime a => a -> Builder #
Week for Week Date format, 01 - 53.
>>>weekF t"07"
weekCenturyF :: FormatTime a => a -> Builder #
Century (first two digits of year) for Week Date format, 00 - 99.
>>>weekCenturyF t"20"
weekYYF :: FormatTime a => a -> Builder #
Last two digits of year for Week Date format, 00 - 99.
>>>weekYYF t"18"
weekYearF :: FormatTime a => a -> Builder #
Year for Week Date format e.g. 2013.
>>>weekYearF t"2018"
dayF :: FormatTime a => a -> Builder #
Day of year for Ordinal Date format, 001 - 366.
>>>dayF t"045"
dayOfMonthSF :: FormatTime a => a -> Builder #
Day of month, leading space as needed, 1 - 31.
dayOfMonthOrdF :: FormatTime a => a -> Builder #
Day of month, 1st, 2nd, 25th, etc.
>>>dayOfMonthOrdF t"14th"
dayOfMonthF :: FormatTime a => a -> Builder #
Day of month, leading 0 as needed, 01 - 31.
>>>dayOfMonthF t"14"
monthF :: FormatTime a => a -> Builder #
Month of year, leading 0 as needed, 01 - 12.
>>>monthF t"02"
monthNameShortF :: FormatTime a => a -> Builder #
monthNameF :: FormatTime a => a -> Builder #
centuryF :: FormatTime a => a -> Builder #
Century (being the first two digits of the year), 00 - 99.
>>>centuryF t"20"
yyF :: FormatTime a => a -> Builder #
Last two digits of year, 00 - 99.
>>>yyF t"18"
yearF :: FormatTime a => a -> Builder #
Year.
>>>yearF t"2018"
dateSlashLF :: FormatTime a => a -> Builder #
As dateFmt locale (e.g. %m/%d/%y).
>>>dateSlashLF t"02/14/18"
dateDashF :: FormatTime a => a -> Builder #
Same as %Y-%m-%d.
>>>dateDashF t"2018-02-14"
dateSlashF :: FormatTime a => a -> Builder #
Same as %m/%d/%y.
>>>dateSlashF t"02/14/18"
epochF :: FormatTime a => a -> Builder #
Number of whole seconds since the Unix epoch. For times before the Unix
epoch, this is a negative number. Note that in %s.%q and %s%Q the
decimals are positive, not negative. For example, 0.9 seconds before the
Unix epoch is formatted as -1.1 with %s%Q.
>>>epochF t"1518646845"
subsecondF :: FormatTime a => a -> Builder #
Decimal point of the second. Up to 12 digits, without trailing zeros. For a whole number of seconds, this produces an empty string.
>>>subsecondF t".5"
picosecondF :: FormatTime a => a -> Builder #
Picosecond, including trailing zeros, 000000000000 - 999999999999.
>>>picosecondF t"500000000000"
secondF :: FormatTime a => a -> Builder #
Second, without decimal part, 00 - 60.
>>>secondF t"45"
minuteF :: FormatTime a => a -> Builder #
Minute, 00 - 59.
>>>minuteF t"20"
hour12SF :: FormatTime a => a -> Builder #
Hour, 12-hour, leading space as needed, 1 - 12.
>>>hour12SF t" 4">>>hour12SF midnight"12"
hour24SF :: FormatTime a => a -> Builder #
Hour, 24-hour, leading space as needed, 0 - 23.
>>>hour24SF t"16">>>hour24SF midnight" 0"
hour12F :: FormatTime a => a -> Builder #
Hour, 12-hour, leading 0 as needed, 01 - 12.
>>>hour12F t"04">>>hour12F midnight"12"
hour24F :: FormatTime a => a -> Builder #
Hour, 24-hour, leading 0 as needed, 00 - 23.
>>>hour24F t"16">>>hour24F midnight"00"
dayHalfUF :: FormatTime a => a -> Builder #
Day half from (amPm locale), AM, PM.
>>>dayHalfUF t"PM"
dayHalfF :: FormatTime a => a -> Builder #
Day half from (amPm locale), converted to lowercase, am, pm.
>>>dayHalfF t"pm"
hmsPLF :: FormatTime a => a -> Builder #
As time12Fmt locale (e.g. %I:%M:%S %p).
>>>hmsPLF t"04:20:45 PM"
hmsLF :: FormatTime a => a -> Builder #
As timeFmt locale (e.g. %H:%M:%S).
>>>hmsLF t"16:20:45"
hmsF :: FormatTime a => a -> Builder #
Same as %H:%M:%S.
>>>hmsF t"16:20:45"
hmF :: FormatTime a => a -> Builder #
Same as %H:%M.
>>>hmF t"16:20"
dateTimeF :: FormatTime a => a -> Builder #
As dateTimeFmt locale (e.g. %a %b %e %H:%M:%S %Z %Y).
>>>dateTimeF t"Wed Feb 14 16:20:45 CST 2018"
tzNameF :: FormatTime a => a -> Builder #
Timezone name.
>>>tzNameF t"CST"
tzF :: FormatTime a => a -> Builder #
Timezone offset on the format -HHMM.
>>>t2018-02-14 16:20:45.5 CST>>>tzF t"-0600"
timeF :: FormatTime a => Text -> a -> Builder #
Format time with an arbitrary formatting string. Other formatters in
this module are implemented using timeF.
hexF :: FormatAsHex a => a -> Builder #
Format a number or bytestring as hex:
>>>hexF 3635"e33">>>hexF ("\0\50\63\80" :: BS.ByteString)"00323f50"
base64F :: FormatAsBase64 a => a -> Builder #
Convert a bytestring to base64:
>>>base64F ("\0\50\63\80" :: BS.ByteString)"ADI/UA=="
base64UrlF :: FormatAsBase64 a => a -> Builder #
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=="
genericF :: (Generic a, GBuildable (Rep a)) => a -> Builder #
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.
tupleF :: TupleF a => a -> Builder #
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.
formatLn :: (HasCallStack, FormatType r) => Format -> r #
Like format, but adds a newline.
format :: (HasCallStack, FormatType r) => Format -> r #
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 42 + 2 = 4
You can use arbitrary formatters:
>>>format "0x{} + 0x{} = 0x{}" (hexF 130) (hexF 270) (hexF (130+270))0x82 + 0x10e = 0x190
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.
ordinalF :: (Buildable a, Integral a) => a -> Builder #
Add an ordinal suffix to a number:
>>>ordinalF 15"15th">>>ordinalF 22"22nd"
commaizeF :: (Buildable a, Integral a) => a -> Builder #
Break digits in a number:
>>>commaizeF 15830000"15,830,000"
fixedF :: Real a => Int -> a -> Builder #
Format a floating-point number without scientific notation:
>>>listF' (fixedF 5) [pi,0.1,10]"[3.14159, 0.10000, 10.00000]"
exptF :: Real a => Int -> a -> Builder #
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]"
floatF :: Real a => a -> Builder #
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]"
baseF :: (HasCallStack, Integral a) => Int -> a -> Builder #
Format a number in arbitrary base (up to 36):
>>>baseF 3 10000"111201101">>>baseF 7 10000"41104">>>baseF 36 10000"7ps"
binF :: Integral a => a -> Builder #
Format a number as binary:
>>>listF' binF [7,8,9,10]"[111, 1000, 1001, 1010]"
octF :: Integral a => a -> Builder #
Format a number as octal:
>>>listF' octF [7,8,9,10]"[7, 10, 11, 12]"
unlessF :: Bool -> Builder -> Builder #
Display something only if the condition is False (empty string
otherwise).
padBothF :: Buildable a => Int -> Char -> a -> Builder #
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=="
padRightF :: Buildable a => Int -> Char -> a -> Builder #
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"
padLeftF :: Buildable a => Int -> Char -> a -> Builder #
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"
suffixF :: Buildable a => Int -> a -> Builder #
Take the last N characters:
>>>suffixF 3 "hello""llo"
prefixF :: Buildable a => Int -> a -> Builder #
Take the first N characters:
>>>prefixF 3 "hello""hel"
eitherF :: (Buildable a, Buildable b) => Either a b -> Builder #
Format an Either:
>>>eitherF (Right 1 :: Either Bool Int)"<Right: 1>"
jsonMapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder #
A version of jsonMapF 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 #
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 ] }
blockMapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder #
A version of blockMapF 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 #
A YAML-like map formatter:
>>>fmt $ blockMapF [("Odds", blockListF [1,3]), ("Evens", blockListF [2,4])]Odds: - 1 - 3 Evens: - 2 - 4
mapF' :: (IsList t, Item t ~ (k, v)) => (k -> Builder) -> (v -> Builder) -> t -> Builder #
A version of mapF that lets you supply your own building function for
keys and values.
mapF :: (IsList t, Item t ~ (k, v), Buildable k, Buildable v) => t -> Builder #
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.
jsonListF' :: Foldable f => (a -> Builder) -> f a -> Builder #
A version of jsonListF that lets you supply your own building function
for list elements.
jsonListF :: (Foldable f, Buildable a) => f a -> Builder #
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 ]
Arguments
| :: 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 "-").
blockListF :: (Foldable f, Buildable a) => f a -> Builder #
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
listF' :: Foldable f => (a -> Builder) -> f a -> Builder #
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]"
listF :: (Foldable f, Buildable a) => f a -> Builder #
A simple comma-separated list formatter.
>>>listF ["hello", "world"]"[hello, world]"
For multiline output, use jsonListF.
unlinesF :: (Foldable f, Buildable a) => f a -> Builder #
Arrange elements on separate lines.
>>>fmt $ unlinesF ["hello", "world"]hello world
unwordsF :: (Foldable f, Buildable a) => f a -> Builder #
Put spaces between elements.
>>>fmt $ unwordsF ["hello", "world"]hello world
Of course, it works on anything Buildable:
>>>fmt $ unwordsF [1, 2]1 2
nameF :: Builder -> Builder -> Builder #
Attach a name to anything:
>>>fmt $ nameF "clients" $ blockListF ["Alice", "Bob", "Zalgo"]clients: - Alice - Bob - Zalgo
indentF' :: Int -> Text -> Builder -> Builder #
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.
indentF :: Int -> Builder -> Builder #
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.
prettyLn :: (Buildable a, FromBuilder b) => a -> b #
Like pretty, but appends a newline.
pretty :: (Buildable a, FromBuilder b) => a -> b #
fmtLn :: FromBuilder b => Builder -> b #
Like fmt, but appends a newline.
fmt :: FromBuilder b => Builder -> b #
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!
(|++||) :: (Show a, FromBuilder b) => a -> Builder -> b infixr 1 #
(||++|) :: (Buildable a, FromBuilder b) => a -> Builder -> b infixr 1 #
(||++||) :: (Show a, FromBuilder b) => a -> Builder -> b infixr 1 #
(|++|) :: (Buildable a, FromBuilder b) => a -> Builder -> b infixr 1 #
(+||) :: FromBuilder b => Builder -> Builder -> b infixr 1 #
Concatenate, then convert.
(|+) :: (Buildable a, FromBuilder b) => a -> Builder -> b infixr 1 #
build and concatenate, then convert.
(+|) :: FromBuilder b => Builder -> Builder -> b infixr 1 #
Concatenate, then convert.
The class of types that can be rendered to a Builder.
Instances
Orphan instances
| FromBuilder Utf8Builder Source # | With this instance we can use |
Methods fromBuilder :: Builder -> Utf8Builder # | |
| EnumText a => Display (UsingEnumText a) Source # | |