| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Fmt
Synopsis
- type Term = IO ()
- type LogFmt = Fmt LogStr
- newtype Fmt m a b = Fmt {
- unFmt :: (m -> a) -> b
- spr :: IsString s => Fmt LogStr s m -> Fmt m a a
- printf :: Fmt LogStr Term a -> a
- runFmt :: Fmt m m a -> a
- runLogFmt :: IsString s => Fmt LogStr s a -> a
- fmt :: m -> Fmt m a a
- logFmt :: ToLogStr m => m -> Fmt LogStr a a
- (%) :: Semigroup m => Fmt m b c -> Fmt m a b -> Fmt m a c
- apply :: Fmt1 m s m -> Fmt m s a -> Fmt m s a
- bind :: Fmt m a1 b -> (m -> Fmt m a2 a1) -> Fmt m a2 b
- cat :: (Monoid m, Foldable f) => f (Fmt m a a) -> Fmt m a a
- refmt :: (m1 -> m2) -> Fmt m1 a b -> Fmt m2 a b
- replace1 :: ByteString -> Fmt LogStr a a -> Fmt LogStr a b -> Fmt LogStr a b
- splitWith :: (ByteString -> (ByteString, ByteString)) -> (ByteString -> ByteString -> Fmt LogStr a2 a1) -> Fmt LogStr a1 b -> Fmt LogStr a2 b
- type Fmt1 m s a = Fmt m s (a -> s)
- type Fmt2 m s a b = Fmt m s (a -> b -> s)
- fmt1 :: (a -> m) -> Fmt1 m s a
- fmt2 :: (a -> b -> m) -> Fmt2 m s a b
- fmt1_ :: Fmt m a a -> Fmt1 m a b
- fmt2_ :: Fmt m a a -> Fmt2 m a b c
- (.%) :: Semigroup m => Fmt1 m s a -> Fmt1 m s a -> Fmt1 m s a
- cat1 :: (Monoid m, Foldable f) => Fmt1 m m a -> Fmt1 m s (f a)
- cat1With :: (Foldable f, ToLogStr str, IsString str) => ([str] -> str) -> Fmt1 LogStr str a -> Fmt1 LogStr s (f a)
- split1With :: (Traversable f, ToLogStr str) => (Fmt1 m s_ m -> Fmt1 m m (f LogStr)) -> (ByteString -> f str) -> Fmt LogStr s a -> Fmt m s a
- type Html a = Fmt LogStr a a
- toHtml :: ToLogStr s => s -> Html a
- comment :: ToLogStr s => s -> Html a
- newtype Attr = Attr (forall a. Html a -> Html a)
- class Element html where
- (!?) :: Element html => html -> (Bool, Attr) -> html
- hsep :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a)
- vsep :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a)
- hang :: Foldable f => Int -> Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a)
- indent :: (IsString m, Semigroup m) => Int -> Fmt m a b -> Fmt m a b
- prefix :: Semigroup m => m -> Fmt m a b -> Fmt m a b
- suffix :: Semigroup m => m -> Fmt m a b -> Fmt m a b
- enclose :: Semigroup m => Fmt m b2 c -> Fmt m a b1 -> Fmt m b1 b2 -> Fmt m a c
- tuple :: (Semigroup m, IsString m) => Fmt m b c -> Fmt m a b -> Fmt m a c
- quotes :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b
- quotes' :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b
- parens :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b
- braces :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b
- brackets :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b
- backticks :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b
- left1 :: IsString m => Fmt1 m m a -> Fmt1 m s (Either a b)
- right1 :: IsString m => Fmt1 m m b -> Fmt1 m s (Either a b)
- either1 :: Fmt1 m m a -> Fmt1 m m b -> Fmt1 m s (Either a b)
- maybe1 :: m -> Fmt1 m m a -> Fmt1 m s (Maybe a)
- list1 :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a)
- jsonList :: (Foldable f, ToLogStr a) => Fmt1 LogStr s (f a)
- yamlList :: (Foldable f, ToLogStr a) => Fmt1 LogStr s (f a)
- jsonMap :: (ToLogStr k, IsList map, Item map ~ (k, ByteString)) => Fmt1 LogStr s map
- yamlMap :: (ToLogStr k, ToLogStr v, IsList map, Item map ~ (k, v)) => Fmt1 LogStr s map
- data LogStr
- fromLogStr :: LogStr -> ByteString
- class ToLogStr msg where
- class IsString a where
- fromString :: String -> a
Documentation
Type
A formatter, implemented as an indexed continuation
When you construct formatters the first type
parameter, r, will remain polymorphic. The second type
parameter, a, will change to reflect the types of the data that
will be formatted. For example, in
person :: Fmt2 ByteString Int person = "Person's name is " % t % ", age is " % d
the first type parameter remains polymorphic, and the second type
parameter is ByteString -> Int -> r, which indicates that it formats a
ByteString and an Int.
When you run the formatter, for example with format, you provide
the arguments and they will be formatted into a string.
>>>format ("This person's name is " % s % ", their age is " % d) "Anne" 22"This person's name is Anne, their age is 22"
Instances
| Monoid m => Arrow (Fmt m) # | |
| Cochoice (Fmt m) # | |
| Closed (Fmt m) # | |
| Costrong (Fmt m) # | |
| Monoid m => Strong (Fmt m) # | |
| Profunctor (Fmt m) # | |
Defined in Data.Fmt | |
| Element (Html a) # | |
| Monoid m => Category (Fmt m :: Type -> Type -> Type) # | |
| Monad (Fmt m a) # | |
| Functor (Fmt m a) # | |
| Applicative (Fmt m a) # | |
| Element (Html a -> Html b) # | |
| (IsString s, Show a) => Show (Fmt LogStr s a) # | |
| (IsString m, a ~ b) => IsString (Fmt m a b) # | |
Defined in Data.Fmt Methods fromString :: String -> Fmt m a b # | |
| Semigroup m => Semigroup (Fmt1 m s a) # | |
| Monoid m => Monoid (Fmt1 m s a) # | |
spr :: IsString s => Fmt LogStr s m -> Fmt m a a #
Run a monadic formatting expression.
Like the method of PrintfType, spr executes the formatting
commands contained in the expression and returns the result as a monadic
variable.
For example, note that the li tag repeats, while the
ul tag does not:
>>>:{let contact = p "You can reach me at" % ul . spr . li $ do c1 <- a ! href @String "https://example.com" $ "Website" c2 <- a ! href @String "mailto:cmk@example.com" $ "Email" pure $ c1 <> c2 in runLogStr contact :} "<p>You can reach me at</p><ul><li><a href=\"https://foo.com\">Web</a></li><li><a href=\"mailto:cmk@foo.com\">Email</a></li></ul>"
Fmt
cat :: (Monoid m, Foldable f) => f (Fmt m a a) -> Fmt m a a #
Concatenate a collection of formatters.
replace1 :: ByteString -> Fmt LogStr a a -> Fmt LogStr a b -> Fmt LogStr a b #
Replace one occurance of a search term.
replace1 "bar" "foo" "foobarbaz"
"foofoobaz"
splitWith :: (ByteString -> (ByteString, ByteString)) -> (ByteString -> ByteString -> Fmt LogStr a2 a1) -> Fmt LogStr a1 b -> Fmt LogStr a2 b #
Fmt1
type Fmt2 m s a b = Fmt m s (a -> b -> s) #
A binary higher-order formatter.
Fmt2 m s a b ~ (m -> s) -> a -> b -> s(.%) :: Semigroup m => Fmt1 m s a -> Fmt1 m s a -> Fmt1 m s a infixr 6 #
Concatenate two formatters, applying both to the same input.
cat1 :: (Monoid m, Foldable f) => Fmt1 m m a -> Fmt1 m s (f a) #
Format each value in a list and concatenate them all:
>>>runFmt (cat1 (s % " ")) ["one", "two", "three"]"one two three "
cat1With :: (Foldable f, ToLogStr str, IsString str) => ([str] -> str) -> Fmt1 LogStr str a -> Fmt1 LogStr s (f a) #
Use the given text-joining function to join together the individually rendered items of a list.
>>>runLogFmt (cat1With (mconcat . reverse) d) [123, 456, 789]"789456123"
cat1Withunlines::Foldablef =>Fmt1LogStrStringa ->Fmt1LogStrs (f a)cat1Withunlines::Foldablef =>Fmt1LogStrTexta ->Fmt1LogStrs (f a)cat1Withunlines::Foldablef =>Fmt1LogStrByteStringa ->Fmt1LogStrs (f a)cat1With$intercalate" " ::Foldablef =>Fmt1LogStrStringa ->Fmt1LogStrs (f a)cat1With$intercalate" " ::Foldablef =>Fmt1LogStrTexta ->Fmt1LogStrs (f a)cat1With$intercalate" " ::Foldablef =>Fmt1LogStrByteStringa ->Fmt1LogStrs (f a)
split1With :: (Traversable f, ToLogStr str) => (Fmt1 m s_ m -> Fmt1 m m (f LogStr)) -> (ByteString -> f str) -> Fmt LogStr s a -> Fmt m s a #
Turn a text-splitting function into a formatting combinator.
split1Withhsep:: (Traversablef,ToLogStrmsg) => (ByteString-> f msg) ->FmtLogStrs a ->FmtLogStrs asplit1Withvsep:: (Traversablef,ToLogStrmsg) => (ByteString-> f msg) ->FmtLogStrs a ->FmtLogStrs asplit1Withlist1:: (Traversablef,ToLogStrmsg) => (ByteString-> f msg) ->FmtLogStrs a ->FmtLogStrs a
>>>commas = reverse . fmap BL.reverse . BL.chunksOf 3 . BL.reverse>>>dollars = prefix "$" . split1With commas (intercalate ",") . reversed>>>runLogFmt (dollars d) 1234567890"$1,234,567,890">>>printf (split1With (BL.splitOn ",") vsep t) "one,two,three"one two three>>>printf (split1With (BL.splitOn ",") (indentEach 4) t) "one,two,three"one two three
Html
type Html a = Fmt LogStr a a #
Format HTML
For example:
contact ::HtmlLogStrcontact =p"You can reach me at"%ul.spr.li$ do c1 <-a!hrefString "https://example.com" $ Website c2 <-String "mailto:cmk@example.com" $ Emaila!hrefpure$ c1<>c2
generates the following output:
"<p>You can reach me at</p><ul><li><a href=\"https://foo.com\">Web</a></li><li><a href=\"mailto:cmk@foo.com\">Email</a></li></ul>"
Type for an attribute.
Apply an attribute to an HTML tag.
The interface is similar to https://hackage.haskell.org/package/blaze-builder.
You should not define your own instances of this class.
Methods
Apply an attribute to an element.
>>>printf $ img ! src "foo.png"<img src="foo.png" />
This can be used on nested elements as well:
>>>printf $ p ! style "float: right" $ "Hello!"<p style="float: right">Hello!</p>
(!?) :: Element html => html -> (Bool, Attr) -> html #
Shorthand for setting an attribute depending on a conditional.
Example:
p !? (isBig, A.class "big") $ "Hello"
Gives the same result as:
(if isBig then p ! A.class "big" else p) "Hello"
Formatting
hsep :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a) #
Format each value in a list with spaces in between:
>>>runLogFmt (hsep d) [1, 2, 3]"1 2 3"
vsep :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a) #
Format each value in a list, placing each on its own line:
>>>printf (vsep c) ['a'..'c']a b c
hang :: Foldable f => Int -> Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a) #
Format a list of items, placing one per line, indent by the given number of spaces.
indentEachn =vsep.indentn
>>>printf (split1With BL.lines (indentList 2) t) "one\ntwo\nthree"one two three>>>printf ("The lucky numbers are:\n" % indentList 2 d) [7, 13, 1, 42]The lucky numbers are: 7 13 1 42
indent :: (IsString m, Semigroup m) => Int -> Fmt m a b -> Fmt m a b #
Insert the given number of spaces at the start of the rendered text:
>>>runFmt (indent 4 d) 7" 7"
Note that this only indents the first line of a multi-line string.
To indent all lines see reindent.
prefix :: Semigroup m => m -> Fmt m a b -> Fmt m a b #
Add the given prefix to the formatted item:
>>>runLogFmt ("The answer is: " % prefix "wait for it... " d) 42"The answer is: wait for it... 42"
>>>printf (vsep (indent 4 (prefix "- " d))) [1, 2, 3]- 1 - 2 - 3
enclose :: Semigroup m => Fmt m b2 c -> Fmt m a b1 -> Fmt m b1 b2 -> Fmt m a c #
Enclose the output string with the given strings:
>>>runFmt (parens $ enclose v s ", ") 1 "two""(1, two)">>>runFmt (enclose (fmt "<!--") (fmt "-->") s) "an html comment""<!--an html comment-->"
quotes :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b #
Add double quotes around the formatted item:
Use this to escape a string:
>>>runFmt ("He said it was based on " % quotes t' % ".") "science"He said it was based on "science".
quotes' :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b #
Add single quotes around the formatted item:
>>>let obj = Just Nothing in format ("The object is: " % quotes' shown % ".") obj"The object is: 'Just Nothing'."
parens :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b #
Add parentheses around the formatted item:
>>>runFmt ("We found " % parens d % " discrepancies.") 17"We found (17) discrepancies."
>>>printf (get 5 (list1 (parens d))) [1..][(1), (2), (3), (4), (5)]
braces :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b #
Add braces around the formatted item:
>>>runFmt ("\\begin" % braces t) "section""\\begin{section}"
brackets :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b #
Add square brackets around the formatted item:
>>>runFmt (brackets d) 7"[7]"
backticks :: (Semigroup m, IsString m) => Fmt m a b -> Fmt m a b #
Add backticks around the formatted item:
>>>runLogFmt ("Be sure to run " % backticks builder % " as root.") ":(){:|:&};:""Be sure to run `:(){:|:&};:` as root."
Collections
left1 :: IsString m => Fmt1 m m a -> Fmt1 m s (Either a b) #
Render the value in a Left with the given formatter, rendering a Right as an empty string:
>>>runLogFmt (left1 text) (Left "bingo")"bingo"
>>>runLogFmt (left1 text) (Right 16)""
right1 :: IsString m => Fmt1 m m b -> Fmt1 m s (Either a b) #
Render the value in a Right with the given formatter, rendering a Left as an empty string:
>>>runLogFmt (right1 text) (Left 16)""
>>>runLogFmt (right1 text) (Right "bingo")"bingo"
either1 :: Fmt1 m m a -> Fmt1 m m b -> Fmt1 m s (Either a b) #
Render the value in an Either:
>>>runLogFmt (either1 text int) (Left "Error!""Error!"
>>>runLogFmt (either1 text int) (Right 69)"69"
maybe1 :: m -> Fmt1 m m a -> Fmt1 m s (Maybe a) #
Render a Maybe value either as a default (if Nothing) or using the given formatter:
>>>runLogFmt (maybe1 "Goodbye" text) Nothing"Goodbye"
>>>runLogFmt (maybe1 "Goodbye" text) (Just "Hello")"Hello"
list1 :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a) #
Add square brackets around the Foldable (e.g. a list), and separate each formatted item with a comma and space.
>>>runLogFmt (list1 s) ["one", "two", "three"]"[one, two, three]">>>printf (quotes $ list1 d) [1,2,3]["1", "2", "3"]>>>printf (quotes $ list1 s) ["one", "two", "three"]["one", "two", "three"]
jsonList :: (Foldable f, ToLogStr a) => Fmt1 LogStr s (f a) #
A JSON-style formatter for lists.
>>>printf jsonList [1,2,3][ 1 , 2 , 3 ]
Like yamlListF, it handles multiline elements well:
>>>fmt $ jsonListF ["hello\nworld", "foo\nbar\nquix"][ hello world , foo bar quix ]
yamlList :: (Foldable f, ToLogStr a) => Fmt1 LogStr s (f a) #
A multiline formatter for lists.
>>>printf (yamlList d) [1,2,3]- 1 - 2 - 3
Multi-line elements are indented correctly:
>>>printf (yamlList s) ["hello\nworld", "foo\nbar\nquix"]- hello world - foo bar quix
jsonMap :: (ToLogStr k, IsList map, Item map ~ (k, ByteString)) => Fmt1 LogStr s map #
A JSON-like map formatter; works for Map, HashMap, etc, and lists of pairs.
>>>fmt $ jsonMapF [("Odds", jsonListF [1,3]), ("Evens", jsonListF [2,4])]{ Odds: [ 1 , 3 ] , Evens: [ 2 , 4 ] }
Re-exports
Instances
| Eq LogStr | |
| Show LogStr | |
| IsString LogStr | |
Defined in System.Log.FastLogger.LogStr Methods fromString :: String -> LogStr # | |
| Semigroup LogStr | |
| Monoid LogStr | |
| ToLogStr LogStr | |
Defined in System.Log.FastLogger.LogStr | |
| Element (Html a) # | |
| Element (Html a -> Html b) # | |
| (IsString s, Show a) => Show (Fmt LogStr s a) # | |
fromLogStr :: LogStr -> ByteString #
Instances
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a #
Instances
| IsString ByteString | |
Defined in Data.ByteString.Lazy.Internal Methods fromString :: String -> ByteString # | |
| IsString ByteString | |
Defined in Data.ByteString.Internal Methods fromString :: String -> ByteString # | |
| IsString LogStr | |
Defined in System.Log.FastLogger.LogStr Methods fromString :: String -> LogStr # | |
| a ~ Char => IsString [a] |
Since: base-2.1 |
Defined in Data.String Methods fromString :: String -> [a] # | |
| IsString a => IsString (Identity a) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Identity a # | |
| IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Const a b # | |
| IsString a => IsString (Tagged s a) | |
Defined in Data.Tagged Methods fromString :: String -> Tagged s a # | |
| (IsString m, a ~ b) => IsString (Fmt m a b) # | |
Defined in Data.Fmt Methods fromString :: String -> Fmt m a b # | |