| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Text.Format
Description
Format string with named args
-- Named args
"My name is {name}, I am {age} years old" ~~ ("name" ~% "Joe") ~~ ("age" ~% 24) ≡ "My name is Joe, I am 24 years old"
-- Arg can have default value
"{var:x} = {val:10}" ~~ ("var" ~% y) ≡ "y = 10"
-- Numeric position can be used
"{0} {1} {0}" ~~ "foo" ~~ "bar" ≡ "foo bar foo"
-- Positions can be omitted
"{} {}" ~~ "foo" ~~ 10 ≡ "foo 10"
-- Double braces to escape them
"{} and {{}}" ~~ 10 ≡ "10 and {}"Synopsis
- data FormattedPart = FormattedPart {}
- newtype Formatted = Formatted {}
- withFlags :: String -> [String] -> Formatted
- data FormatArg
- data Format = Format {
- formatString :: String
- formatArgs :: [FormatArg]
- data Formatter = Formatter {}
- prebuild :: Format -> Formatted
- build :: Format -> Formatted
- getNamedArguments :: Format -> [String]
- class Formattable a where
- class Hole a where
- fmt :: Formattable a => a -> FormatArg
- class FormatResult r where
- format :: FormatResult r => String -> r
- formats :: FormatResult r => String -> [FormatArg] -> r
- (~~) :: (Hole a, FormatResult r) => Format -> a -> r
- (~%) :: Formattable a => String -> a -> FormatArg
- module Text.Format.Flags
Documentation
data FormattedPart Source #
Constructors
| FormattedPart | |
Fields | |
Instances
| Eq FormattedPart Source # | |
Defined in Text.Format Methods (==) :: FormattedPart -> FormattedPart -> Bool # (/=) :: FormattedPart -> FormattedPart -> Bool # | |
| Ord FormattedPart Source # | |
Defined in Text.Format Methods compare :: FormattedPart -> FormattedPart -> Ordering # (<) :: FormattedPart -> FormattedPart -> Bool # (<=) :: FormattedPart -> FormattedPart -> Bool # (>) :: FormattedPart -> FormattedPart -> Bool # (>=) :: FormattedPart -> FormattedPart -> Bool # max :: FormattedPart -> FormattedPart -> FormattedPart # min :: FormattedPart -> FormattedPart -> FormattedPart # | |
| Show FormattedPart Source # | |
Defined in Text.Format Methods showsPrec :: Int -> FormattedPart -> ShowS # show :: FormattedPart -> String # showList :: [FormattedPart] -> ShowS # | |
| IsString FormattedPart Source # | |
Defined in Text.Format Methods fromString :: String -> FormattedPart # | |
Constructors
| Formatted | |
Fields | |
Instances
| Eq Formatted Source # | |
| Ord Formatted Source # | |
| Show Formatted Source # | |
| IsString Formatted Source # | |
Defined in Text.Format Methods fromString :: String -> Formatted # | |
| Semigroup Formatted Source # | |
| Monoid Formatted Source # | |
| FormatResult Formatted Source # | |
Defined in Text.Format Methods formatResult :: Format -> Formatted Source # | |
| Hole Formatted Source # | |
Constructors
| Format | |
Fields
| |
Instances
| Show Format Source # | |
| IsString Format Source # | |
Defined in Text.Format Methods fromString :: String -> Format # | |
| FormatResult Format Source # | |
Defined in Text.Format Methods formatResult :: Format -> Format Source # | |
Constructors
| Formatter | |
Fields
| |
Instances
| Read Formatter Source # | |
| Show Formatter Source # | |
| Formattable Formatter Source # | |
Defined in Text.Format Methods formattable :: Formatter -> FormatFlags -> Formatted Source # | |
getNamedArguments :: Format -> [String] Source #
class Formattable a where Source #
Formattable class, by default using show
Methods
formattable :: a -> FormatFlags -> Formatted Source #
formattable :: Show a => a -> FormatFlags -> Formatted Source #
Instances
Minimal complete definition
fmt :: Formattable a => a -> FormatArg Source #
class FormatResult r where Source #
Minimal complete definition
Methods
formatResult :: Format -> r Source #
Instances
| IsString s => FormatResult s Source # | |
Defined in Text.Format Methods formatResult :: Format -> s Source # | |
| FormatResult String Source # | |
Defined in Text.Format Methods formatResult :: Format -> String Source # | |
| FormatResult Format Source # | |
Defined in Text.Format Methods formatResult :: Format -> Format Source # | |
| FormatResult Formatted Source # | |
Defined in Text.Format Methods formatResult :: Format -> Formatted Source # | |
format :: FormatResult r => String -> r Source #
module Text.Format.Flags