| Copyright | (c) 2020 Alex Chapman | 
|---|---|
| License | BSD3 | 
| Maintainer | alex@farfromthere.net | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Formatting.Combinators
Contents
Description
Description : Formatting combinators for building new formatters, with some useful pre-defined formatters.
A formatting combinator takes a Format and returns another Format.
Generally we want to change what the original format takes as its *input*,
leaving the output polymorphic.
Many of these combinators can be chained together to form a single Format.
Implementation detail: in order to be able to chain multiple combinators to make a single Format we need them all to use the same intermediate string type, and we have chosen Builder.
This does not tie you to using Builders, because the final output string type r is still polymorphic.
|
Synopsis
- concatenated :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- joinedWith :: Foldable t => ([Text] -> Text) -> Format Builder (a -> Builder) -> Format r (t a -> r)
- intercalated :: Foldable t => Text -> Format Builder (a -> Builder) -> Format r (t a -> r)
- unworded :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- unlined :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- spaced :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- commaSep :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- commaSpaceSep :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- list :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- qlist :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r)
- took :: Int -> Format r ([a] -> r) -> Format r ([a] -> r)
- dropped :: Int -> Format r ([a] -> r) -> Format r ([a] -> r)
- splat :: (Char -> Bool) -> (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) -> Format r a -> Format r a
- splatWith :: (Text -> [Text]) -> (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) -> Format r a -> Format r a
- splatOn :: Text -> (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) -> Format r a -> Format r a
- worded :: (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) -> Format r a -> Format r a
- lined :: (Format Builder (Builder -> Builder) -> Format Builder ([Builder] -> Builder)) -> Format r a -> Format r a
- alteredWith :: (Text -> Text) -> Format r a -> Format r a
- replaced :: Text -> Text -> Format r a -> Format r a
- uppercased :: Format r a -> Format r a
- lowercased :: Format r a -> Format r a
- titlecased :: Format r a -> Format r a
- ltruncated :: Int64 -> Format r a -> Format r a
- ctruncated :: Int64 -> Int64 -> Format r a -> Format r a
- rtruncated :: Int64 -> Format r a -> Format r a
- lpadded :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r)
- rpadded :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r)
- cpadded :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r)
- lfixed :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r)
- rfixed :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r)
- cfixed :: Int64 -> Int64 -> Char -> Format r (a -> r) -> Format r (a -> r)
- prefixed :: Builder -> Format r a -> Format r a
- suffixed :: Builder -> Format r a -> Format r a
- surrounded :: Builder -> Format r a -> Format r a
- enclosed :: Builder -> Builder -> Format r a -> Format r a
- squoted :: Format r a -> Format r a
- dquoted :: Format r a -> Format r a
- parenthesised :: Format r a -> Format r a
- squared :: Format r a -> Format r a
- braced :: Format r a -> Format r a
- angled :: Format r a -> Format r a
- backticked :: Format r a -> Format r a
- indented :: Int -> Format r a -> Format r a
- indentedLines :: Foldable t => Int -> Format Builder (a -> Builder) -> Format r (t a -> r)
- reindented :: Int -> Format r a -> Format r a
- roundedTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r)
- truncatedTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r)
- ceilingedTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r)
- flooredTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r)
- viewed :: ((a -> Const a b) -> s -> Const a t) -> Format r (a -> r) -> Format r (s -> r)
- accessed :: (s -> a) -> Format r (a -> r) -> Format r (s -> r)
- binPrefix :: Integral a => Int64 -> Format r (a -> r)
- octPrefix :: Integral a => Int64 -> Format r (a -> r)
- hexPrefix :: Integral a => Int64 -> Format r (a -> r)
Formatting lists of data
concatenated :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Format each value in a list and concatenate them all:
>>>format (concatenated text) ["one", "two", "three"]"onetwothree"
>>>format (took 15 (concatenated bin)) [1..]"1101110010111011110001001101010111100110111101111"
joinedWith :: Foldable t => ([Text] -> Text) -> Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Use the given text-joining function to join together the individually rendered items of a list.
>>>format (joinedWith (mconcat . reverse) int) [123, 456, 789]"789456123"
intercalated :: Foldable t => Text -> Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Format each value in a list and place the given string between each:
>>>fprintLn (intercalated "||" int) [1, 2, 3]1||2||3
unworded :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Format each value in a list with spaces in between:
>>>format (unworded int) [1, 2, 3]"1 2 3"
unlined :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Format each value in a list, placing each on its own line:
>>>fprint (unlined char) ['a'..'c']a b c
spaced :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Separate the formatted items of the Foldable (e.g. list) with spaces:
>>>format (spaced int) [1, 2, 3]"1 2 3"
Note that this behaviour is identical to unworded, it's just a different way of thinking about it.
commaSep :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Separate the formatted items of the Foldable (e.g. list) with commas:
>>>format (commaSep stext) ["one", "two", "three", "four", "five"]"one,two,three,four,five"
>>>format (took 5 (commaSep int)) [1..]"1,2,3,4,5"
commaSpaceSep :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Separate the formatted items of the Foldable (e.g. list) with commas and spaces:
>>>format (took 3 (commaSpaceSep ords)) [1..]"1st, 2nd, 3rd"
list :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Add square brackets around the Foldable (e.g. a list), and separate each formatted item with a comma and space.
>>>format (list stext) ["one", "two", "three"]"[one, two, three]"
>>>format (list shown) ["one", "two", "three"]"[\"one\", \"two\", \"three\"]"
qlist :: Foldable t => Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Like list, but also put double quotes around each rendered item:
>>>fprintLn (qlist stext) ["one", "two", "three"]["one", "two", "three"]
took :: Int -> Format r ([a] -> r) -> Format r ([a] -> r) Source #
Take only the first n items from the list of items.
>>>format (took 7 (list bin)) [1..]"[1, 10, 11, 100, 101, 110, 111]"
>>>format (list bin) (take 7 [1..])"[1, 10, 11, 100, 101, 110, 111]"
dropped :: Int -> Format r ([a] -> r) -> Format r ([a] -> r) Source #
Drop the first n items from the list of items.
>>>format (dropped 3 (list int) [1..6]"[4, 5, 6]"
Splitting strings to pass to other formatters
Arguments
| :: (Char -> Bool) | Whether to split the string at this character | 
| -> (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) | A list-formatting combinator, e.g.  | 
| -> Format r a | The base formatter, whose rendered text will be split | 
| -> Format r a | 
Split the formatted item in places the given predicated matches, and use the given list combinator to render the resultant list of strings (this function was sent to us from a parallel universe in which splat is the past participle of split, e.g. "whoops, I splat my pants").
>>>format (splat Data.Char.isSpace commaSpaceSep stext) "This\t is\n\t\t poorly formatted ""This, , , is, , , , , poorly, formatted, , , "
Arguments
| :: (Text -> [Text]) | The text splitter | 
| -> (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) | A list-formatting combinator, e.g.  | 
| -> Format r a | The base formatter, whose rendered text will be split | 
| -> Format r a | 
Utility for taking a text-splitting function and turning it into a formatting combinator.
>>>format (splatWith (TL.chunksOf 3) list int) 1234567890"[123, 456, 789, 0]"
Arguments
| :: Text | The text to split on | 
| -> (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) | A list-formatting combinator, e.g.  | 
| -> Format r a | The base formatter, whose rendered text will be split | 
| -> Format r a | 
Split the formatted item at instances of the given string, and use the given list combinator to render the resultant list of strings.
>>>fprint (splatOn "," unlined text) "one,two,three"one two three
>>>fprint (splatOn "," indentedLines text) "one,two,three"one two three
Arguments
| :: (Format r' (Builder -> r') -> Format Builder ([Builder] -> Builder)) | A list-formatting combinator, e.g.  | 
| -> Format r a | The base formatter, whose rendered text will be split | 
| -> Format r a | 
Split the formatted item into words and use the given list combinator to render the resultant list of strings.
>>>format (worded list text) "one two three ""[one, two, three]"
Arguments
| :: (Format Builder (Builder -> Builder) -> Format Builder ([Builder] -> Builder)) | A list-formatting combinator, e.g.  | 
| -> Format r a | The base formatter, whose rendered text will be split | 
| -> Format r a | 
Split the formatted item into lines and use the given list combinator to render the resultant list of strings.
>>>fprintLn (lined qlist text) "one two three\n\nfour five six\nseven eight nine\n\n"["one two three", "", "four five six", "seven eight nine", ""]
Altering formatted strings
alteredWith :: (Text -> Text) -> Format r a -> Format r a Source #
Alter the formatted string with the given function.
>>>format (alteredWith Data.Text.Lazy.reverse int) 123456"654321"
replaced :: Text -> Text -> Format r a -> Format r a Source #
Take a formatter and replace the given needle with the given replacement in its output.
>>>format (replaced "Bruce" "<redacted>" stext) "Bruce replied that Bruce's name was, in fact, '<redacted>'.""<redacted> replied that <redacted>'s name was, in fact, '<redacted>'."
uppercased :: Format r a -> Format r a Source #
Convert any letters in the output of the given formatter to upper-case.
>>>format (uppercased text) "I'm not shouting, you're shouting.""I'M NOT SHOUTING, YOU'RE SHOUTING."
lowercased :: Format r a -> Format r a Source #
Convert any letters in the output of the given formatter to lower-case.
>>>format (lowercased text) "Cd SrC/; Rm -Rf *""cd src/; rm -rf *"
titlecased :: Format r a -> Format r a Source #
Convert the formatted string to title case, or something like it:
>>>format (titlecased string) "the life of brian""The Life Of Brian"
ltruncated :: Int64 -> Format r a -> Format r a Source #
Truncate the formatted string at the end so that it is no more than the given number of characters in length, placing an ellipsis at the end such that it does not exceed this length.
>>>format (truncated 5 text) "hello""hello"
>>>format (truncated 5 text) "hellos""he..."
ctruncated :: Int64 -> Int64 -> Format r a -> Format r a Source #
Truncate the formatted string in the center, leaving the given number of characters at the start and end, and placing an ellipsis in between. The length will be no longer than `start + end + 3` characters long.
>>>format (ctruncated 15 4 text) "The quick brown fox jumps over the lazy dog.""The quick brown...dog."
>>>format (ctruncated 15 4 text) "The quick brown fox""The quick brown fox"
rtruncated :: Int64 -> Format r a -> Format r a Source #
Truncate the formatted string at the start so that it is no more than the given number of characters in length, placing an ellipsis at the start such that it does not exceed this length.
>>>format (rtruncated 5 text) "hello""hello"
>>>format (rtruncated 5 text) "hellos""...os"
lpadded :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r) Source #
Pad the formatted string on the left with the given character to give it the given minimum width:
>>>format (lpadded 7 ' ' int) 1" 1"
>>>format (lpadded 7 ' ' int) 123456789"123456789"
rpadded :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r) Source #
Pad the formatted string on the right with the given character to give it the given minimum width:
>>>format (rpadded 7 ' ' int) 1"1 "
cpadded :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r) Source #
Pad the formatted string on the left and right with the given character to center it, giving it the given minimum width:
>>>format (cpadded 7 ' ' int) 1" 1 "
lfixed :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r) Source #
Format the item with a fixed width, padding with the given character on the left to extend, adding an ellipsis on the right to shorten:
>>>format (lfixed 10 ' ' int) 123"123 "
>>>format (lfixed 10 ' ' int) 1234567890"1234567890"
>>>format (lfixed 10 ' ' int) 123456789012345"1234567..."
rfixed :: Int64 -> Char -> Format r (a -> r) -> Format r (a -> r) Source #
Format the item with a fixed width, padding with the given character on the right to extend, adding an ellipsis on the right to shorten:
>>>format (rfixed 10 ' ' int) 123" 123"
>>>format (rfixed 10 ' ' int) 1234567890"1234567890"
>>>format (rfixed 10 ' ' int) 123456789012345"...9012345"
cfixed :: Int64 -> Int64 -> Char -> Format r (a -> r) -> Format r (a -> r) Source #
Format the item with a fixed width, padding with the given character on either side to extend, adding an ellipsis in the center to shorten.
The total length will be `l + r + 3` characters.
>>>format (cfixed 4 3 ' ' int) 123" 123 "
>>>format (cfixed 4 3 ' ' int) 1234567890"1234567890"
>>>format (cfixed 4 3 ' ' int) 123456789012345"1234...345"
Wrapping formatted strings
prefixed :: Builder -> Format r a -> Format r a Source #
Add the given prefix to the formatted item:
>>>format ("The answer is: " % prefixed "wait for it... " int) 42"The answer is: wait for it... 42"
>>>fprint (unlined (indented 4 (prefixed "- " int))) [1, 2, 3]- 1 - 2 - 3
surrounded :: Builder -> Format r a -> Format r a Source #
Surround the output string with the given string:
>>>format (surrounded "***" string) "glue""***glue***"
enclosed :: Builder -> Builder -> Format r a -> Format r a Source #
Enclose the output string with the given strings:
>>>format (enclosed "<!--" "-->" text) "an html comment""<!--an html comment-->"
squoted :: Format r a -> Format r a Source #
Add single quotes around the formatted item:
>>>let obj = Just Nothing in format ("The object is: " % squoted shown % ".") obj"The object is: 'Just Nothing'."
dquoted :: Format r a -> Format r a Source #
Add double quotes around the formatted item:
>>>fprintLn ("He said it was based on " % dquoted stext % ".") "science"He said it was based on "science".
parenthesised :: Format r a -> Format r a Source #
Add parentheses around the formatted item:
>>>format ("We found " % parenthesised int % " discrepancies.") 17"We found (17) discrepancies."
>>>fprintLn (took 5 (list (parenthesised int))) [1..][(1), (2), (3), (4), (5)]
squared :: Format r a -> Format r a Source #
Add square brackets around the formatted item:
>>>format (squared int) 7"[7]"
braced :: Format r a -> Format r a Source #
Add curly brackets around the formatted item:
>>>format ("\\begin" % braced text) "section""\\begin{section}"
angled :: Format r a -> Format r a Source #
Add angle brackets around the formatted item:
>>>format (angled int) 7"<7>"
>>>format (list (angled text)) ["html", "head", "title", "body", "div", "span"]"[<html>, <head>, <title>, <body>, <div>, <span>]"
backticked :: Format r a -> Format r a Source #
Add backticks around the formatted item:
>>>format ("Be sure to run " % backticked builder % " as root.") ":(){:|:&};:""Be sure to run `:(){:|:&};:` as root."
Changing indentation
indented :: Int -> Format r a -> Format r a Source #
Insert the given number of spaces at the start of the rendered text:
>>>format (indented 4 int) 7" 7"
Note that this only indents the first line of a multi-line string.
 To indent all lines see reindented.
indentedLines :: Foldable t => Int -> Format Builder (a -> Builder) -> Format r (t a -> r) Source #
Format a list of items, placing one per line, indented by the given number of spaces.
>>>fprintLn ("The lucky numbers are:\n" % indentedLines 4 int) [7, 13, 1, 42]The lucky numbers are: 7 13 1 42
reindented :: Int -> Format r a -> Format r a Source #
Indent each line of the formatted string by the given number of spaces:
>>>fprint (reindented 2 text) "one\ntwo\nthree"one two three
Numerical adapters
roundedTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r) Source #
Take a fractional number and round it before formatting it as the given Format:
>>>format (roundedTo int) 6.66"7">>>format (list (roundedTo int)) [10.66, 6.66, 1.0, 3.4]"[11, 7, 1, 3]"
Note: the type variable f will almost always be 'Format r', so the type of this function can be thought of as:
roundedTo :: (Integral i, RealFrac d) => Format r (i -> r) -> Format r (d -> r)
truncatedTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r) Source #
Take a fractional number and truncate it before formatting it as the given Format:
>>>format (truncatedTo int) 6.66"6">>>format (list (truncatedTo int)) [10.66, 6.66, 1.0, 3.4]"[10, 6, 1, 3]"
Note: the type variable f will almost always be 'Format r', so the type of this function can be thought of as:
truncatedTo :: (Integral i, RealFrac d) => Format r (i -> r) -> Format r (d -> r)
ceilingedTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r) Source #
Take a fractional number and ceiling it before formatting it as the given Format:
>>>format (ceilingedTo int) 6.66"7">>>format (list (ceilingedTo int)) [10.66, 6.66, 1.0, 3.4]"[11, 7, 1, 4]"
Note: the type variable f will almost always be 'Format r', so the type of this function can be thought of as:
ceilingedTo :: (Integral i, RealFrac d) => Format r (i -> r) -> Format r (d -> r)
flooredTo :: (Integral i, RealFrac d, Functor f) => f (i -> r) -> f (d -> r) Source #
Take a fractional number and floor it before formatting it as the given Format:
>>>format (flooredTo int) 6.66"6">>>format (list (flooredTo int)) [10.66, 6.66, 1.0, 3.4]"[10, 6, 1, 3]"
Note: the type variable f will almost always be 'Format r', so the type of this function can be thought of as:
flooredTo :: (Integral i, RealFrac d) => Format r (i -> r) -> Format r (d -> r)
Structure formatting
viewed :: ((a -> Const a b) -> s -> Const a t) -> Format r (a -> r) -> Format r (s -> r) Source #
Use the given lens to view an item, formatting it with the given formatter.
You can think of this as having the type:
viewed::Lens's a -> Format r (a -> r) -> Format r (s -> r)
>>>format (viewed _1 int) (1, "hello")"1"
This is useful when combined with the Monoid instance for Format, because it allows us to give a data structure as an argument only once, and deconstruct it with the formatters:
data Person = Person
  { _personName :: Text
  , _personAge :: Int
  }
makeLenses ''Person
me :: Person
me = Person Alex 38
format ("The person's name is " % squoted (viewed personName text) % ", and their age is " <> viewed personAge int) me
"The person's name is Alex, and their age is 38"
accessed :: (s -> a) -> Format r (a -> r) -> Format r (s -> r) Source #
Access an element of the structure and format it with the given formatter.
>>>format (accessed fst int) (1, "hello")"1"
Repeating the example from viewed:
format ("The person's name is " % squoted (accessed _personName text) % ", and their age is " <> accessed _personAge int) me
 "The person's name is Alex, and their age is 38"
Fixed-width number formatting
binPrefix :: Integral a => Int64 -> Format r (a -> r) Source #
Render an integer using binary notation with a leading 0b, padding with zeroes to the given width:
>>>format (binPrefix 16) 4097"0b0001000000000001"