{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Language.Ginger.StringFormatting.Python
(
formatList
, FormattingGroup (..)
, FormatArg (..)
, parseFormat
, renderFormat
, renderFormatItem
, FormatItem (..)
, FormatField (..)
, FieldName (..)
, FieldConversion (..)
, FieldZeroCoercion (..)
, FieldAlternateForm (..)
, FieldZeroPadding (..)
, FieldGrouping (..)
, FieldSign (..)
, FieldType (..)
, FieldAlign (..)
, OrDefault (..)
, fromDefault
, FieldSpec (..)
, defFieldSpec
)
where
import Control.Monad (void)
import qualified Text.Megaparsec as P
import qualified Text.Megaparsec.Char as P
import Data.Void (Void)
import Data.Char (isDigit, GeneralCategory (..), generalCategory, isAscii)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import GHC.Float (floatToDigits)
import Text.Read (readMaybe)
import Text.Printf (printf)
data FormatArg
= IntArg !Integer
| FloatArg !Double
| StringArg !Text
| ListArg !(Vector FormatArg)
| DictArg !(Map Text FormatArg)
|
PolyArg
(Maybe Text)
(Maybe Integer)
(Maybe Double)
(Maybe (Vector FormatArg))
(Maybe (Map Text FormatArg))
deriving (Int -> FormatArg -> ShowS
[FormatArg] -> ShowS
FormatArg -> String
(Int -> FormatArg -> ShowS)
-> (FormatArg -> String)
-> ([FormatArg] -> ShowS)
-> Show FormatArg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatArg -> ShowS
showsPrec :: Int -> FormatArg -> ShowS
$cshow :: FormatArg -> String
show :: FormatArg -> String
$cshowList :: [FormatArg] -> ShowS
showList :: [FormatArg] -> ShowS
Show, FormatArg -> FormatArg -> Bool
(FormatArg -> FormatArg -> Bool)
-> (FormatArg -> FormatArg -> Bool) -> Eq FormatArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatArg -> FormatArg -> Bool
== :: FormatArg -> FormatArg -> Bool
$c/= :: FormatArg -> FormatArg -> Bool
/= :: FormatArg -> FormatArg -> Bool
Eq, Eq FormatArg
Eq FormatArg =>
(FormatArg -> FormatArg -> Ordering)
-> (FormatArg -> FormatArg -> Bool)
-> (FormatArg -> FormatArg -> Bool)
-> (FormatArg -> FormatArg -> Bool)
-> (FormatArg -> FormatArg -> Bool)
-> (FormatArg -> FormatArg -> FormatArg)
-> (FormatArg -> FormatArg -> FormatArg)
-> Ord FormatArg
FormatArg -> FormatArg -> Bool
FormatArg -> FormatArg -> Ordering
FormatArg -> FormatArg -> FormatArg
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FormatArg -> FormatArg -> Ordering
compare :: FormatArg -> FormatArg -> Ordering
$c< :: FormatArg -> FormatArg -> Bool
< :: FormatArg -> FormatArg -> Bool
$c<= :: FormatArg -> FormatArg -> Bool
<= :: FormatArg -> FormatArg -> Bool
$c> :: FormatArg -> FormatArg -> Bool
> :: FormatArg -> FormatArg -> Bool
$c>= :: FormatArg -> FormatArg -> Bool
>= :: FormatArg -> FormatArg -> Bool
$cmax :: FormatArg -> FormatArg -> FormatArg
max :: FormatArg -> FormatArg -> FormatArg
$cmin :: FormatArg -> FormatArg -> FormatArg
min :: FormatArg -> FormatArg -> FormatArg
Ord)
argAsString :: FormatArg -> Either String Text
argAsString :: FormatArg -> Either String Text
argAsString (IntArg Integer
i) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
i
argAsString (FloatArg Double
f) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Double -> Text
forall a. Show a => a -> Text
Text.show Double
f
argAsString (StringArg Text
s) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
s
argAsString (PolyArg (Just Text
s) Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
s
argAsString (PolyArg Maybe Text
_ (Just Integer
i) Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
i
argAsString (PolyArg Maybe Text
_ Maybe Integer
_ (Just Double
f) Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Double -> Text
forall a. Show a => a -> Text
Text.show Double
f
argAsString FormatArg
_ = String -> Either String Text
forall a b. a -> Either a b
Left String
"Cannot convert argument to string"
argAsRepr :: FormatArg -> Either String Text
argAsRepr :: FormatArg -> Either String Text
argAsRepr (IntArg Integer
i) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
i
argAsRepr (FloatArg Double
f) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Double -> Text
forall a. Show a => a -> Text
Text.show Double
f
argAsRepr (StringArg Text
s) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
Text.show Text
s
argAsRepr (ListArg Vector FormatArg
xs) = do
inner <- (FormatArg -> Either String Text)
-> [FormatArg] -> Either String [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM FormatArg -> Either String Text
argAsRepr (Vector FormatArg -> [FormatArg]
forall a. Vector a -> [a]
Vector.toList Vector FormatArg
xs)
pure $ "[" <> Text.intercalate ", " inner <> "]"
argAsRepr (DictArg Map Text FormatArg
xs) = do
inner <- ((Text, FormatArg) -> Either String Text)
-> [(Text, FormatArg)] -> Either String [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(Text
k, FormatArg
v) -> (Text
k Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> Either String Text -> Either String Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FormatArg -> Either String Text
argAsRepr FormatArg
v) (Map Text FormatArg -> [(Text, FormatArg)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Text FormatArg
xs)
pure $ "{" <> Text.intercalate ", " inner <> "}"
argAsRepr (PolyArg (Just Text
s) Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
Text.show Text
s
argAsRepr (PolyArg Maybe Text
_ (Just Integer
i) Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
i
argAsRepr (PolyArg Maybe Text
_ Maybe Integer
_ (Just Double
f) Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Double -> Text
forall a. Show a => a -> Text
Text.show Double
f
argAsRepr (PolyArg Maybe Text
_ Maybe Integer
_ Maybe Double
_ (Just Vector FormatArg
xs) Maybe (Map Text FormatArg)
_) = FormatArg -> Either String Text
argAsRepr (Vector FormatArg -> FormatArg
ListArg Vector FormatArg
xs)
argAsRepr (PolyArg Maybe Text
_ Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ (Just Map Text FormatArg
xs)) = FormatArg -> Either String Text
argAsRepr (Map Text FormatArg -> FormatArg
DictArg Map Text FormatArg
xs)
argAsRepr FormatArg
_ = String -> Either String Text
forall a b. a -> Either a b
Left String
"Cannot convert argument to string"
reprArg :: FormatArg -> Either String FormatArg
reprArg :: FormatArg -> Either String FormatArg
reprArg FormatArg
a = Text -> FormatArg
StringArg (Text -> FormatArg)
-> Either String Text -> Either String FormatArg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FormatArg -> Either String Text
argAsRepr FormatArg
a
stringArg :: FormatArg -> Either String FormatArg
stringArg :: FormatArg -> Either String FormatArg
stringArg FormatArg
a = Text -> FormatArg
StringArg (Text -> FormatArg)
-> Either String Text -> Either String FormatArg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FormatArg -> Either String Text
argAsString FormatArg
a
asciiArg :: FormatArg -> Either String FormatArg
asciiArg :: FormatArg -> Either String FormatArg
asciiArg FormatArg
a = Text -> FormatArg
StringArg (Text -> FormatArg) -> (Text -> Text) -> Text -> FormatArg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
Text.filter Char -> Bool
isAscii (Text -> FormatArg)
-> Either String Text -> Either String FormatArg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FormatArg -> Either String Text
argAsString FormatArg
a
argAsInt :: FormatArg -> Either String Integer
argAsInt :: FormatArg -> Either String Integer
argAsInt (IntArg Integer
i) = Integer -> Either String Integer
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Integer
i
argAsInt (FloatArg Double
f) = Integer -> Either String Integer
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Either String Integer)
-> Integer -> Either String Integer
forall a b. (a -> b) -> a -> b
$ Double -> Integer
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round Double
f
argAsInt (StringArg Text
s) =
Either String Integer
-> (Integer -> Either String Integer)
-> Maybe Integer
-> Either String Integer
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String Integer
forall a b. a -> Either a b
Left String
"Non-numeric string used as integer") Integer -> Either String Integer
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Integer -> Either String Integer)
-> (Text -> Maybe Integer) -> Text -> Either String Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> Maybe Integer
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe Integer)
-> (Text -> String) -> Text -> Maybe Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> String
Text.unpack (Text -> Either String Integer) -> Text -> Either String Integer
forall a b. (a -> b) -> a -> b
$
Text
s
argAsInt (PolyArg Maybe Text
_ (Just Integer
i) Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Integer -> Either String Integer
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Integer
i
argAsInt (PolyArg Maybe Text
_ Maybe Integer
_ (Just Double
f) Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Integer -> Either String Integer
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Either String Integer)
-> Integer -> Either String Integer
forall a b. (a -> b) -> a -> b
$ Double -> Integer
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round Double
f
argAsInt (PolyArg (Just Text
s) Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = FormatArg -> Either String Integer
argAsInt (Text -> FormatArg
StringArg Text
s)
argAsInt FormatArg
_ = String -> Either String Integer
forall a b. a -> Either a b
Left String
"Cannot convert non-scalar to integer"
argAsFloat :: FormatArg -> Either String Double
argAsFloat :: FormatArg -> Either String Double
argAsFloat (IntArg Integer
i) = Double -> Either String Double
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double -> Either String Double) -> Double -> Either String Double
forall a b. (a -> b) -> a -> b
$ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
i
argAsFloat (FloatArg Double
f) = Double -> Either String Double
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Double
f
argAsFloat (StringArg Text
s) =
Either String Double
-> (Double -> Either String Double)
-> Maybe Double
-> Either String Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String Double
forall a b. a -> Either a b
Left String
"Non-numeric string used as float") Double -> Either String Double
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Double -> Either String Double)
-> (Text -> Maybe Double) -> Text -> Either String Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> Maybe Double
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe Double)
-> (Text -> String) -> Text -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> String
Text.unpack (Text -> Either String Double) -> Text -> Either String Double
forall a b. (a -> b) -> a -> b
$
Text
s
argAsFloat (PolyArg Maybe Text
_ Maybe Integer
_ (Just Double
f) Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Double -> Either String Double
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Double
f
argAsFloat (PolyArg Maybe Text
_ (Just Integer
i) Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = Double -> Either String Double
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double -> Either String Double) -> Double -> Either String Double
forall a b. (a -> b) -> a -> b
$ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
i
argAsFloat (PolyArg (Just Text
s) Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = FormatArg -> Either String Double
argAsFloat (Text -> FormatArg
StringArg Text
s)
argAsFloat FormatArg
_ = String -> Either String Double
forall a b. a -> Either a b
Left String
"Cannot convert non-scalar to float"
lookupAttrib :: Text -> FormatArg -> Either String FormatArg
lookupAttrib :: Text -> FormatArg -> Either String FormatArg
lookupAttrib Text
name (DictArg Map Text FormatArg
items) =
Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Maybe FormatArg
-> Either String FormatArg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Attribute " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not found") FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FormatArg -> Either String FormatArg)
-> (Map Text FormatArg -> Maybe FormatArg)
-> Map Text FormatArg
-> Either String FormatArg
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Map Text FormatArg -> Maybe FormatArg
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
name (Map Text FormatArg -> Either String FormatArg)
-> Map Text FormatArg -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$
Map Text FormatArg
items
lookupAttrib Text
name (ListArg Vector FormatArg
items) = do
Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Maybe FormatArg
-> Either String FormatArg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Attribute " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not found") FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FormatArg -> Either String FormatArg)
-> Maybe FormatArg -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ do
index <- String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe Int) -> (Text -> String) -> Text -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack (Text -> Maybe Int) -> Text -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Text
name
items Vector.!? index
lookupAttrib Text
name (PolyArg Maybe Text
_ Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ (Just Map Text FormatArg
xs)) = Text -> FormatArg -> Either String FormatArg
lookupAttrib Text
name (Map Text FormatArg -> FormatArg
DictArg Map Text FormatArg
xs)
lookupAttrib Text
name (PolyArg Maybe Text
_ Maybe Integer
_ Maybe Double
_ (Just Vector FormatArg
xs) Maybe (Map Text FormatArg)
_) = Text -> FormatArg -> Either String FormatArg
lookupAttrib Text
name (Vector FormatArg -> FormatArg
ListArg Vector FormatArg
xs)
lookupAttrib Text
name FormatArg
_ = String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Cannot get attribute " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" from scalar"
lookupIndex :: Integer -> FormatArg -> Either String FormatArg
lookupIndex :: Integer -> FormatArg -> Either String FormatArg
lookupIndex Integer
index (DictArg Map Text FormatArg
items) =
Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Maybe FormatArg
-> Either String FormatArg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Item " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
index String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not found") FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FormatArg -> Either String FormatArg)
-> (Map Text FormatArg -> Maybe FormatArg)
-> Map Text FormatArg
-> Either String FormatArg
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Map Text FormatArg -> Maybe FormatArg
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
index) (Map Text FormatArg -> Either String FormatArg)
-> Map Text FormatArg -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$
Map Text FormatArg
items
lookupIndex Integer
index (ListArg Vector FormatArg
items) = do
Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Maybe FormatArg
-> Either String FormatArg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Item " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
index String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not found") FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FormatArg -> Either String FormatArg)
-> Maybe FormatArg -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$
Vector FormatArg
items Vector FormatArg -> Int -> Maybe FormatArg
forall a. Vector a -> Int -> Maybe a
Vector.!? (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
index)
lookupIndex Integer
index (PolyArg Maybe Text
_ Maybe Integer
_ Maybe Double
_ (Just Vector FormatArg
xs) Maybe (Map Text FormatArg)
_) = Integer -> FormatArg -> Either String FormatArg
lookupIndex Integer
index (Vector FormatArg -> FormatArg
ListArg Vector FormatArg
xs)
lookupIndex Integer
index (PolyArg Maybe Text
_ Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ (Just Map Text FormatArg
xs)) = Integer -> FormatArg -> Either String FormatArg
lookupIndex Integer
index (Map Text FormatArg -> FormatArg
DictArg Map Text FormatArg
xs)
lookupIndex Integer
index FormatArg
_ = String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Cannot get item " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
index String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" from scalar"
data FormattingGroup
= FormatAsInt
| FormatAsFloat
| FormatAsString
| FormatInvalid
deriving (Int -> FormattingGroup -> ShowS
[FormattingGroup] -> ShowS
FormattingGroup -> String
(Int -> FormattingGroup -> ShowS)
-> (FormattingGroup -> String)
-> ([FormattingGroup] -> ShowS)
-> Show FormattingGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormattingGroup -> ShowS
showsPrec :: Int -> FormattingGroup -> ShowS
$cshow :: FormattingGroup -> String
show :: FormattingGroup -> String
$cshowList :: [FormattingGroup] -> ShowS
showList :: [FormattingGroup] -> ShowS
Show, FormattingGroup -> FormattingGroup -> Bool
(FormattingGroup -> FormattingGroup -> Bool)
-> (FormattingGroup -> FormattingGroup -> Bool)
-> Eq FormattingGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormattingGroup -> FormattingGroup -> Bool
== :: FormattingGroup -> FormattingGroup -> Bool
$c/= :: FormattingGroup -> FormattingGroup -> Bool
/= :: FormattingGroup -> FormattingGroup -> Bool
Eq, Eq FormattingGroup
Eq FormattingGroup =>
(FormattingGroup -> FormattingGroup -> Ordering)
-> (FormattingGroup -> FormattingGroup -> Bool)
-> (FormattingGroup -> FormattingGroup -> Bool)
-> (FormattingGroup -> FormattingGroup -> Bool)
-> (FormattingGroup -> FormattingGroup -> Bool)
-> (FormattingGroup -> FormattingGroup -> FormattingGroup)
-> (FormattingGroup -> FormattingGroup -> FormattingGroup)
-> Ord FormattingGroup
FormattingGroup -> FormattingGroup -> Bool
FormattingGroup -> FormattingGroup -> Ordering
FormattingGroup -> FormattingGroup -> FormattingGroup
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FormattingGroup -> FormattingGroup -> Ordering
compare :: FormattingGroup -> FormattingGroup -> Ordering
$c< :: FormattingGroup -> FormattingGroup -> Bool
< :: FormattingGroup -> FormattingGroup -> Bool
$c<= :: FormattingGroup -> FormattingGroup -> Bool
<= :: FormattingGroup -> FormattingGroup -> Bool
$c> :: FormattingGroup -> FormattingGroup -> Bool
> :: FormattingGroup -> FormattingGroup -> Bool
$c>= :: FormattingGroup -> FormattingGroup -> Bool
>= :: FormattingGroup -> FormattingGroup -> Bool
$cmax :: FormattingGroup -> FormattingGroup -> FormattingGroup
max :: FormattingGroup -> FormattingGroup -> FormattingGroup
$cmin :: FormattingGroup -> FormattingGroup -> FormattingGroup
min :: FormattingGroup -> FormattingGroup -> FormattingGroup
Ord, Int -> FormattingGroup
FormattingGroup -> Int
FormattingGroup -> [FormattingGroup]
FormattingGroup -> FormattingGroup
FormattingGroup -> FormattingGroup -> [FormattingGroup]
FormattingGroup
-> FormattingGroup -> FormattingGroup -> [FormattingGroup]
(FormattingGroup -> FormattingGroup)
-> (FormattingGroup -> FormattingGroup)
-> (Int -> FormattingGroup)
-> (FormattingGroup -> Int)
-> (FormattingGroup -> [FormattingGroup])
-> (FormattingGroup -> FormattingGroup -> [FormattingGroup])
-> (FormattingGroup -> FormattingGroup -> [FormattingGroup])
-> (FormattingGroup
-> FormattingGroup -> FormattingGroup -> [FormattingGroup])
-> Enum FormattingGroup
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormattingGroup -> FormattingGroup
succ :: FormattingGroup -> FormattingGroup
$cpred :: FormattingGroup -> FormattingGroup
pred :: FormattingGroup -> FormattingGroup
$ctoEnum :: Int -> FormattingGroup
toEnum :: Int -> FormattingGroup
$cfromEnum :: FormattingGroup -> Int
fromEnum :: FormattingGroup -> Int
$cenumFrom :: FormattingGroup -> [FormattingGroup]
enumFrom :: FormattingGroup -> [FormattingGroup]
$cenumFromThen :: FormattingGroup -> FormattingGroup -> [FormattingGroup]
enumFromThen :: FormattingGroup -> FormattingGroup -> [FormattingGroup]
$cenumFromTo :: FormattingGroup -> FormattingGroup -> [FormattingGroup]
enumFromTo :: FormattingGroup -> FormattingGroup -> [FormattingGroup]
$cenumFromThenTo :: FormattingGroup
-> FormattingGroup -> FormattingGroup -> [FormattingGroup]
enumFromThenTo :: FormattingGroup
-> FormattingGroup -> FormattingGroup -> [FormattingGroup]
Enum, FormattingGroup
FormattingGroup -> FormattingGroup -> Bounded FormattingGroup
forall a. a -> a -> Bounded a
$cminBound :: FormattingGroup
minBound :: FormattingGroup
$cmaxBound :: FormattingGroup
maxBound :: FormattingGroup
Bounded)
formattingGroup :: FormatArg -> FormattingGroup
formattingGroup :: FormatArg -> FormattingGroup
formattingGroup StringArg {} = FormattingGroup
FormatAsString
formattingGroup IntArg {} = FormattingGroup
FormatAsInt
formattingGroup FloatArg {} = FormattingGroup
FormatAsFloat
formattingGroup (PolyArg Maybe Text
_ Maybe Integer
_ (Just Double
_) Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = FormattingGroup
FormatAsFloat
formattingGroup (PolyArg Maybe Text
_ (Just Integer
_) Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = FormattingGroup
FormatAsInt
formattingGroup (PolyArg (Just Text
_) Maybe Integer
_ Maybe Double
_ Maybe (Vector FormatArg)
_ Maybe (Map Text FormatArg)
_) = FormattingGroup
FormatAsString
formattingGroup FormatArg
_ = FormattingGroup
FormatInvalid
formatList :: Text
-> [(Maybe Text, FormatArg)]
-> Either String Text
formatList :: Text -> [(Maybe Text, FormatArg)] -> Either String Text
formatList Text
fmt [(Maybe Text, FormatArg)]
allArgs = do
f <- Text -> Either String [FormatItem]
parseFormat Text
fmt
renderFormat f allArgs
renderFormat :: [FormatItem] -> [(Maybe Text, FormatArg)] -> Either String Text
renderFormat :: [FormatItem] -> [(Maybe Text, FormatArg)] -> Either String Text
renderFormat [FormatItem]
xs [(Maybe Text, FormatArg)]
allArgs =
Integer -> [FormatItem] -> Either String Text
go Integer
0 [FormatItem]
xs
where
args :: Vector FormatArg
args = [FormatArg] -> Vector FormatArg
forall a. [a] -> Vector a
Vector.fromList (((Maybe Text, FormatArg) -> FormatArg)
-> [(Maybe Text, FormatArg)] -> [FormatArg]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Text, FormatArg) -> FormatArg
forall a b. (a, b) -> b
snd [(Maybe Text, FormatArg)]
allArgs)
kwargs :: Map Text FormatArg
kwargs = [(Text, FormatArg)] -> Map Text FormatArg
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (Text
k, FormatArg
v) | (Just Text
k, FormatArg
v) <- [(Maybe Text, FormatArg)]
allArgs ]
go :: Integer -> [FormatItem] -> Either String Text
go Integer
_ [] = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
""
go Integer
n (FormatItem
item:[FormatItem]
items) = case FormatItem
item of
PlainFormatItem {} ->
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) (Text -> Text -> Text)
-> Either String Text -> Either String (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Integer
-> Vector FormatArg
-> Map Text FormatArg
-> FormatItem
-> Either String Text
renderFormatItem Integer
n Vector FormatArg
args Map Text FormatArg
kwargs FormatItem
item Either String (Text -> Text)
-> Either String Text -> Either String Text
forall a b.
Either String (a -> b) -> Either String a -> Either String b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Integer -> [FormatItem] -> Either String Text
go Integer
n [FormatItem]
items
FormatItem
_ ->
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) (Text -> Text -> Text)
-> Either String Text -> Either String (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Integer
-> Vector FormatArg
-> Map Text FormatArg
-> FormatItem
-> Either String Text
renderFormatItem Integer
n Vector FormatArg
args Map Text FormatArg
kwargs FormatItem
item Either String (Text -> Text)
-> Either String Text -> Either String Text
forall a b.
Either String (a -> b) -> Either String a -> Either String b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Integer -> [FormatItem] -> Either String Text
go (Integer -> Integer
forall a. Enum a => a -> a
succ Integer
n) [FormatItem]
items
parseFormat :: Text -> Either String [FormatItem]
parseFormat :: Text -> Either String [FormatItem]
parseFormat Text
fmt =
(ParseErrorBundle Text Void -> Either String [FormatItem])
-> ([FormatItem] -> Either String [FormatItem])
-> Either (ParseErrorBundle Text Void) [FormatItem]
-> Either String [FormatItem]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Either String [FormatItem]
forall a b. a -> Either a b
Left (String -> Either String [FormatItem])
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> Either String [FormatItem]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
P.errorBundlePretty) [FormatItem] -> Either String [FormatItem]
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (ParseErrorBundle Text Void) [FormatItem]
-> Either String [FormatItem])
-> Either (ParseErrorBundle Text Void) [FormatItem]
-> Either String [FormatItem]
forall a b. (a -> b) -> a -> b
$
Parsec Void Text [FormatItem]
-> String
-> Text
-> Either (ParseErrorBundle Text Void) [FormatItem]
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
P.parse Parsec Void Text [FormatItem]
pFormat String
"format string" Text
fmt
padL :: Char -> Int -> Text -> Text
padL :: Char -> Int -> Text -> Text
padL Char
p Int
w Text
t =
let pw :: Int
pw = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Text -> Int
Text.length Text
t Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
w
in Int -> Text -> Text
Text.replicate Int
pw (Char -> Text
Text.singleton Char
p) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
renderFormatItem :: Integer
-> Vector FormatArg
-> Map Text FormatArg
-> FormatItem
-> Either String Text
renderFormatItem :: Integer
-> Vector FormatArg
-> Map Text FormatArg
-> FormatItem
-> Either String Text
renderFormatItem Integer
_ Vector FormatArg
_ Map Text FormatArg
_ (PlainFormatItem Text
txt) = Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
txt
renderFormatItem Integer
defPosition Vector FormatArg
args Map Text FormatArg
kwargs (FieldFormatItem FormatField
field) = do
val' <- Vector FormatArg
-> Map Text FormatArg -> FieldName -> Either String FormatArg
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs (FieldName -> OrDefault FieldName -> FieldName
forall a. a -> OrDefault a -> a
fromDefault (Integer -> FieldName
FieldNameNumber Integer
defPosition) (OrDefault FieldName -> FieldName)
-> OrDefault FieldName -> FieldName
forall a b. (a -> b) -> a -> b
$ FormatField -> OrDefault FieldName
formatFieldName FormatField
field)
val <- case formatFieldConversion field of
FieldConversion
FieldConvNone -> FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FormatArg
val'
FieldConversion
FieldConvRepr -> FormatArg -> Either String FormatArg
reprArg FormatArg
val'
FieldConversion
FieldConvString -> FormatArg -> Either String FormatArg
stringArg FormatArg
val'
FieldConversion
FieldConvASCII -> FormatArg -> Either String FormatArg
asciiArg FormatArg
val'
let fgroup = FormatArg -> FormattingGroup
formattingGroup FormatArg
val
spec = FormatField -> FieldSpec
formatFieldSpec FormatField
field
let formatAsString :: Either String Text
formatAsString = FormatArg -> Either String Text
argAsString FormatArg
val
formatAsInt :: Either String Text
formatAsInt = do
i <- FormatArg -> Either String Integer
argAsInt FormatArg
val
pure . applyGrouping $ Text.show i
formatAsFloat :: Either String Text
formatAsFloat = do
f <- FormatArg -> Either String Double
argAsFloat FormatArg
val
pure $ Text.show f
formatAsHex :: Either String Text
formatAsHex = do
i <- FormatArg -> Either String Integer
argAsInt FormatArg
val
let hex = Text -> Text
applyHexGrouping (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Integer -> String
forall r. PrintfType r => String -> r
printf String
"%x" Integer
i
case fieldSpecAlternateForm spec of
FieldAlternateForm
AlternateForm -> Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text
"0x" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
hex
FieldAlternateForm
NormalForm -> Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
hex
formatAsOctal :: Either String Text
formatAsOctal = do
i <- FormatArg -> Either String Integer
argAsInt FormatArg
val
let octal = Text -> Text
applyHexGrouping (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Integer -> String
forall r. PrintfType r => String -> r
printf String
"%o" Integer
i
case fieldSpecAlternateForm spec of
FieldAlternateForm
AlternateForm -> Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text
"0o" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
octal
FieldAlternateForm
NormalForm -> Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
octal
formatAsBinary :: Either String Text
formatAsBinary = do
i <- FormatArg -> Either String Integer
argAsInt FormatArg
val
let binary = Text -> Text
applyHexGrouping (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Integer -> String
forall r. PrintfType r => String -> r
printf String
"%b" Integer
i
case fieldSpecAlternateForm spec of
FieldAlternateForm
AlternateForm -> Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text
"0b" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
binary
FieldAlternateForm
NormalForm -> Text -> Either String Text
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
binary
formatAsFixed :: Either String Text
formatAsFixed = do
f <- FormatArg -> Either String Double
argAsFloat FormatArg
val
let precision = (Int -> OrDefault Int -> Int
forall a. a -> OrDefault a -> a
fromDefault Int
5 (OrDefault Int -> Int) -> OrDefault Int -> Int
forall a b. (a -> b) -> a -> b
$ FieldSpec -> OrDefault Int
fieldSpecPrecision FieldSpec
spec)
(intpart, fracpart) = properFraction $ abs f
intpartStr = Text -> Text
applyGrouping (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show (Integer
intpart :: Integer)
fracpartMul :: Integer = round $ fracpart * 10 ^ precision
fracpartStr = Char -> Int -> Text -> Text
padL Char
'0' Int
precision (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
fracpartMul
let sign = Double -> Text
getFloatSign Double
f
pure $ sign <> Text.show intpartStr <> "." <> fracpartStr
formatAsPercentage :: Either String Text
formatAsPercentage = do
f <- FormatArg -> Either String Double
argAsFloat FormatArg
val
let precision = (Int -> OrDefault Int -> Int
forall a. a -> OrDefault a -> a
fromDefault Int
5 (OrDefault Int -> Int) -> OrDefault Int -> Int
forall a b. (a -> b) -> a -> b
$ FieldSpec -> OrDefault Int
fieldSpecPrecision FieldSpec
spec)
(intpart, fracpart) = properFraction $ abs f
intpartStr = Integer -> Text
forall a. Show a => a -> Text
Text.show (Integer
intpart :: Integer)
fracpartMul :: Integer = round $ fracpart * 10 ^ precision
fracpartStr = Char -> Int -> Text -> Text
padL Char
'0' Int
precision (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. Show a => a -> Text
Text.show Integer
fracpartMul
let sign = Double -> Text
getFloatSign Double
f
pure $ sign <> Text.show intpartStr <> "." <> fracpartStr <> "%"
formatAsScientific :: Either String Text
formatAsScientific = do
f <- FormatArg -> Either String Double
argAsFloat FormatArg
val
let precision = (Int -> OrDefault Int -> Int
forall a. a -> OrDefault a -> a
fromDefault Int
5 (OrDefault Int -> Int) -> OrDefault Int -> Int
forall a b. (a -> b) -> a -> b
$ FieldSpec -> OrDefault Int
fieldSpecPrecision FieldSpec
spec)
(mantissaDigits, exponentInt) = floatToDigits 10 (abs f)
sign = Double -> Text
getFloatSign Double
f
mantissaStr = Text -> Text
applyGrouping (Text -> Text) -> ([Int] -> Text) -> [Int] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> ([Int] -> [Text]) -> [Int] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Text) -> [Int] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Text
forall a. Show a => a -> Text
Text.show ([Int] -> [Text]) -> ([Int] -> [Int]) -> [Int] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
precision ([Int] -> Text) -> [Int] -> Text
forall a b. (a -> b) -> a -> b
$ [Int]
mantissaDigits
expStr = Int -> Text
forall a. Show a => a -> Text
Text.show Int
exponentInt
pure $ sign <> "0." <> mantissaStr <> "e" <> expStr
insertThousandsSep :: Text -> Text -> Text
insertThousandsSep = Int -> Text -> Text -> Text
insertSep Int
3
insertHexSep :: Text -> Text -> Text
insertHexSep = Int -> Text -> Text -> Text
insertSep Int
4
insertSep :: Int -> Text -> Text -> Text
insertSep Int
n Text
sep Text
src =
let chunks :: [Text]
chunks = [Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
Text.reverse ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> [Text]
Text.chunksOf Int
n (Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.reverse (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text
src
in Text -> [Text] -> Text
Text.intercalate Text
sep [Text]
chunks
applyGrouping :: Text -> Text
applyGrouping Text
src =
case FieldSpec -> FieldGrouping
fieldSpecGrouping FieldSpec
spec of
FieldGrouping
NoGrouping -> Text
src
FieldGrouping
GroupComma -> Text -> Text -> Text
insertThousandsSep Text
"," Text
src
FieldGrouping
GroupUnderscore -> Text -> Text -> Text
insertThousandsSep Text
"_" Text
src
applyHexGrouping :: Text -> Text
applyHexGrouping Text
src =
case FieldSpec -> FieldGrouping
fieldSpecGrouping FieldSpec
spec of
FieldGrouping
NoGrouping -> Text
src
FieldGrouping
GroupComma -> Text
src
FieldGrouping
GroupUnderscore -> Text -> Text -> Text
insertHexSep Text
"_" Text
src
getFloatSign :: Double -> Text
getFloatSign Double
f =
case (Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Double -> Double
forall a. Num a => a -> a
signum Double
f) Double
0, FieldSpec -> FieldSign
fieldSpecSign FieldSpec
spec) of
(Ordering
LT, FieldSign
_) -> Text
"-"
(Ordering
GT, FieldSign
SignNegative) -> Text
"+"
(Ordering
EQ, FieldSign
SignNegative) -> Text
""
(Ordering
_, FieldSign
SignAlways) -> Text
"+"
(Ordering
_, FieldSign
SignSpacePadded) -> Text
" "
strVal <- case fieldSpecType spec of
FieldType
FieldTypeGeneral -> case FormattingGroup
fgroup of
FormattingGroup
FormatAsString -> Either String Text
formatAsString
FormattingGroup
FormatAsInt -> Either String Text
formatAsInt
FormattingGroup
FormatAsFloat -> Either String Text
formatAsFloat
FormattingGroup
FormatInvalid -> String -> Either String Text
forall a b. a -> Either a b
Left String
"Cannot format non-scalar as 'general'"
FieldType
FieldTypeNumber -> case FormattingGroup
fgroup of
FormattingGroup
FormatAsString -> Either String Text
formatAsString
FormattingGroup
FormatAsInt -> Either String Text
formatAsInt
FormattingGroup
FormatAsFloat -> Either String Text
formatAsFloat
FormattingGroup
FormatInvalid -> String -> Either String Text
forall a b. a -> Either a b
Left String
"Cannot format non-scalar as 'number'"
FieldType
FieldTypeDecimalInt -> Either String Text
formatAsInt
FieldType
FieldTypeHex -> Either String Text
formatAsHex
FieldType
FieldTypeHexUpper -> Text -> Text
Text.toUpper (Text -> Text) -> Either String Text -> Either String Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String Text
formatAsHex
FieldType
FieldTypeOctal -> Either String Text
formatAsOctal
FieldType
FieldTypeBinary -> Either String Text
formatAsBinary
FieldType
FieldTypeFixedPoint -> Either String Text
formatAsFixed
FieldType
FieldTypeFixedPointUpper -> Text -> Text
Text.toUpper (Text -> Text) -> Either String Text -> Either String Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String Text
formatAsFixed
FieldType
FieldTypeScientific -> Either String Text
formatAsScientific
FieldType
FieldTypeScientificUpper -> Text -> Text
Text.toUpper (Text -> Text) -> Either String Text -> Either String Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String Text
formatAsScientific
FieldType
FieldTypePercentage -> Either String Text
formatAsPercentage
FieldType
FieldTypeString -> Either String Text
formatAsString
FieldType
t -> String -> Either String Text
forall a b. a -> Either a b
Left (String -> Either String Text) -> String -> Either String Text
forall a b. (a -> b) -> a -> b
$ String
"Field type " String -> ShowS
forall a. [a] -> [a] -> [a]
++ FieldType -> String
forall a. Show a => a -> String
show FieldType
t String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not implemented"
let defAlignment = case FormattingGroup
fgroup of
FormattingGroup
FormatAsString -> FieldAlign
AlignLeft
FormattingGroup
_ -> FieldAlign
AlignRight
pure $ align
(fromDefault defAlignment $ fieldSpecAlign spec)
(fieldSpecWidth spec)
(fromDefault ' ' $ fieldSpecFill spec)
strVal
align :: FieldAlign -> OrDefault Int -> Char -> Text -> Text
align :: FieldAlign -> OrDefault Int -> Char -> Text -> Text
align FieldAlign
_ OrDefault Int
Default Char
_ Text
str = Text
str
align FieldAlign
AlignLeft (Specific Int
w) Char
fill Text
str =
let extra :: Int
extra = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
Text.length Text
str)
in Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
Text.replicate Int
extra (Char -> Text
Text.singleton Char
fill)
align FieldAlign
AlignRight (Specific Int
w) Char
fill Text
str =
let extra :: Int
extra = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
Text.length Text
str)
in Int -> Text -> Text
Text.replicate Int
extra (Char -> Text
Text.singleton Char
fill) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str
align FieldAlign
AlignCenter (Specific Int
w) Char
fill Text
str =
let extra :: Int
extra = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
Text.length Text
str)
extraL :: Int
extraL = Int
extra Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
extraR :: Int
extraR = Int
extra Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
extraL
in Int -> Text -> Text
Text.replicate Int
extraL (Char -> Text
Text.singleton Char
fill)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
Text.replicate Int
extraR (Char -> Text
Text.singleton Char
fill)
align FieldAlign
AlignZeroPad (Specific Int
w) Char
fill Text
str =
if Int -> Text -> Text
Text.take Int
1 Text
str Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"-", Text
"+", Text
" "] then
Int -> Text -> Text
Text.take Int
1 Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FieldAlign -> OrDefault Int -> Char -> Text -> Text
align FieldAlign
AlignRight (Int -> OrDefault Int
forall a. a -> OrDefault a
Specific (Int -> OrDefault Int) -> Int -> OrDefault Int
forall a b. (a -> b) -> a -> b
$ Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Char
fill (Int -> Text -> Text
Text.drop Int
1 Text
str)
else
FieldAlign -> OrDefault Int -> Char -> Text -> Text
align FieldAlign
AlignRight (Int -> OrDefault Int
forall a. a -> OrDefault a
Specific Int
w) Char
fill Text
str
lookupFormatItemArg :: Vector FormatArg
-> Map Text FormatArg
-> FieldName
-> Either String FormatArg
lookupFormatItemArg :: Vector FormatArg
-> Map Text FormatArg -> FieldName -> Either String FormatArg
lookupFormatItemArg Vector FormatArg
_args Map Text FormatArg
kwargs (FieldNameIdentifier Text
n) =
Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Maybe FormatArg
-> Either String FormatArg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Field not found: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
n) FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FormatArg -> Either String FormatArg)
-> Maybe FormatArg -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$
Text -> Map Text FormatArg -> Maybe FormatArg
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
n Map Text FormatArg
kwargs
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
_kwargs (FieldNameNumber Integer
i) =
Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Maybe FormatArg
-> Either String FormatArg
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String FormatArg
forall a b. a -> Either a b
Left (String -> Either String FormatArg)
-> String -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$ String
"Field not found: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i) FormatArg -> Either String FormatArg
forall a. a -> Either String a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FormatArg -> Either String FormatArg)
-> Maybe FormatArg -> Either String FormatArg
forall a b. (a -> b) -> a -> b
$
Vector FormatArg
args Vector FormatArg -> Int -> Maybe FormatArg
forall a. Vector a -> Int -> Maybe a
Vector.!? Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs (FieldNameAttrib Text
a FieldName
b) =
Vector FormatArg
-> Map Text FormatArg -> FieldName -> Either String FormatArg
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs FieldName
b Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Either String FormatArg
forall a b.
Either String a -> (a -> Either String b) -> Either String b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> FormatArg -> Either String FormatArg
lookupAttrib Text
a
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs (FieldNameKeyIndex Text
a FieldName
b) =
Vector FormatArg
-> Map Text FormatArg -> FieldName -> Either String FormatArg
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs FieldName
b Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Either String FormatArg
forall a b.
Either String a -> (a -> Either String b) -> Either String b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> FormatArg -> Either String FormatArg
lookupAttrib Text
a
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs (FieldNameNumIndex Integer
a FieldName
b) =
Vector FormatArg
-> Map Text FormatArg -> FieldName -> Either String FormatArg
lookupFormatItemArg Vector FormatArg
args Map Text FormatArg
kwargs FieldName
b Either String FormatArg
-> (FormatArg -> Either String FormatArg)
-> Either String FormatArg
forall a b.
Either String a -> (a -> Either String b) -> Either String b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Integer -> FormatArg -> Either String FormatArg
lookupIndex Integer
a
data FormatItem
= PlainFormatItem !Text
| FieldFormatItem !FormatField
deriving (Int -> FormatItem -> ShowS
[FormatItem] -> ShowS
FormatItem -> String
(Int -> FormatItem -> ShowS)
-> (FormatItem -> String)
-> ([FormatItem] -> ShowS)
-> Show FormatItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatItem -> ShowS
showsPrec :: Int -> FormatItem -> ShowS
$cshow :: FormatItem -> String
show :: FormatItem -> String
$cshowList :: [FormatItem] -> ShowS
showList :: [FormatItem] -> ShowS
Show, FormatItem -> FormatItem -> Bool
(FormatItem -> FormatItem -> Bool)
-> (FormatItem -> FormatItem -> Bool) -> Eq FormatItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatItem -> FormatItem -> Bool
== :: FormatItem -> FormatItem -> Bool
$c/= :: FormatItem -> FormatItem -> Bool
/= :: FormatItem -> FormatItem -> Bool
Eq)
data FormatField =
FormatField
{ FormatField -> OrDefault FieldName
formatFieldName :: !(OrDefault FieldName)
, FormatField -> FieldConversion
formatFieldConversion :: !FieldConversion
, FormatField -> FieldSpec
formatFieldSpec :: !FieldSpec
}
deriving (Int -> FormatField -> ShowS
[FormatField] -> ShowS
FormatField -> String
(Int -> FormatField -> ShowS)
-> (FormatField -> String)
-> ([FormatField] -> ShowS)
-> Show FormatField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatField -> ShowS
showsPrec :: Int -> FormatField -> ShowS
$cshow :: FormatField -> String
show :: FormatField -> String
$cshowList :: [FormatField] -> ShowS
showList :: [FormatField] -> ShowS
Show, FormatField -> FormatField -> Bool
(FormatField -> FormatField -> Bool)
-> (FormatField -> FormatField -> Bool) -> Eq FormatField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatField -> FormatField -> Bool
== :: FormatField -> FormatField -> Bool
$c/= :: FormatField -> FormatField -> Bool
/= :: FormatField -> FormatField -> Bool
Eq)
data FieldName
= FieldNameIdentifier !Text
| !Integer
| FieldNameAttrib !Text !FieldName
| FieldNameKeyIndex !Text !FieldName
| !Integer !FieldName
deriving (Int -> FieldName -> ShowS
[FieldName] -> ShowS
FieldName -> String
(Int -> FieldName -> ShowS)
-> (FieldName -> String)
-> ([FieldName] -> ShowS)
-> Show FieldName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldName -> ShowS
showsPrec :: Int -> FieldName -> ShowS
$cshow :: FieldName -> String
show :: FieldName -> String
$cshowList :: [FieldName] -> ShowS
showList :: [FieldName] -> ShowS
Show, FieldName -> FieldName -> Bool
(FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool) -> Eq FieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldName -> FieldName -> Bool
== :: FieldName -> FieldName -> Bool
$c/= :: FieldName -> FieldName -> Bool
/= :: FieldName -> FieldName -> Bool
Eq)
data FieldConversion
= FieldConvNone
| FieldConvRepr
| FieldConvString
| FieldConvASCII
deriving (Int -> FieldConversion -> ShowS
[FieldConversion] -> ShowS
FieldConversion -> String
(Int -> FieldConversion -> ShowS)
-> (FieldConversion -> String)
-> ([FieldConversion] -> ShowS)
-> Show FieldConversion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldConversion -> ShowS
showsPrec :: Int -> FieldConversion -> ShowS
$cshow :: FieldConversion -> String
show :: FieldConversion -> String
$cshowList :: [FieldConversion] -> ShowS
showList :: [FieldConversion] -> ShowS
Show, FieldConversion -> FieldConversion -> Bool
(FieldConversion -> FieldConversion -> Bool)
-> (FieldConversion -> FieldConversion -> Bool)
-> Eq FieldConversion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldConversion -> FieldConversion -> Bool
== :: FieldConversion -> FieldConversion -> Bool
$c/= :: FieldConversion -> FieldConversion -> Bool
/= :: FieldConversion -> FieldConversion -> Bool
Eq)
data FieldZeroCoercion
= AllowNegativeZero
| ForcePositiveZero
deriving (Int -> FieldZeroCoercion -> ShowS
[FieldZeroCoercion] -> ShowS
FieldZeroCoercion -> String
(Int -> FieldZeroCoercion -> ShowS)
-> (FieldZeroCoercion -> String)
-> ([FieldZeroCoercion] -> ShowS)
-> Show FieldZeroCoercion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldZeroCoercion -> ShowS
showsPrec :: Int -> FieldZeroCoercion -> ShowS
$cshow :: FieldZeroCoercion -> String
show :: FieldZeroCoercion -> String
$cshowList :: [FieldZeroCoercion] -> ShowS
showList :: [FieldZeroCoercion] -> ShowS
Show, FieldZeroCoercion -> FieldZeroCoercion -> Bool
(FieldZeroCoercion -> FieldZeroCoercion -> Bool)
-> (FieldZeroCoercion -> FieldZeroCoercion -> Bool)
-> Eq FieldZeroCoercion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
== :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
$c/= :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
/= :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
Eq, Eq FieldZeroCoercion
Eq FieldZeroCoercion =>
(FieldZeroCoercion -> FieldZeroCoercion -> Ordering)
-> (FieldZeroCoercion -> FieldZeroCoercion -> Bool)
-> (FieldZeroCoercion -> FieldZeroCoercion -> Bool)
-> (FieldZeroCoercion -> FieldZeroCoercion -> Bool)
-> (FieldZeroCoercion -> FieldZeroCoercion -> Bool)
-> (FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion)
-> (FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion)
-> Ord FieldZeroCoercion
FieldZeroCoercion -> FieldZeroCoercion -> Bool
FieldZeroCoercion -> FieldZeroCoercion -> Ordering
FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldZeroCoercion -> FieldZeroCoercion -> Ordering
compare :: FieldZeroCoercion -> FieldZeroCoercion -> Ordering
$c< :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
< :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
$c<= :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
<= :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
$c> :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
> :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
$c>= :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
>= :: FieldZeroCoercion -> FieldZeroCoercion -> Bool
$cmax :: FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion
max :: FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion
$cmin :: FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion
min :: FieldZeroCoercion -> FieldZeroCoercion -> FieldZeroCoercion
Ord, Int -> FieldZeroCoercion
FieldZeroCoercion -> Int
FieldZeroCoercion -> [FieldZeroCoercion]
FieldZeroCoercion -> FieldZeroCoercion
FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
FieldZeroCoercion
-> FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
(FieldZeroCoercion -> FieldZeroCoercion)
-> (FieldZeroCoercion -> FieldZeroCoercion)
-> (Int -> FieldZeroCoercion)
-> (FieldZeroCoercion -> Int)
-> (FieldZeroCoercion -> [FieldZeroCoercion])
-> (FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion])
-> (FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion])
-> (FieldZeroCoercion
-> FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion])
-> Enum FieldZeroCoercion
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldZeroCoercion -> FieldZeroCoercion
succ :: FieldZeroCoercion -> FieldZeroCoercion
$cpred :: FieldZeroCoercion -> FieldZeroCoercion
pred :: FieldZeroCoercion -> FieldZeroCoercion
$ctoEnum :: Int -> FieldZeroCoercion
toEnum :: Int -> FieldZeroCoercion
$cfromEnum :: FieldZeroCoercion -> Int
fromEnum :: FieldZeroCoercion -> Int
$cenumFrom :: FieldZeroCoercion -> [FieldZeroCoercion]
enumFrom :: FieldZeroCoercion -> [FieldZeroCoercion]
$cenumFromThen :: FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
enumFromThen :: FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
$cenumFromTo :: FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
enumFromTo :: FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
$cenumFromThenTo :: FieldZeroCoercion
-> FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
enumFromThenTo :: FieldZeroCoercion
-> FieldZeroCoercion -> FieldZeroCoercion -> [FieldZeroCoercion]
Enum, FieldZeroCoercion
FieldZeroCoercion -> FieldZeroCoercion -> Bounded FieldZeroCoercion
forall a. a -> a -> Bounded a
$cminBound :: FieldZeroCoercion
minBound :: FieldZeroCoercion
$cmaxBound :: FieldZeroCoercion
maxBound :: FieldZeroCoercion
Bounded)
data FieldAlternateForm
= NormalForm
| AlternateForm
deriving (Int -> FieldAlternateForm -> ShowS
[FieldAlternateForm] -> ShowS
FieldAlternateForm -> String
(Int -> FieldAlternateForm -> ShowS)
-> (FieldAlternateForm -> String)
-> ([FieldAlternateForm] -> ShowS)
-> Show FieldAlternateForm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldAlternateForm -> ShowS
showsPrec :: Int -> FieldAlternateForm -> ShowS
$cshow :: FieldAlternateForm -> String
show :: FieldAlternateForm -> String
$cshowList :: [FieldAlternateForm] -> ShowS
showList :: [FieldAlternateForm] -> ShowS
Show, FieldAlternateForm -> FieldAlternateForm -> Bool
(FieldAlternateForm -> FieldAlternateForm -> Bool)
-> (FieldAlternateForm -> FieldAlternateForm -> Bool)
-> Eq FieldAlternateForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldAlternateForm -> FieldAlternateForm -> Bool
== :: FieldAlternateForm -> FieldAlternateForm -> Bool
$c/= :: FieldAlternateForm -> FieldAlternateForm -> Bool
/= :: FieldAlternateForm -> FieldAlternateForm -> Bool
Eq, Eq FieldAlternateForm
Eq FieldAlternateForm =>
(FieldAlternateForm -> FieldAlternateForm -> Ordering)
-> (FieldAlternateForm -> FieldAlternateForm -> Bool)
-> (FieldAlternateForm -> FieldAlternateForm -> Bool)
-> (FieldAlternateForm -> FieldAlternateForm -> Bool)
-> (FieldAlternateForm -> FieldAlternateForm -> Bool)
-> (FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm)
-> (FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm)
-> Ord FieldAlternateForm
FieldAlternateForm -> FieldAlternateForm -> Bool
FieldAlternateForm -> FieldAlternateForm -> Ordering
FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldAlternateForm -> FieldAlternateForm -> Ordering
compare :: FieldAlternateForm -> FieldAlternateForm -> Ordering
$c< :: FieldAlternateForm -> FieldAlternateForm -> Bool
< :: FieldAlternateForm -> FieldAlternateForm -> Bool
$c<= :: FieldAlternateForm -> FieldAlternateForm -> Bool
<= :: FieldAlternateForm -> FieldAlternateForm -> Bool
$c> :: FieldAlternateForm -> FieldAlternateForm -> Bool
> :: FieldAlternateForm -> FieldAlternateForm -> Bool
$c>= :: FieldAlternateForm -> FieldAlternateForm -> Bool
>= :: FieldAlternateForm -> FieldAlternateForm -> Bool
$cmax :: FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm
max :: FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm
$cmin :: FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm
min :: FieldAlternateForm -> FieldAlternateForm -> FieldAlternateForm
Ord, Int -> FieldAlternateForm
FieldAlternateForm -> Int
FieldAlternateForm -> [FieldAlternateForm]
FieldAlternateForm -> FieldAlternateForm
FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
FieldAlternateForm
-> FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
(FieldAlternateForm -> FieldAlternateForm)
-> (FieldAlternateForm -> FieldAlternateForm)
-> (Int -> FieldAlternateForm)
-> (FieldAlternateForm -> Int)
-> (FieldAlternateForm -> [FieldAlternateForm])
-> (FieldAlternateForm
-> FieldAlternateForm -> [FieldAlternateForm])
-> (FieldAlternateForm
-> FieldAlternateForm -> [FieldAlternateForm])
-> (FieldAlternateForm
-> FieldAlternateForm
-> FieldAlternateForm
-> [FieldAlternateForm])
-> Enum FieldAlternateForm
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldAlternateForm -> FieldAlternateForm
succ :: FieldAlternateForm -> FieldAlternateForm
$cpred :: FieldAlternateForm -> FieldAlternateForm
pred :: FieldAlternateForm -> FieldAlternateForm
$ctoEnum :: Int -> FieldAlternateForm
toEnum :: Int -> FieldAlternateForm
$cfromEnum :: FieldAlternateForm -> Int
fromEnum :: FieldAlternateForm -> Int
$cenumFrom :: FieldAlternateForm -> [FieldAlternateForm]
enumFrom :: FieldAlternateForm -> [FieldAlternateForm]
$cenumFromThen :: FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
enumFromThen :: FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
$cenumFromTo :: FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
enumFromTo :: FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
$cenumFromThenTo :: FieldAlternateForm
-> FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
enumFromThenTo :: FieldAlternateForm
-> FieldAlternateForm -> FieldAlternateForm -> [FieldAlternateForm]
Enum, FieldAlternateForm
FieldAlternateForm
-> FieldAlternateForm -> Bounded FieldAlternateForm
forall a. a -> a -> Bounded a
$cminBound :: FieldAlternateForm
minBound :: FieldAlternateForm
$cmaxBound :: FieldAlternateForm
maxBound :: FieldAlternateForm
Bounded)
data FieldZeroPadding
= NoZeroPadding
| ZeroPadding
deriving (Int -> FieldZeroPadding -> ShowS
[FieldZeroPadding] -> ShowS
FieldZeroPadding -> String
(Int -> FieldZeroPadding -> ShowS)
-> (FieldZeroPadding -> String)
-> ([FieldZeroPadding] -> ShowS)
-> Show FieldZeroPadding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldZeroPadding -> ShowS
showsPrec :: Int -> FieldZeroPadding -> ShowS
$cshow :: FieldZeroPadding -> String
show :: FieldZeroPadding -> String
$cshowList :: [FieldZeroPadding] -> ShowS
showList :: [FieldZeroPadding] -> ShowS
Show, FieldZeroPadding -> FieldZeroPadding -> Bool
(FieldZeroPadding -> FieldZeroPadding -> Bool)
-> (FieldZeroPadding -> FieldZeroPadding -> Bool)
-> Eq FieldZeroPadding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldZeroPadding -> FieldZeroPadding -> Bool
== :: FieldZeroPadding -> FieldZeroPadding -> Bool
$c/= :: FieldZeroPadding -> FieldZeroPadding -> Bool
/= :: FieldZeroPadding -> FieldZeroPadding -> Bool
Eq, Eq FieldZeroPadding
Eq FieldZeroPadding =>
(FieldZeroPadding -> FieldZeroPadding -> Ordering)
-> (FieldZeroPadding -> FieldZeroPadding -> Bool)
-> (FieldZeroPadding -> FieldZeroPadding -> Bool)
-> (FieldZeroPadding -> FieldZeroPadding -> Bool)
-> (FieldZeroPadding -> FieldZeroPadding -> Bool)
-> (FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding)
-> (FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding)
-> Ord FieldZeroPadding
FieldZeroPadding -> FieldZeroPadding -> Bool
FieldZeroPadding -> FieldZeroPadding -> Ordering
FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldZeroPadding -> FieldZeroPadding -> Ordering
compare :: FieldZeroPadding -> FieldZeroPadding -> Ordering
$c< :: FieldZeroPadding -> FieldZeroPadding -> Bool
< :: FieldZeroPadding -> FieldZeroPadding -> Bool
$c<= :: FieldZeroPadding -> FieldZeroPadding -> Bool
<= :: FieldZeroPadding -> FieldZeroPadding -> Bool
$c> :: FieldZeroPadding -> FieldZeroPadding -> Bool
> :: FieldZeroPadding -> FieldZeroPadding -> Bool
$c>= :: FieldZeroPadding -> FieldZeroPadding -> Bool
>= :: FieldZeroPadding -> FieldZeroPadding -> Bool
$cmax :: FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding
max :: FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding
$cmin :: FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding
min :: FieldZeroPadding -> FieldZeroPadding -> FieldZeroPadding
Ord, Int -> FieldZeroPadding
FieldZeroPadding -> Int
FieldZeroPadding -> [FieldZeroPadding]
FieldZeroPadding -> FieldZeroPadding
FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
FieldZeroPadding
-> FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
(FieldZeroPadding -> FieldZeroPadding)
-> (FieldZeroPadding -> FieldZeroPadding)
-> (Int -> FieldZeroPadding)
-> (FieldZeroPadding -> Int)
-> (FieldZeroPadding -> [FieldZeroPadding])
-> (FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding])
-> (FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding])
-> (FieldZeroPadding
-> FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding])
-> Enum FieldZeroPadding
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldZeroPadding -> FieldZeroPadding
succ :: FieldZeroPadding -> FieldZeroPadding
$cpred :: FieldZeroPadding -> FieldZeroPadding
pred :: FieldZeroPadding -> FieldZeroPadding
$ctoEnum :: Int -> FieldZeroPadding
toEnum :: Int -> FieldZeroPadding
$cfromEnum :: FieldZeroPadding -> Int
fromEnum :: FieldZeroPadding -> Int
$cenumFrom :: FieldZeroPadding -> [FieldZeroPadding]
enumFrom :: FieldZeroPadding -> [FieldZeroPadding]
$cenumFromThen :: FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
enumFromThen :: FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
$cenumFromTo :: FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
enumFromTo :: FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
$cenumFromThenTo :: FieldZeroPadding
-> FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
enumFromThenTo :: FieldZeroPadding
-> FieldZeroPadding -> FieldZeroPadding -> [FieldZeroPadding]
Enum, FieldZeroPadding
FieldZeroPadding -> FieldZeroPadding -> Bounded FieldZeroPadding
forall a. a -> a -> Bounded a
$cminBound :: FieldZeroPadding
minBound :: FieldZeroPadding
$cmaxBound :: FieldZeroPadding
maxBound :: FieldZeroPadding
Bounded)
data FieldGrouping
= NoGrouping
| GroupComma
| GroupUnderscore
deriving (Int -> FieldGrouping -> ShowS
[FieldGrouping] -> ShowS
FieldGrouping -> String
(Int -> FieldGrouping -> ShowS)
-> (FieldGrouping -> String)
-> ([FieldGrouping] -> ShowS)
-> Show FieldGrouping
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldGrouping -> ShowS
showsPrec :: Int -> FieldGrouping -> ShowS
$cshow :: FieldGrouping -> String
show :: FieldGrouping -> String
$cshowList :: [FieldGrouping] -> ShowS
showList :: [FieldGrouping] -> ShowS
Show, FieldGrouping -> FieldGrouping -> Bool
(FieldGrouping -> FieldGrouping -> Bool)
-> (FieldGrouping -> FieldGrouping -> Bool) -> Eq FieldGrouping
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldGrouping -> FieldGrouping -> Bool
== :: FieldGrouping -> FieldGrouping -> Bool
$c/= :: FieldGrouping -> FieldGrouping -> Bool
/= :: FieldGrouping -> FieldGrouping -> Bool
Eq, Eq FieldGrouping
Eq FieldGrouping =>
(FieldGrouping -> FieldGrouping -> Ordering)
-> (FieldGrouping -> FieldGrouping -> Bool)
-> (FieldGrouping -> FieldGrouping -> Bool)
-> (FieldGrouping -> FieldGrouping -> Bool)
-> (FieldGrouping -> FieldGrouping -> Bool)
-> (FieldGrouping -> FieldGrouping -> FieldGrouping)
-> (FieldGrouping -> FieldGrouping -> FieldGrouping)
-> Ord FieldGrouping
FieldGrouping -> FieldGrouping -> Bool
FieldGrouping -> FieldGrouping -> Ordering
FieldGrouping -> FieldGrouping -> FieldGrouping
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldGrouping -> FieldGrouping -> Ordering
compare :: FieldGrouping -> FieldGrouping -> Ordering
$c< :: FieldGrouping -> FieldGrouping -> Bool
< :: FieldGrouping -> FieldGrouping -> Bool
$c<= :: FieldGrouping -> FieldGrouping -> Bool
<= :: FieldGrouping -> FieldGrouping -> Bool
$c> :: FieldGrouping -> FieldGrouping -> Bool
> :: FieldGrouping -> FieldGrouping -> Bool
$c>= :: FieldGrouping -> FieldGrouping -> Bool
>= :: FieldGrouping -> FieldGrouping -> Bool
$cmax :: FieldGrouping -> FieldGrouping -> FieldGrouping
max :: FieldGrouping -> FieldGrouping -> FieldGrouping
$cmin :: FieldGrouping -> FieldGrouping -> FieldGrouping
min :: FieldGrouping -> FieldGrouping -> FieldGrouping
Ord, Int -> FieldGrouping
FieldGrouping -> Int
FieldGrouping -> [FieldGrouping]
FieldGrouping -> FieldGrouping
FieldGrouping -> FieldGrouping -> [FieldGrouping]
FieldGrouping -> FieldGrouping -> FieldGrouping -> [FieldGrouping]
(FieldGrouping -> FieldGrouping)
-> (FieldGrouping -> FieldGrouping)
-> (Int -> FieldGrouping)
-> (FieldGrouping -> Int)
-> (FieldGrouping -> [FieldGrouping])
-> (FieldGrouping -> FieldGrouping -> [FieldGrouping])
-> (FieldGrouping -> FieldGrouping -> [FieldGrouping])
-> (FieldGrouping
-> FieldGrouping -> FieldGrouping -> [FieldGrouping])
-> Enum FieldGrouping
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldGrouping -> FieldGrouping
succ :: FieldGrouping -> FieldGrouping
$cpred :: FieldGrouping -> FieldGrouping
pred :: FieldGrouping -> FieldGrouping
$ctoEnum :: Int -> FieldGrouping
toEnum :: Int -> FieldGrouping
$cfromEnum :: FieldGrouping -> Int
fromEnum :: FieldGrouping -> Int
$cenumFrom :: FieldGrouping -> [FieldGrouping]
enumFrom :: FieldGrouping -> [FieldGrouping]
$cenumFromThen :: FieldGrouping -> FieldGrouping -> [FieldGrouping]
enumFromThen :: FieldGrouping -> FieldGrouping -> [FieldGrouping]
$cenumFromTo :: FieldGrouping -> FieldGrouping -> [FieldGrouping]
enumFromTo :: FieldGrouping -> FieldGrouping -> [FieldGrouping]
$cenumFromThenTo :: FieldGrouping -> FieldGrouping -> FieldGrouping -> [FieldGrouping]
enumFromThenTo :: FieldGrouping -> FieldGrouping -> FieldGrouping -> [FieldGrouping]
Enum, FieldGrouping
FieldGrouping -> FieldGrouping -> Bounded FieldGrouping
forall a. a -> a -> Bounded a
$cminBound :: FieldGrouping
minBound :: FieldGrouping
$cmaxBound :: FieldGrouping
maxBound :: FieldGrouping
Bounded)
data FieldSign
= SignNegative
| SignSpacePadded
| SignAlways
deriving (Int -> FieldSign -> ShowS
[FieldSign] -> ShowS
FieldSign -> String
(Int -> FieldSign -> ShowS)
-> (FieldSign -> String)
-> ([FieldSign] -> ShowS)
-> Show FieldSign
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldSign -> ShowS
showsPrec :: Int -> FieldSign -> ShowS
$cshow :: FieldSign -> String
show :: FieldSign -> String
$cshowList :: [FieldSign] -> ShowS
showList :: [FieldSign] -> ShowS
Show, FieldSign -> FieldSign -> Bool
(FieldSign -> FieldSign -> Bool)
-> (FieldSign -> FieldSign -> Bool) -> Eq FieldSign
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldSign -> FieldSign -> Bool
== :: FieldSign -> FieldSign -> Bool
$c/= :: FieldSign -> FieldSign -> Bool
/= :: FieldSign -> FieldSign -> Bool
Eq, Eq FieldSign
Eq FieldSign =>
(FieldSign -> FieldSign -> Ordering)
-> (FieldSign -> FieldSign -> Bool)
-> (FieldSign -> FieldSign -> Bool)
-> (FieldSign -> FieldSign -> Bool)
-> (FieldSign -> FieldSign -> Bool)
-> (FieldSign -> FieldSign -> FieldSign)
-> (FieldSign -> FieldSign -> FieldSign)
-> Ord FieldSign
FieldSign -> FieldSign -> Bool
FieldSign -> FieldSign -> Ordering
FieldSign -> FieldSign -> FieldSign
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldSign -> FieldSign -> Ordering
compare :: FieldSign -> FieldSign -> Ordering
$c< :: FieldSign -> FieldSign -> Bool
< :: FieldSign -> FieldSign -> Bool
$c<= :: FieldSign -> FieldSign -> Bool
<= :: FieldSign -> FieldSign -> Bool
$c> :: FieldSign -> FieldSign -> Bool
> :: FieldSign -> FieldSign -> Bool
$c>= :: FieldSign -> FieldSign -> Bool
>= :: FieldSign -> FieldSign -> Bool
$cmax :: FieldSign -> FieldSign -> FieldSign
max :: FieldSign -> FieldSign -> FieldSign
$cmin :: FieldSign -> FieldSign -> FieldSign
min :: FieldSign -> FieldSign -> FieldSign
Ord, Int -> FieldSign
FieldSign -> Int
FieldSign -> [FieldSign]
FieldSign -> FieldSign
FieldSign -> FieldSign -> [FieldSign]
FieldSign -> FieldSign -> FieldSign -> [FieldSign]
(FieldSign -> FieldSign)
-> (FieldSign -> FieldSign)
-> (Int -> FieldSign)
-> (FieldSign -> Int)
-> (FieldSign -> [FieldSign])
-> (FieldSign -> FieldSign -> [FieldSign])
-> (FieldSign -> FieldSign -> [FieldSign])
-> (FieldSign -> FieldSign -> FieldSign -> [FieldSign])
-> Enum FieldSign
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldSign -> FieldSign
succ :: FieldSign -> FieldSign
$cpred :: FieldSign -> FieldSign
pred :: FieldSign -> FieldSign
$ctoEnum :: Int -> FieldSign
toEnum :: Int -> FieldSign
$cfromEnum :: FieldSign -> Int
fromEnum :: FieldSign -> Int
$cenumFrom :: FieldSign -> [FieldSign]
enumFrom :: FieldSign -> [FieldSign]
$cenumFromThen :: FieldSign -> FieldSign -> [FieldSign]
enumFromThen :: FieldSign -> FieldSign -> [FieldSign]
$cenumFromTo :: FieldSign -> FieldSign -> [FieldSign]
enumFromTo :: FieldSign -> FieldSign -> [FieldSign]
$cenumFromThenTo :: FieldSign -> FieldSign -> FieldSign -> [FieldSign]
enumFromThenTo :: FieldSign -> FieldSign -> FieldSign -> [FieldSign]
Enum, FieldSign
FieldSign -> FieldSign -> Bounded FieldSign
forall a. a -> a -> Bounded a
$cminBound :: FieldSign
minBound :: FieldSign
$cmaxBound :: FieldSign
maxBound :: FieldSign
Bounded)
data FieldType
= FieldTypeString
| FieldTypeBinary
| FieldTypeCharacter
| FieldTypeDecimalInt
| FieldTypeOctal
| FieldTypeHex
| FieldTypeHexUpper
| FieldTypeNumber
| FieldTypeScientific
| FieldTypeScientificUpper
| FieldTypeFixedPoint
| FieldTypeFixedPointUpper
| FieldTypeGeneral
| FieldTypeGeneralUpper
| FieldTypePercentage
deriving (Int -> FieldType -> ShowS
[FieldType] -> ShowS
FieldType -> String
(Int -> FieldType -> ShowS)
-> (FieldType -> String)
-> ([FieldType] -> ShowS)
-> Show FieldType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldType -> ShowS
showsPrec :: Int -> FieldType -> ShowS
$cshow :: FieldType -> String
show :: FieldType -> String
$cshowList :: [FieldType] -> ShowS
showList :: [FieldType] -> ShowS
Show, FieldType -> FieldType -> Bool
(FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool) -> Eq FieldType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldType -> FieldType -> Bool
== :: FieldType -> FieldType -> Bool
$c/= :: FieldType -> FieldType -> Bool
/= :: FieldType -> FieldType -> Bool
Eq, Eq FieldType
Eq FieldType =>
(FieldType -> FieldType -> Ordering)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> FieldType)
-> (FieldType -> FieldType -> FieldType)
-> Ord FieldType
FieldType -> FieldType -> Bool
FieldType -> FieldType -> Ordering
FieldType -> FieldType -> FieldType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldType -> FieldType -> Ordering
compare :: FieldType -> FieldType -> Ordering
$c< :: FieldType -> FieldType -> Bool
< :: FieldType -> FieldType -> Bool
$c<= :: FieldType -> FieldType -> Bool
<= :: FieldType -> FieldType -> Bool
$c> :: FieldType -> FieldType -> Bool
> :: FieldType -> FieldType -> Bool
$c>= :: FieldType -> FieldType -> Bool
>= :: FieldType -> FieldType -> Bool
$cmax :: FieldType -> FieldType -> FieldType
max :: FieldType -> FieldType -> FieldType
$cmin :: FieldType -> FieldType -> FieldType
min :: FieldType -> FieldType -> FieldType
Ord, Int -> FieldType
FieldType -> Int
FieldType -> [FieldType]
FieldType -> FieldType
FieldType -> FieldType -> [FieldType]
FieldType -> FieldType -> FieldType -> [FieldType]
(FieldType -> FieldType)
-> (FieldType -> FieldType)
-> (Int -> FieldType)
-> (FieldType -> Int)
-> (FieldType -> [FieldType])
-> (FieldType -> FieldType -> [FieldType])
-> (FieldType -> FieldType -> [FieldType])
-> (FieldType -> FieldType -> FieldType -> [FieldType])
-> Enum FieldType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldType -> FieldType
succ :: FieldType -> FieldType
$cpred :: FieldType -> FieldType
pred :: FieldType -> FieldType
$ctoEnum :: Int -> FieldType
toEnum :: Int -> FieldType
$cfromEnum :: FieldType -> Int
fromEnum :: FieldType -> Int
$cenumFrom :: FieldType -> [FieldType]
enumFrom :: FieldType -> [FieldType]
$cenumFromThen :: FieldType -> FieldType -> [FieldType]
enumFromThen :: FieldType -> FieldType -> [FieldType]
$cenumFromTo :: FieldType -> FieldType -> [FieldType]
enumFromTo :: FieldType -> FieldType -> [FieldType]
$cenumFromThenTo :: FieldType -> FieldType -> FieldType -> [FieldType]
enumFromThenTo :: FieldType -> FieldType -> FieldType -> [FieldType]
Enum, FieldType
FieldType -> FieldType -> Bounded FieldType
forall a. a -> a -> Bounded a
$cminBound :: FieldType
minBound :: FieldType
$cmaxBound :: FieldType
maxBound :: FieldType
Bounded)
data FieldAlign
= AlignLeft
| AlignRight
| AlignCenter
| AlignZeroPad
deriving (Int -> FieldAlign -> ShowS
[FieldAlign] -> ShowS
FieldAlign -> String
(Int -> FieldAlign -> ShowS)
-> (FieldAlign -> String)
-> ([FieldAlign] -> ShowS)
-> Show FieldAlign
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldAlign -> ShowS
showsPrec :: Int -> FieldAlign -> ShowS
$cshow :: FieldAlign -> String
show :: FieldAlign -> String
$cshowList :: [FieldAlign] -> ShowS
showList :: [FieldAlign] -> ShowS
Show, FieldAlign -> FieldAlign -> Bool
(FieldAlign -> FieldAlign -> Bool)
-> (FieldAlign -> FieldAlign -> Bool) -> Eq FieldAlign
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldAlign -> FieldAlign -> Bool
== :: FieldAlign -> FieldAlign -> Bool
$c/= :: FieldAlign -> FieldAlign -> Bool
/= :: FieldAlign -> FieldAlign -> Bool
Eq, Eq FieldAlign
Eq FieldAlign =>
(FieldAlign -> FieldAlign -> Ordering)
-> (FieldAlign -> FieldAlign -> Bool)
-> (FieldAlign -> FieldAlign -> Bool)
-> (FieldAlign -> FieldAlign -> Bool)
-> (FieldAlign -> FieldAlign -> Bool)
-> (FieldAlign -> FieldAlign -> FieldAlign)
-> (FieldAlign -> FieldAlign -> FieldAlign)
-> Ord FieldAlign
FieldAlign -> FieldAlign -> Bool
FieldAlign -> FieldAlign -> Ordering
FieldAlign -> FieldAlign -> FieldAlign
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldAlign -> FieldAlign -> Ordering
compare :: FieldAlign -> FieldAlign -> Ordering
$c< :: FieldAlign -> FieldAlign -> Bool
< :: FieldAlign -> FieldAlign -> Bool
$c<= :: FieldAlign -> FieldAlign -> Bool
<= :: FieldAlign -> FieldAlign -> Bool
$c> :: FieldAlign -> FieldAlign -> Bool
> :: FieldAlign -> FieldAlign -> Bool
$c>= :: FieldAlign -> FieldAlign -> Bool
>= :: FieldAlign -> FieldAlign -> Bool
$cmax :: FieldAlign -> FieldAlign -> FieldAlign
max :: FieldAlign -> FieldAlign -> FieldAlign
$cmin :: FieldAlign -> FieldAlign -> FieldAlign
min :: FieldAlign -> FieldAlign -> FieldAlign
Ord, Int -> FieldAlign
FieldAlign -> Int
FieldAlign -> [FieldAlign]
FieldAlign -> FieldAlign
FieldAlign -> FieldAlign -> [FieldAlign]
FieldAlign -> FieldAlign -> FieldAlign -> [FieldAlign]
(FieldAlign -> FieldAlign)
-> (FieldAlign -> FieldAlign)
-> (Int -> FieldAlign)
-> (FieldAlign -> Int)
-> (FieldAlign -> [FieldAlign])
-> (FieldAlign -> FieldAlign -> [FieldAlign])
-> (FieldAlign -> FieldAlign -> [FieldAlign])
-> (FieldAlign -> FieldAlign -> FieldAlign -> [FieldAlign])
-> Enum FieldAlign
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldAlign -> FieldAlign
succ :: FieldAlign -> FieldAlign
$cpred :: FieldAlign -> FieldAlign
pred :: FieldAlign -> FieldAlign
$ctoEnum :: Int -> FieldAlign
toEnum :: Int -> FieldAlign
$cfromEnum :: FieldAlign -> Int
fromEnum :: FieldAlign -> Int
$cenumFrom :: FieldAlign -> [FieldAlign]
enumFrom :: FieldAlign -> [FieldAlign]
$cenumFromThen :: FieldAlign -> FieldAlign -> [FieldAlign]
enumFromThen :: FieldAlign -> FieldAlign -> [FieldAlign]
$cenumFromTo :: FieldAlign -> FieldAlign -> [FieldAlign]
enumFromTo :: FieldAlign -> FieldAlign -> [FieldAlign]
$cenumFromThenTo :: FieldAlign -> FieldAlign -> FieldAlign -> [FieldAlign]
enumFromThenTo :: FieldAlign -> FieldAlign -> FieldAlign -> [FieldAlign]
Enum, FieldAlign
FieldAlign -> FieldAlign -> Bounded FieldAlign
forall a. a -> a -> Bounded a
$cminBound :: FieldAlign
minBound :: FieldAlign
$cmaxBound :: FieldAlign
maxBound :: FieldAlign
Bounded)
data OrDefault a
= Default
| Specific a
deriving (Int -> OrDefault a -> ShowS
[OrDefault a] -> ShowS
OrDefault a -> String
(Int -> OrDefault a -> ShowS)
-> (OrDefault a -> String)
-> ([OrDefault a] -> ShowS)
-> Show (OrDefault a)
forall a. Show a => Int -> OrDefault a -> ShowS
forall a. Show a => [OrDefault a] -> ShowS
forall a. Show a => OrDefault a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> OrDefault a -> ShowS
showsPrec :: Int -> OrDefault a -> ShowS
$cshow :: forall a. Show a => OrDefault a -> String
show :: OrDefault a -> String
$cshowList :: forall a. Show a => [OrDefault a] -> ShowS
showList :: [OrDefault a] -> ShowS
Show, OrDefault a -> OrDefault a -> Bool
(OrDefault a -> OrDefault a -> Bool)
-> (OrDefault a -> OrDefault a -> Bool) -> Eq (OrDefault a)
forall a. Eq a => OrDefault a -> OrDefault a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => OrDefault a -> OrDefault a -> Bool
== :: OrDefault a -> OrDefault a -> Bool
$c/= :: forall a. Eq a => OrDefault a -> OrDefault a -> Bool
/= :: OrDefault a -> OrDefault a -> Bool
Eq, Eq (OrDefault a)
Eq (OrDefault a) =>
(OrDefault a -> OrDefault a -> Ordering)
-> (OrDefault a -> OrDefault a -> Bool)
-> (OrDefault a -> OrDefault a -> Bool)
-> (OrDefault a -> OrDefault a -> Bool)
-> (OrDefault a -> OrDefault a -> Bool)
-> (OrDefault a -> OrDefault a -> OrDefault a)
-> (OrDefault a -> OrDefault a -> OrDefault a)
-> Ord (OrDefault a)
OrDefault a -> OrDefault a -> Bool
OrDefault a -> OrDefault a -> Ordering
OrDefault a -> OrDefault a -> OrDefault a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (OrDefault a)
forall a. Ord a => OrDefault a -> OrDefault a -> Bool
forall a. Ord a => OrDefault a -> OrDefault a -> Ordering
forall a. Ord a => OrDefault a -> OrDefault a -> OrDefault a
$ccompare :: forall a. Ord a => OrDefault a -> OrDefault a -> Ordering
compare :: OrDefault a -> OrDefault a -> Ordering
$c< :: forall a. Ord a => OrDefault a -> OrDefault a -> Bool
< :: OrDefault a -> OrDefault a -> Bool
$c<= :: forall a. Ord a => OrDefault a -> OrDefault a -> Bool
<= :: OrDefault a -> OrDefault a -> Bool
$c> :: forall a. Ord a => OrDefault a -> OrDefault a -> Bool
> :: OrDefault a -> OrDefault a -> Bool
$c>= :: forall a. Ord a => OrDefault a -> OrDefault a -> Bool
>= :: OrDefault a -> OrDefault a -> Bool
$cmax :: forall a. Ord a => OrDefault a -> OrDefault a -> OrDefault a
max :: OrDefault a -> OrDefault a -> OrDefault a
$cmin :: forall a. Ord a => OrDefault a -> OrDefault a -> OrDefault a
min :: OrDefault a -> OrDefault a -> OrDefault a
Ord, (forall a b. (a -> b) -> OrDefault a -> OrDefault b)
-> (forall a b. a -> OrDefault b -> OrDefault a)
-> Functor OrDefault
forall a b. a -> OrDefault b -> OrDefault a
forall a b. (a -> b) -> OrDefault a -> OrDefault b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> OrDefault a -> OrDefault b
fmap :: forall a b. (a -> b) -> OrDefault a -> OrDefault b
$c<$ :: forall a b. a -> OrDefault b -> OrDefault a
<$ :: forall a b. a -> OrDefault b -> OrDefault a
Functor)
fromDefault :: a -> OrDefault a -> a
fromDefault :: forall a. a -> OrDefault a -> a
fromDefault a
d OrDefault a
Default = a
d
fromDefault a
_ (Specific a
x) = a
x
data FieldSpec =
FieldSpec
{ FieldSpec -> OrDefault FieldAlign
fieldSpecAlign :: !(OrDefault FieldAlign)
, FieldSpec -> OrDefault Char
fieldSpecFill :: !(OrDefault Char)
, FieldSpec -> FieldSign
fieldSpecSign :: !FieldSign
, FieldSpec -> FieldZeroCoercion
fieldSpecZeroCoercion :: !FieldZeroCoercion
, FieldSpec -> FieldAlternateForm
fieldSpecAlternateForm :: !FieldAlternateForm
, FieldSpec -> FieldZeroPadding
fieldSpecZeroPadding :: !FieldZeroPadding
, FieldSpec -> OrDefault Int
fieldSpecWidth :: !(OrDefault Int)
, FieldSpec -> FieldGrouping
fieldSpecGrouping :: !FieldGrouping
, FieldSpec -> OrDefault Int
fieldSpecPrecision :: !(OrDefault Int)
, FieldSpec -> FieldType
fieldSpecType :: !FieldType
}
deriving (Int -> FieldSpec -> ShowS
[FieldSpec] -> ShowS
FieldSpec -> String
(Int -> FieldSpec -> ShowS)
-> (FieldSpec -> String)
-> ([FieldSpec] -> ShowS)
-> Show FieldSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldSpec -> ShowS
showsPrec :: Int -> FieldSpec -> ShowS
$cshow :: FieldSpec -> String
show :: FieldSpec -> String
$cshowList :: [FieldSpec] -> ShowS
showList :: [FieldSpec] -> ShowS
Show, FieldSpec -> FieldSpec -> Bool
(FieldSpec -> FieldSpec -> Bool)
-> (FieldSpec -> FieldSpec -> Bool) -> Eq FieldSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldSpec -> FieldSpec -> Bool
== :: FieldSpec -> FieldSpec -> Bool
$c/= :: FieldSpec -> FieldSpec -> Bool
/= :: FieldSpec -> FieldSpec -> Bool
Eq)
defFieldSpec :: FieldSpec
defFieldSpec :: FieldSpec
defFieldSpec =
FieldSpec
{ fieldSpecAlign :: OrDefault FieldAlign
fieldSpecAlign = OrDefault FieldAlign
forall a. OrDefault a
Default
, fieldSpecFill :: OrDefault Char
fieldSpecFill = OrDefault Char
forall a. OrDefault a
Default
, fieldSpecSign :: FieldSign
fieldSpecSign = FieldSign
SignNegative
, fieldSpecZeroCoercion :: FieldZeroCoercion
fieldSpecZeroCoercion = FieldZeroCoercion
AllowNegativeZero
, fieldSpecAlternateForm :: FieldAlternateForm
fieldSpecAlternateForm = FieldAlternateForm
NormalForm
, fieldSpecZeroPadding :: FieldZeroPadding
fieldSpecZeroPadding = FieldZeroPadding
NoZeroPadding
, fieldSpecWidth :: OrDefault Int
fieldSpecWidth = OrDefault Int
forall a. OrDefault a
Default
, fieldSpecGrouping :: FieldGrouping
fieldSpecGrouping = FieldGrouping
NoGrouping
, fieldSpecPrecision :: OrDefault Int
fieldSpecPrecision = OrDefault Int
forall a. OrDefault a
Default
, fieldSpecType :: FieldType
fieldSpecType = FieldType
FieldTypeGeneral
}
type P a = P.Parsec Void Text a
pFormat :: P [FormatItem]
pFormat :: Parsec Void Text [FormatItem]
pFormat = ParsecT Void Text Identity FormatItem
-> Parsec Void Text [FormatItem]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
P.many ParsecT Void Text Identity FormatItem
pFormatItem Parsec Void Text [FormatItem]
-> ParsecT Void Text Identity () -> Parsec Void Text [FormatItem]
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Void Text Identity ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
P.eof
pFormatItem :: P FormatItem
pFormatItem :: ParsecT Void Text Identity FormatItem
pFormatItem = [ParsecT Void Text Identity FormatItem]
-> ParsecT Void Text Identity FormatItem
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ Text -> FormatItem
PlainFormatItem (Text -> FormatItem)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity FormatItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
P.chunk Text
Tokens Text
"{{"
, Text -> FormatItem
PlainFormatItem (Text -> FormatItem)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity FormatItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tokens Text -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
P.chunk Text
Tokens Text
"}}"
, FormatField -> FormatItem
FieldFormatItem (FormatField -> FormatItem)
-> ParsecT Void Text Identity FormatField
-> ParsecT Void Text Identity FormatItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'{' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FormatField
-> ParsecT Void Text Identity FormatField
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Void Text Identity FormatField
pFormatField ParsecT Void Text Identity FormatField
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FormatField
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'}')
, Text -> FormatItem
PlainFormatItem (Text -> FormatItem)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity FormatItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
P.takeWhile1P Maybe String
forall a. Maybe a
Nothing (Token Text -> Token Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
Token Text
'{')
]
pFormatField :: P FormatField
pFormatField :: ParsecT Void Text Identity FormatField
pFormatField =
OrDefault FieldName -> FieldConversion -> FieldSpec -> FormatField
FormatField
(OrDefault FieldName
-> FieldConversion -> FieldSpec -> FormatField)
-> ParsecT Void Text Identity (OrDefault FieldName)
-> ParsecT
Void Text Identity (FieldConversion -> FieldSpec -> FormatField)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrDefault FieldName
-> ParsecT Void Text Identity (OrDefault FieldName)
-> ParsecT Void Text Identity (OrDefault FieldName)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
P.option OrDefault FieldName
forall a. OrDefault a
Default (FieldName -> OrDefault FieldName
forall a. a -> OrDefault a
Specific (FieldName -> OrDefault FieldName)
-> ParsecT Void Text Identity FieldName
-> ParsecT Void Text Identity (OrDefault FieldName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity FieldName
pFieldName)
ParsecT
Void Text Identity (FieldConversion -> FieldSpec -> FormatField)
-> ParsecT Void Text Identity FieldConversion
-> ParsecT Void Text Identity (FieldSpec -> FormatField)
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldConversion
-> ParsecT Void Text Identity FieldConversion
-> ParsecT Void Text Identity FieldConversion
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
P.option FieldConversion
FieldConvNone ParsecT Void Text Identity FieldConversion
pFieldConv
ParsecT Void Text Identity (FieldSpec -> FormatField)
-> ParsecT Void Text Identity FieldSpec
-> ParsecT Void Text Identity FormatField
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldSpec
-> ParsecT Void Text Identity FieldSpec
-> ParsecT Void Text Identity FieldSpec
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
P.option FieldSpec
defFieldSpec ParsecT Void Text Identity FieldSpec
pFieldSpec
pFieldName :: P FieldName
pFieldName :: ParsecT Void Text Identity FieldName
pFieldName = do
base <- [ParsecT Void Text Identity FieldName]
-> ParsecT Void Text Identity FieldName
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ Text -> FieldName
FieldNameIdentifier (Text -> FieldName)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity FieldName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
pIdentifier
, Integer -> FieldName
FieldNameNumber (Integer -> FieldName)
-> ParsecT Void Text Identity Integer
-> ParsecT Void Text Identity FieldName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Integer
forall a. Num a => P a
pInteger
]
pTail base
where
pTail :: FieldName -> ParsecT Void Text Identity FieldName
pTail FieldName
base = [ParsecT Void Text Identity FieldName]
-> ParsecT Void Text Identity FieldName
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ FieldName -> ParsecT Void Text Identity FieldName
pDotTail FieldName
base ParsecT Void Text Identity FieldName
-> (FieldName -> ParsecT Void Text Identity FieldName)
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity a
-> (a -> ParsecT Void Text Identity b)
-> ParsecT Void Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FieldName -> ParsecT Void Text Identity FieldName
pTail
, FieldName -> ParsecT Void Text Identity FieldName
pIndexTail FieldName
base ParsecT Void Text Identity FieldName
-> (FieldName -> ParsecT Void Text Identity FieldName)
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity a
-> (a -> ParsecT Void Text Identity b)
-> ParsecT Void Text Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FieldName -> ParsecT Void Text Identity FieldName
pTail
, FieldName -> ParsecT Void Text Identity FieldName
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldName
base
]
pDotTail :: FieldName -> ParsecT Void Text Identity FieldName
pDotTail FieldName
base = do
ParsecT Void Text Identity Char -> ParsecT Void Text Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text Identity Char -> ParsecT Void Text Identity ())
-> ParsecT Void Text Identity Char -> ParsecT Void Text Identity ()
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'.'
Text -> FieldName -> FieldName
FieldNameAttrib (Text -> FieldName -> FieldName)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (FieldName -> FieldName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
pIdentifier ParsecT Void Text Identity (FieldName -> FieldName)
-> ParsecT Void Text Identity FieldName
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName -> ParsecT Void Text Identity FieldName
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldName
base
pIndexTail :: FieldName -> ParsecT Void Text Identity FieldName
pIndexTail FieldName
base =
Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'[' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldName
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
[ParsecT Void Text Identity FieldName]
-> ParsecT Void Text Identity FieldName
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ Text -> FieldName -> FieldName
FieldNameKeyIndex (Text -> FieldName -> FieldName)
-> ParsecT Void Text Identity Text
-> ParsecT Void Text Identity (FieldName -> FieldName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Text
pIdentifier ParsecT Void Text Identity (FieldName -> FieldName)
-> ParsecT Void Text Identity FieldName
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName -> ParsecT Void Text Identity FieldName
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldName
base
, Integer -> FieldName -> FieldName
FieldNameNumIndex (Integer -> FieldName -> FieldName)
-> ParsecT Void Text Identity Integer
-> ParsecT Void Text Identity (FieldName -> FieldName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Integer
forall a. Num a => P a
pInteger ParsecT Void Text Identity (FieldName -> FieldName)
-> ParsecT Void Text Identity FieldName
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName -> ParsecT Void Text Identity FieldName
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldName
base
]
ParsecT Void Text Identity FieldName
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldName
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
']'
pInteger :: Num a => P a
pInteger :: forall a. Num a => P a
pInteger = do
digits <- Maybe String
-> (Token Text -> Bool) -> ParsecT Void Text Identity (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
P.takeWhile1P (String -> Maybe String
forall a. a -> Maybe a
Just String
"digit") Char -> Bool
Token Text -> Bool
isDigit
pure . fromInteger . read . Text.unpack $ digits
pIdentifier :: P Text
pIdentifier :: ParsecT Void Text Identity Text
pIdentifier = do
t0 <- (Token Text -> Bool) -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
P.satisfy Char -> Bool
Token Text -> Bool
isIdentStartChar
ts <- P.takeWhileP (Just "identifier char") isIdentChar
pure $ Text.cons t0 ts
identStartCategories :: Set GeneralCategory
identStartCategories :: Set GeneralCategory
identStartCategories =
[GeneralCategory] -> Set GeneralCategory
forall a. Ord a => [a] -> Set a
Set.fromList
[ GeneralCategory
UppercaseLetter
, GeneralCategory
LowercaseLetter
, GeneralCategory
TitlecaseLetter
, GeneralCategory
ModifierLetter
, GeneralCategory
OtherLetter
, GeneralCategory
LetterNumber
]
identCategories :: Set GeneralCategory
identCategories :: Set GeneralCategory
identCategories =
Set GeneralCategory
identStartCategories Set GeneralCategory -> Set GeneralCategory -> Set GeneralCategory
forall a. Semigroup a => a -> a -> a
<>
[GeneralCategory] -> Set GeneralCategory
forall a. Ord a => [a] -> Set a
Set.fromList
[ GeneralCategory
NonSpacingMark
, GeneralCategory
SpacingCombiningMark
, GeneralCategory
DecimalNumber
, GeneralCategory
ConnectorPunctuation
]
identStartCharacters :: Set Char
identStartCharacters :: Set Char
identStartCharacters =
String -> Set Char
forall a. Ord a => [a] -> Set a
Set.fromList
[ Char
'_'
, Char
'\x1885'
, Char
'\x1886'
, Char
'\x2118'
, Char
'\x212E'
, Char
'\x309B'
, Char
'\x309C'
]
identCharacters :: Set Char
identCharacters :: Set Char
identCharacters =
Set Char
identStartCharacters Set Char -> Set Char -> Set Char
forall a. Semigroup a => a -> a -> a
<>
String -> Set Char
forall a. Ord a => [a] -> Set a
Set.fromList
[ Char
'\x00B7'
, Char
'\x0387'
, Char
'\x1369'
, Char
'\x1370'
, Char
'\x1371'
, Char
'\x19DA'
, Char
'\x200C'
, Char
'\x200D'
, Char
'\xFF65'
]
isIdentStartChar :: Char -> Bool
isIdentStartChar :: Char -> Bool
isIdentStartChar Char
c =
Char
c Char -> Set Char -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Char
identStartCharacters Bool -> Bool -> Bool
||
Char -> GeneralCategory
generalCategory Char
c GeneralCategory -> Set GeneralCategory -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set GeneralCategory
identStartCategories
isIdentChar :: Char -> Bool
isIdentChar :: Char -> Bool
isIdentChar Char
c =
Char
c Char -> Set Char -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Char
identCharacters Bool -> Bool -> Bool
||
Char -> GeneralCategory
generalCategory Char
c GeneralCategory -> Set GeneralCategory -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set GeneralCategory
identCategories
pFieldConv :: P FieldConversion
pFieldConv :: ParsecT Void Text Identity FieldConversion
pFieldConv =
Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'!' ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldConversion
-> ParsecT Void Text Identity FieldConversion
forall a b.
ParsecT Void Text Identity a
-> ParsecT Void Text Identity b -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
[ParsecT Void Text Identity FieldConversion]
-> ParsecT Void Text Identity FieldConversion
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ FieldConversion
FieldConvRepr FieldConversion
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldConversion
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'r'
, FieldConversion
FieldConvString FieldConversion
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldConversion
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
's'
, FieldConversion
FieldConvASCII FieldConversion
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldConversion
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'a'
]
pFieldSpec :: P FieldSpec
pFieldSpec :: ParsecT Void Text Identity FieldSpec
pFieldSpec = do
ParsecT Void Text Identity Char -> ParsecT Void Text Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Void Text Identity Char -> ParsecT Void Text Identity ())
-> ParsecT Void Text Identity Char -> ParsecT Void Text Identity ()
forall a b. (a -> b) -> a -> b
$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
':'
(fill, alignment) <- P (OrDefault Char, OrDefault FieldAlign)
pFillAlign
FieldSpec
<$> pure alignment
<*> pure fill
<*> P.option (fieldSpecSign defFieldSpec) pFieldSign
<*> P.option (fieldSpecZeroCoercion defFieldSpec) pFieldZeroCoercion
<*> P.option (fieldSpecAlternateForm defFieldSpec) pFieldAlternateForm
<*> P.option (fieldSpecZeroPadding defFieldSpec) pFieldZeroPadding
<*> P.option Default (Specific <$> pInteger)
<*> P.option (fieldSpecGrouping defFieldSpec) pFieldGrouping
<*> P.option Default (Specific <$> pInteger)
<*> P.option (fieldSpecType defFieldSpec) pFieldType
pFillAlign :: P (OrDefault Char, OrDefault FieldAlign)
pFillAlign :: P (OrDefault Char, OrDefault FieldAlign)
pFillAlign =
[P (OrDefault Char, OrDefault FieldAlign)]
-> P (OrDefault Char, OrDefault FieldAlign)
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ P (OrDefault Char, OrDefault FieldAlign)
-> P (OrDefault Char, OrDefault FieldAlign)
forall a.
ParsecT Void Text Identity a -> ParsecT Void Text Identity a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
P.try (P (OrDefault Char, OrDefault FieldAlign)
-> P (OrDefault Char, OrDefault FieldAlign))
-> P (OrDefault Char, OrDefault FieldAlign)
-> P (OrDefault Char, OrDefault FieldAlign)
forall a b. (a -> b) -> a -> b
$
(,) (OrDefault Char
-> OrDefault FieldAlign -> (OrDefault Char, OrDefault FieldAlign))
-> ParsecT Void Text Identity (OrDefault Char)
-> ParsecT
Void
Text
Identity
(OrDefault FieldAlign -> (OrDefault Char, OrDefault FieldAlign))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> OrDefault Char
forall a. a -> OrDefault a
Specific (Char -> OrDefault Char)
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity (OrDefault Char)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity Char
ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *). MonadParsec e s m => m (Token s)
P.anySingle) ParsecT
Void
Text
Identity
(OrDefault FieldAlign -> (OrDefault Char, OrDefault FieldAlign))
-> ParsecT Void Text Identity (OrDefault FieldAlign)
-> P (OrDefault Char, OrDefault FieldAlign)
forall a b.
ParsecT Void Text Identity (a -> b)
-> ParsecT Void Text Identity a -> ParsecT Void Text Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (FieldAlign -> OrDefault FieldAlign
forall a. a -> OrDefault a
Specific (FieldAlign -> OrDefault FieldAlign)
-> ParsecT Void Text Identity FieldAlign
-> ParsecT Void Text Identity (OrDefault FieldAlign)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity FieldAlign
pFieldAlign)
, (OrDefault Char
forall a. OrDefault a
Default,) (OrDefault FieldAlign -> (OrDefault Char, OrDefault FieldAlign))
-> (FieldAlign -> OrDefault FieldAlign)
-> FieldAlign
-> (OrDefault Char, OrDefault FieldAlign)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldAlign -> OrDefault FieldAlign
forall a. a -> OrDefault a
Specific (FieldAlign -> (OrDefault Char, OrDefault FieldAlign))
-> ParsecT Void Text Identity FieldAlign
-> P (OrDefault Char, OrDefault FieldAlign)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Void Text Identity FieldAlign
pFieldAlign
, (OrDefault Char, OrDefault FieldAlign)
-> P (OrDefault Char, OrDefault FieldAlign)
forall a. a -> ParsecT Void Text Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OrDefault Char
forall a. OrDefault a
Default, OrDefault FieldAlign
forall a. OrDefault a
Default)
]
pFieldAlign :: P FieldAlign
pFieldAlign :: ParsecT Void Text Identity FieldAlign
pFieldAlign =
[ParsecT Void Text Identity FieldAlign]
-> ParsecT Void Text Identity FieldAlign
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ FieldAlign
AlignLeft FieldAlign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldAlign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'<'
, FieldAlign
AlignRight FieldAlign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldAlign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'>'
, FieldAlign
AlignCenter FieldAlign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldAlign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'^'
, FieldAlign
AlignZeroPad FieldAlign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldAlign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'='
]
pFieldZeroCoercion :: P FieldZeroCoercion
pFieldZeroCoercion :: ParsecT Void Text Identity FieldZeroCoercion
pFieldZeroCoercion = FieldZeroCoercion
ForcePositiveZero FieldZeroCoercion
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldZeroCoercion
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'z'
pFieldSign :: P FieldSign
pFieldSign :: ParsecT Void Text Identity FieldSign
pFieldSign =
[ParsecT Void Text Identity FieldSign]
-> ParsecT Void Text Identity FieldSign
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ FieldSign
SignAlways FieldSign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldSign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'+'
, FieldSign
SignSpacePadded FieldSign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldSign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
' '
, FieldSign
SignNegative FieldSign
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldSign
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'-'
]
pFieldAlternateForm :: P FieldAlternateForm
pFieldAlternateForm :: ParsecT Void Text Identity FieldAlternateForm
pFieldAlternateForm = FieldAlternateForm
AlternateForm FieldAlternateForm
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldAlternateForm
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'#'
pFieldZeroPadding :: P FieldZeroPadding
pFieldZeroPadding :: ParsecT Void Text Identity FieldZeroPadding
pFieldZeroPadding = FieldZeroPadding
ZeroPadding FieldZeroPadding
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldZeroPadding
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'0'
pFieldGrouping :: P FieldGrouping
pFieldGrouping :: ParsecT Void Text Identity FieldGrouping
pFieldGrouping =
[ParsecT Void Text Identity FieldGrouping]
-> ParsecT Void Text Identity FieldGrouping
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ FieldGrouping
GroupComma FieldGrouping
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldGrouping
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
','
, FieldGrouping
GroupUnderscore FieldGrouping
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldGrouping
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'_'
]
pFieldType :: P FieldType
pFieldType :: ParsecT Void Text Identity FieldType
pFieldType =
[ParsecT Void Text Identity FieldType]
-> ParsecT Void Text Identity FieldType
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
P.choice
[ FieldType
FieldTypeString FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
's'
, FieldType
FieldTypeBinary FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'b'
, FieldType
FieldTypeCharacter FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'c'
, FieldType
FieldTypeDecimalInt FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'd'
, FieldType
FieldTypeOctal FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'o'
, FieldType
FieldTypeHex FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'x'
, FieldType
FieldTypeHexUpper FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'X'
, FieldType
FieldTypeNumber FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'n'
, FieldType
FieldTypeScientific FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'e'
, FieldType
FieldTypeScientificUpper FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'E'
, FieldType
FieldTypeFixedPoint FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'f'
, FieldType
FieldTypeFixedPointUpper FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'F'
, FieldType
FieldTypeGeneral FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'g'
, FieldType
FieldTypeGeneralUpper FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'G'
, FieldType
FieldTypePercentage FieldType
-> ParsecT Void Text Identity Char
-> ParsecT Void Text Identity FieldType
forall a b.
a -> ParsecT Void Text Identity b -> ParsecT Void Text Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token Text -> ParsecT Void Text Identity (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
P.char Char
Token Text
'%'
]