logfmt-0.0.1: Formatting
Safe HaskellNone
LanguageHaskell2010

Data.Fmt

Synopsis

Documentation

type Term = IO () #

Type

newtype Fmt m a b #

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"

Constructors

Fmt 

Fields

Instances

Instances details
Monoid m => Arrow (Fmt m) # 
Instance details

Defined in Data.Fmt

Methods

arr :: (b -> c) -> Fmt m b c #

first :: Fmt m b c -> Fmt m (b, d) (c, d) #

second :: Fmt m b c -> Fmt m (d, b) (d, c) #

(***) :: Fmt m b c -> Fmt m b' c' -> Fmt m (b, b') (c, c') #

(&&&) :: Fmt m b c -> Fmt m b c' -> Fmt m b (c, c') #

Cochoice (Fmt m) # 
Instance details

Defined in Data.Fmt

Methods

unleft :: Fmt m (Either a d) (Either b d) -> Fmt m a b

unright :: Fmt m (Either d a) (Either d b) -> Fmt m a b

Closed (Fmt m) # 
Instance details

Defined in Data.Fmt

Methods

closed :: Fmt m a b -> Fmt m (x -> a) (x -> b)

Costrong (Fmt m) # 
Instance details

Defined in Data.Fmt

Methods

unfirst :: Fmt m (a, d) (b, d) -> Fmt m a b

unsecond :: Fmt m (d, a) (d, b) -> Fmt m a b

Monoid m => Strong (Fmt m) # 
Instance details

Defined in Data.Fmt

Methods

first' :: Fmt m a b -> Fmt m (a, c) (b, c)

second' :: Fmt m a b -> Fmt m (c, a) (c, b)

Profunctor (Fmt m) # 
Instance details

Defined in Data.Fmt

Methods

dimap :: (a -> b) -> (c -> d) -> Fmt m b c -> Fmt m a d

lmap :: (a -> b) -> Fmt m b c -> Fmt m a c

rmap :: (b -> c) -> Fmt m a b -> Fmt m a c

(#.) :: forall a b c q. Coercible c b => q b c -> Fmt m a b -> Fmt m a c

(.#) :: forall a b c q. Coercible b a => Fmt m b c -> q a b -> Fmt m a c

Element (Html a) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: Html a -> Attr -> Html a #

Monoid m => Category (Fmt m :: Type -> Type -> Type) # 
Instance details

Defined in Data.Fmt

Methods

id :: forall (a :: k). Fmt m a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Fmt m b c -> Fmt m a b -> Fmt m a c #

Monad (Fmt m a) # 
Instance details

Defined in Data.Fmt

Methods

(>>=) :: Fmt m a a0 -> (a0 -> Fmt m a b) -> Fmt m a b #

(>>) :: Fmt m a a0 -> Fmt m a b -> Fmt m a b #

return :: a0 -> Fmt m a a0 #

Functor (Fmt m a) # 
Instance details

Defined in Data.Fmt

Methods

fmap :: (a0 -> b) -> Fmt m a a0 -> Fmt m a b #

(<$) :: a0 -> Fmt m a b -> Fmt m a a0 #

Applicative (Fmt m a) # 
Instance details

Defined in Data.Fmt

Methods

pure :: a0 -> Fmt m a a0 #

(<*>) :: Fmt m a (a0 -> b) -> Fmt m a a0 -> Fmt m a b #

liftA2 :: (a0 -> b -> c) -> Fmt m a a0 -> Fmt m a b -> Fmt m a c #

(*>) :: Fmt m a a0 -> Fmt m a b -> Fmt m a b #

(<*) :: Fmt m a a0 -> Fmt m a b -> Fmt m a a0 #

Element (Html a -> Html b) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: (Html a -> Html b) -> Attr -> Html a -> Html b #

(IsString s, Show a) => Show (Fmt LogStr s a) # 
Instance details

Defined in Data.Fmt

Methods

showsPrec :: Int -> Fmt LogStr s a -> ShowS #

show :: Fmt LogStr s a -> String #

showList :: [Fmt LogStr s a] -> ShowS #

(IsString m, a ~ b) => IsString (Fmt m a b) # 
Instance details

Defined in Data.Fmt

Methods

fromString :: String -> Fmt m a b #

Semigroup m => Semigroup (Fmt1 m s a) # 
Instance details

Defined in Data.Fmt

Methods

(<>) :: Fmt1 m s a -> Fmt1 m s a -> Fmt1 m s a #

sconcat :: NonEmpty (Fmt1 m s a) -> Fmt1 m s a #

stimes :: Integral b => b -> Fmt1 m s a -> Fmt1 m s a #

Monoid m => Monoid (Fmt1 m s a) # 
Instance details

Defined in Data.Fmt

Methods

mempty :: Fmt1 m s a #

mappend :: Fmt1 m s a -> Fmt1 m s a -> Fmt1 m s a #

mconcat :: [Fmt1 m s a] -> 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>"

printf :: Fmt LogStr Term a -> a #

Run a formatter and print out the text to stdout.

runFmt :: Fmt m m a -> a #

Run a Fmt.

runLogFmt :: IsString s => Fmt LogStr s a -> a #

Run a LogFmt.

Fmt

fmt :: m -> Fmt m a a #

Format a constant value of type m.

logFmt :: ToLogStr m => m -> Fmt LogStr a a #

Format a constant value of type m.

(%) :: Semigroup m => Fmt m b c -> Fmt m a b -> Fmt m a c infixr 0 #

Concatenate two formatters.

apply :: Fmt1 m s m -> Fmt m s a -> Fmt m s a #

Apply a Fmt1 to a Fmt.

bind :: Fmt m a1 b -> (m -> Fmt m a2 a1) -> Fmt m a2 b #

Indexed bind.

cat :: (Monoid m, Foldable f) => f (Fmt m a a) -> Fmt m a a #

Concatenate a collection of formatters.

refmt :: (m1 -> m2) -> Fmt m1 a b -> Fmt m2 a b #

Map over the the formatting Monoid.

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"

Fmt1

type Fmt1 m s a = Fmt m s (a -> s) #

A unary higher-order formatter.

 Fmt1 m s a ~ (m -> s) -> a -> s

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

fmt1 :: (a -> m) -> Fmt1 m s a #

Format a value of type a using a function of type a -> m.

 runFmt . fmt1 :: (a -> m) -> a -> m

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 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"
cat1With unlines :: Foldable f => Fmt1 LogStr String a -> Fmt1 LogStr s (f a)
cat1With unlines :: Foldable f => Fmt1 LogStr Text a -> Fmt1 LogStr s (f a)
cat1With unlines :: Foldable f => Fmt1 LogStr ByteString a -> Fmt1 LogStr s (f a)
cat1With $ intercalate " " :: Foldable f => Fmt1 LogStr String a -> Fmt1 LogStr s (f a)
cat1With $ intercalate " " :: Foldable f => Fmt1 LogStr Text a -> Fmt1 LogStr s (f a)
cat1With $ intercalate " " :: Foldable f => Fmt1 LogStr ByteString 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 #

Turn a text-splitting function into a formatting combinator.

 split1With hsep :: (Traversable f, ToLogStr msg) => (ByteString -> f msg) -> Fmt LogStr s a -> Fmt LogStr s a
 split1With vsep :: (Traversable f, ToLogStr msg) => (ByteString -> f msg) -> Fmt LogStr s a -> Fmt LogStr s a
 split1With list1 :: (Traversable f, ToLogStr msg) => (ByteString -> f msg) -> Fmt LogStr s a -> Fmt LogStr s 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 :: Html LogStr
 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
 

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>"

toHtml :: ToLogStr s => s -> Html a #

comment :: ToLogStr s => s -> Html a #

newtype Attr #

Type for an attribute.

Constructors

Attr (forall a. Html a -> Html a) 

Instances

Instances details
Semigroup Attr # 
Instance details

Defined in Data.Fmt

Methods

(<>) :: Attr -> Attr -> Attr #

sconcat :: NonEmpty Attr -> Attr #

stimes :: Integral b => b -> Attr -> Attr #

Monoid Attr # 
Instance details

Defined in Data.Fmt

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

class Element html where #

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

(!) :: html -> Attr -> html #

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>

Instances

Instances details
Element (Html a) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: Html a -> Attr -> Html a #

Element (Html a -> Html b) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: (Html a -> Html b) -> Attr -> Html a -> Html b #

(!?) :: 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.

 indentEach n = vsep . indent n
>>> 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

suffix :: Semigroup m => m -> Fmt m a b -> Fmt m a b #

Add the given suffix to the formatted item.

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-->"

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 #

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
    ]
}

yamlMap :: (ToLogStr k, ToLogStr v, IsList map, Item map ~ (k, v)) => Fmt1 LogStr s map #

Re-exports

data LogStr #

Instances

Instances details
Eq LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

(==) :: LogStr -> LogStr -> Bool #

(/=) :: LogStr -> LogStr -> Bool #

Show LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

IsString LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

fromString :: String -> LogStr #

Semigroup LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

Monoid LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

ToLogStr LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: LogStr -> LogStr #

Element (Html a) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: Html a -> Attr -> Html a #

Element (Html a -> Html b) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: (Html a -> Html b) -> Attr -> Html a -> Html b #

(IsString s, Show a) => Show (Fmt LogStr s a) # 
Instance details

Defined in Data.Fmt

Methods

showsPrec :: Int -> Fmt LogStr s a -> ShowS #

show :: Fmt LogStr s a -> String #

showList :: [Fmt LogStr s a] -> ShowS #

class ToLogStr msg where #

Methods

toLogStr :: msg -> LogStr #

Instances

Instances details
ToLogStr Double 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Double -> LogStr #

ToLogStr Float 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Float -> LogStr #

ToLogStr Int 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Int -> LogStr #

ToLogStr Int8 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Int8 -> LogStr #

ToLogStr Int16 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Int16 -> LogStr #

ToLogStr Int32 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Int32 -> LogStr #

ToLogStr Int64 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Int64 -> LogStr #

ToLogStr Integer 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Integer -> LogStr #

ToLogStr Word 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Word -> LogStr #

ToLogStr Word8 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Word8 -> LogStr #

ToLogStr Word16 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Word16 -> LogStr #

ToLogStr Word32 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Word32 -> LogStr #

ToLogStr Word64 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Word64 -> LogStr #

ToLogStr String 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: String -> LogStr #

ToLogStr ByteString 
Instance details

Defined in System.Log.FastLogger.LogStr

ToLogStr ByteString 
Instance details

Defined in System.Log.FastLogger.LogStr

ToLogStr Builder 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Builder -> LogStr #

ToLogStr Text 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Text -> LogStr #

ToLogStr Text 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: Text -> LogStr #

ToLogStr LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

toLogStr :: LogStr -> LogStr #

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Methods

fromString :: String -> a #

Instances

Instances details
IsString ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString LogStr 
Instance details

Defined in System.Log.FastLogger.LogStr

Methods

fromString :: String -> LogStr #

a ~ Char => IsString [a]

(a ~ Char) context was introduced in 4.9.0.0

Since: base-2.1

Instance details

Defined in Data.String

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Identity a #

IsString a => IsString (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Const a b #

IsString a => IsString (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

fromString :: String -> Tagged s a #

(IsString m, a ~ b) => IsString (Fmt m a b) # 
Instance details

Defined in Data.Fmt

Methods

fromString :: String -> Fmt m a b #