Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Ginger.StringFormatting.Python
Description
Python-style string formatting. See https://docs.python.org/3/library/string.html#formatstrings for spec.
Synopsis
- formatList :: Text -> [(Maybe Text, FormatArg)] -> Either String Text
- data FormattingGroup
- data FormatArg
- parseFormat :: Text -> Either String [FormatItem]
- renderFormat :: [FormatItem] -> [(Maybe Text, FormatArg)] -> Either String Text
- renderFormatItem :: Integer -> Vector FormatArg -> Map Text FormatArg -> FormatItem -> Either String Text
- data FormatItem
- data FormatField = FormatField {}
- data FieldName
- data FieldConversion
- data FieldZeroCoercion
- data FieldAlternateForm
- data FieldZeroPadding
- data FieldGrouping
- data FieldSign
- data FieldType
- data FieldAlign
- data OrDefault a
- fromDefault :: a -> OrDefault a -> a
- data FieldSpec = FieldSpec {
- fieldSpecAlign :: !(OrDefault FieldAlign)
- fieldSpecFill :: !(OrDefault Char)
- fieldSpecSign :: !FieldSign
- fieldSpecZeroCoercion :: !FieldZeroCoercion
- fieldSpecAlternateForm :: !FieldAlternateForm
- fieldSpecZeroPadding :: !FieldZeroPadding
- fieldSpecWidth :: !(OrDefault Int)
- fieldSpecGrouping :: !FieldGrouping
- fieldSpecPrecision :: !(OrDefault Int)
- fieldSpecType :: !FieldType
- defFieldSpec :: FieldSpec
Running
formatList :: Text -> [(Maybe Text, FormatArg)] -> Either String Text Source #
Apply format string, passing arguments as a list of optional key / value pairs. All arguments can be addressed positionally; those that have a key that is a valid identifier can also be addressed by that.
data FormattingGroup Source #
Formatting group; this determines the interpretation of formatting types
such as g
, which will behave differently depending on the type of
argument.
Constructors
FormatAsInt | |
FormatAsFloat | |
FormatAsString | |
FormatInvalid |
Instances
Formattable argument. We reduce potential inputs to a limited set of representations; it is the responsibility of the caller to convert whatever values they want to use as formatting args to this type.
Constructors
IntArg !Integer | Integer arguments |
FloatArg !Double | Floating-point arguments |
StringArg !Text | Any scalar argument that is best represented as a string |
ListArg !(Vector FormatArg) | List argument; cannot be formatted directly, but can be accessed
using index syntax ( |
DictArg !(Map Text FormatArg) | Dictionary argument; cannot be formatted directly, but can be accessed
using index syntax ( |
PolyArg | Polymorphic argument; may offer any of the available representations, allowing the formatter to pick the most appropriate one. |
Instances
Show FormatArg Source # | |
Eq FormatArg Source # | |
Ord FormatArg Source # | |
Defined in Language.Ginger.StringFormatting.Python |
Parsing
parseFormat :: Text -> Either String [FormatItem] Source #
Parse a format string.
Rendering
renderFormat :: [FormatItem] -> [(Maybe Text, FormatArg)] -> Either String Text Source #
Render a format string against the given arguments.
renderFormatItem :: Integer -> Vector FormatArg -> Map Text FormatArg -> FormatItem -> Either String Text Source #
Render a single formatting item using the provided arguments.
AST
data FormatItem Source #
Constructors
PlainFormatItem !Text | |
FieldFormatItem !FormatField |
Instances
Show FormatItem Source # | |
Defined in Language.Ginger.StringFormatting.Python Methods showsPrec :: Int -> FormatItem -> ShowS # show :: FormatItem -> String # showList :: [FormatItem] -> ShowS # | |
Eq FormatItem Source # | |
Defined in Language.Ginger.StringFormatting.Python |
data FormatField Source #
Constructors
FormatField | |
Fields |
Instances
Show FormatField Source # | |
Defined in Language.Ginger.StringFormatting.Python Methods showsPrec :: Int -> FormatField -> ShowS # show :: FormatField -> String # showList :: [FormatField] -> ShowS # | |
Eq FormatField Source # | |
Defined in Language.Ginger.StringFormatting.Python |
Constructors
FieldNameIdentifier !Text | |
FieldNameNumber !Integer | |
FieldNameAttrib !Text !FieldName | |
FieldNameKeyIndex !Text !FieldName | |
FieldNameNumIndex !Integer !FieldName |
data FieldConversion Source #
Constructors
FieldConvNone | |
FieldConvRepr | |
FieldConvString | |
FieldConvASCII |
Instances
Show FieldConversion Source # | |
Defined in Language.Ginger.StringFormatting.Python Methods showsPrec :: Int -> FieldConversion -> ShowS # show :: FieldConversion -> String # showList :: [FieldConversion] -> ShowS # | |
Eq FieldConversion Source # | |
Defined in Language.Ginger.StringFormatting.Python Methods (==) :: FieldConversion -> FieldConversion -> Bool # (/=) :: FieldConversion -> FieldConversion -> Bool # |
data FieldZeroCoercion Source #
Constructors
AllowNegativeZero | |
ForcePositiveZero |
Instances
data FieldAlternateForm Source #
Constructors
NormalForm | |
AlternateForm |
Instances
data FieldZeroPadding Source #
Constructors
NoZeroPadding | |
ZeroPadding |
Instances
data FieldGrouping Source #
Constructors
NoGrouping | |
GroupComma | |
GroupUnderscore |
Instances
Constructors
SignNegative | Default: show sign only when negative |
SignSpacePadded | Show sign if negative, add padding space if positive |
SignAlways | Always show sign |
Instances
Bounded FieldSign Source # | |
Enum FieldSign Source # | |
Defined in Language.Ginger.StringFormatting.Python Methods succ :: FieldSign -> FieldSign # pred :: FieldSign -> FieldSign # fromEnum :: FieldSign -> Int # enumFrom :: FieldSign -> [FieldSign] # enumFromThen :: FieldSign -> FieldSign -> [FieldSign] # enumFromTo :: FieldSign -> FieldSign -> [FieldSign] # enumFromThenTo :: FieldSign -> FieldSign -> FieldSign -> [FieldSign] # | |
Show FieldSign Source # | |
Eq FieldSign Source # | |
Ord FieldSign Source # | |
Defined in Language.Ginger.StringFormatting.Python |
Constructors
Instances
Bounded FieldType Source # | |
Enum FieldType Source # | |
Defined in Language.Ginger.StringFormatting.Python Methods succ :: FieldType -> FieldType # pred :: FieldType -> FieldType # fromEnum :: FieldType -> Int # enumFrom :: FieldType -> [FieldType] # enumFromThen :: FieldType -> FieldType -> [FieldType] # enumFromTo :: FieldType -> FieldType -> [FieldType] # enumFromThenTo :: FieldType -> FieldType -> FieldType -> [FieldType] # | |
Show FieldType Source # | |
Eq FieldType Source # | |
Ord FieldType Source # | |
Defined in Language.Ginger.StringFormatting.Python |
data FieldAlign Source #
Constructors
AlignLeft | |
AlignRight | |
AlignCenter | |
AlignZeroPad |
Instances
Instances
Functor OrDefault Source # | |
Show a => Show (OrDefault a) Source # | |
Eq a => Eq (OrDefault a) Source # | |
Ord a => Ord (OrDefault a) Source # | |
Defined in Language.Ginger.StringFormatting.Python |
fromDefault :: a -> OrDefault a -> a Source #
Constructors
FieldSpec | |
Fields
|