module Data.Text.Format.Heavy.Parse.VarFormat
where
import Data.Maybe
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as B
import Text.Parsec
import Data.Text.Format.Heavy.Types
import Data.Text.Format.Heavy.Formats
pGenericFormat :: Parsec TL.Text st GenericFormat
pGenericFormat = do
mbFillAlign <- optionMaybe (try pFillAlign <?> "fill and align specification")
let fill = fromMaybe ' ' $ fst `fmap` mbFillAlign
let align = snd `fmap` mbFillAlign
mbSign <- optionMaybe (pSign <?> "sign specification")
let sign = fromMaybe OnlyNegative mbSign
mbLeading0x <- optionMaybe (pLeading0x <?> "leading 0x specification")
let leading0x = fromMaybe False mbLeading0x
mbWidth <- optionMaybe (pWidth <?> "width specification")
mbPrecision <- optionMaybe (pPrecision <?> "precision specification")
mbRadix <- optionMaybe (pRadix <?> "radix specification")
return $ GenericFormat {
gfFillChar = fill
, gfAlign = align
, gfSign = sign
, gfLeading0x = leading0x
, gfWidth = mbWidth
, gfPrecision = mbPrecision
, gfRadix = mbRadix
}
where
pAlign :: Parsec TL.Text st Align
pAlign = do
alignChar <- oneOf "<>^"
align <- case alignChar of
'<' -> return AlignLeft
'>' -> return AlignRight
'^' -> return AlignCenter
_ -> fail $ "Unexpected align char: " ++ [alignChar]
return align
pAlignWithFill :: Parsec TL.Text st (Char, Align)
pAlignWithFill = do
fill <- noneOf "<>=^"
align <- pAlign
return (fill, align)
pAlignWithoutFill :: Parsec TL.Text st (Char, Align)
pAlignWithoutFill = do
align <- pAlign
return (' ', align)
pFillAlign :: Parsec TL.Text st (Char, Align)
pFillAlign = do
try pAlignWithoutFill <|> pAlignWithFill
pSign :: Parsec TL.Text st Sign
pSign = do
signChar <- oneOf "+- "
sign <- case signChar of
'+' -> return Always
'-' -> return OnlyNegative
' ' -> return SpaceForPositive
_ -> fail $ "Unexpected sign char: " ++ [signChar]
return sign
pLeading0x :: Parsec TL.Text st Bool
pLeading0x = do
mbSharp <- optionMaybe $ char '#'
case mbSharp of
Nothing -> return False
Just _ -> return True
natural :: Parsec TL.Text st Int
natural = do
ws <- many1 $ oneOf "0123456789"
return $ read ws
pWidth :: Parsec TL.Text st Int
pWidth = natural
pPrecision :: Parsec TL.Text st Int
pPrecision = do
char '.'
natural
pRadix :: Parsec TL.Text st Radix
pRadix = do
rc <- oneOf "xhd"
case rc of
'x' -> return Hexadecimal
'h' -> return Hexadecimal
'd' -> return Decimal
parseGenericFormat :: TL.Text -> Either ParseError GenericFormat
parseGenericFormat text = runParser pGenericFormat () "<variable format specification>" text
pBoolFormat :: Parsec TL.Text st BoolFormat
pBoolFormat = do
true <- many $ noneOf ":,;"
oneOf ":,;"
false <- many $ anyChar
return $ BoolFormat (TL.pack true) (TL.pack false)
parseBoolFormat :: TL.Text -> Either ParseError BoolFormat
parseBoolFormat text = runParser pBoolFormat () "<boolean format specification>" text
parseMaybeFormat :: TL.Text -> Maybe (TL.Text, TL.Text)
parseMaybeFormat text =
let (xFmtStr, nothingStr) = TL.breakOnEnd "|" text
in if TL.null xFmtStr
then Nothing
else Just (TL.init xFmtStr, nothingStr)