{-# LANGUAGE FlexibleContexts, OverloadedStrings, TypeFamilies, PackageImports #-}
module Hledger.Data.StringFormat (
parseStringFormat
, defaultStringFormatStyle
, StringFormat(..)
, StringFormatComponent(..)
, ReportItemField(..)
, tests_StringFormat
) where
import Prelude ()
import "base-compat-batteries" Prelude.Compat
import Numeric
import Data.Char (isPrint)
import Data.Maybe
import qualified Data.Text as T
import Text.Megaparsec
import Text.Megaparsec.Char
import Hledger.Utils.Parse
import Hledger.Utils.String (formatString)
import Hledger.Utils.Test
data StringFormat =
OneLine [StringFormatComponent]
| TopAligned [StringFormatComponent]
| BottomAligned [StringFormatComponent]
deriving (Show, Eq)
data StringFormatComponent =
FormatLiteral String
| FormatField Bool
(Maybe Int)
(Maybe Int)
ReportItemField
deriving (Show, Eq)
data ReportItemField =
AccountField
| DefaultDateField
| DescriptionField
| TotalField
| DepthSpacerField
| FieldNo Int
deriving (Show, Eq)
parseStringFormat :: String -> Either String StringFormat
parseStringFormat input = case (runParser (stringformatp <* eof) "(unknown)") input of
Left y -> Left $ show y
Right x -> Right x
defaultStringFormatStyle = BottomAligned
stringformatp :: SimpleStringParser StringFormat
stringformatp = do
alignspec <- optional (try $ char '%' >> oneOf ("^_,"::String))
let constructor =
case alignspec of
Just '^' -> TopAligned
Just '_' -> BottomAligned
Just ',' -> OneLine
_ -> defaultStringFormatStyle
constructor <$> many componentp
componentp :: SimpleStringParser StringFormatComponent
componentp = formatliteralp <|> formatfieldp
formatliteralp :: SimpleStringParser StringFormatComponent
formatliteralp = do
s <- some c
return $ FormatLiteral s
where
isPrintableButNotPercentage x = isPrint x && (not $ x == '%')
c = (satisfy isPrintableButNotPercentage <?> "printable character")
<|> try (string "%%" >> return '%')
formatfieldp :: SimpleStringParser StringFormatComponent
formatfieldp = do
char '%'
leftJustified <- optional (char '-')
minWidth <- optional (some $ digitChar)
maxWidth <- optional (do char '.'; some $ digitChar)
char '('
f <- fieldp
char ')'
return $ FormatField (isJust leftJustified) (parseDec minWidth) (parseDec maxWidth) f
where
parseDec s = case s of
Just text -> Just m where ((m,_):_) = readDec text
_ -> Nothing
fieldp :: SimpleStringParser ReportItemField
fieldp = do
try (string "account" >> return AccountField)
<|> try (string "depth_spacer" >> return DepthSpacerField)
<|> try (string "date" >> return DescriptionField)
<|> try (string "description" >> return DescriptionField)
<|> try (string "total" >> return TotalField)
<|> try (some digitChar >>= (\s -> return $ FieldNo $ read s))
formatStringTester fs value expected = actual `is` expected
where
actual = case fs of
FormatLiteral l -> formatString False Nothing Nothing l
FormatField leftJustify min max _ -> formatString leftJustify min max value
tests_StringFormat = tests "StringFormat" [
tests "formatStringHelper" [
formatStringTester (FormatLiteral " ") "" " "
, formatStringTester (FormatField False Nothing Nothing DescriptionField) "description" "description"
, formatStringTester (FormatField False (Just 20) Nothing DescriptionField) "description" " description"
, formatStringTester (FormatField False Nothing (Just 20) DescriptionField) "description" "description"
, formatStringTester (FormatField True Nothing (Just 20) DescriptionField) "description" "description"
, formatStringTester (FormatField True (Just 20) Nothing DescriptionField) "description" "description "
, formatStringTester (FormatField True (Just 20) (Just 20) DescriptionField) "description" "description "
, formatStringTester (FormatField True Nothing (Just 3) DescriptionField) "description" "des"
]
,tests "parseStringFormat" $
let s `gives` expected = test (T.pack s) $ parseStringFormat s `is` Right expected
in [
"" `gives` (defaultStringFormatStyle [])
, "D" `gives` (defaultStringFormatStyle [FormatLiteral "D"])
, "%(date)" `gives` (defaultStringFormatStyle [FormatField False Nothing Nothing DescriptionField])
, "%(total)" `gives` (defaultStringFormatStyle [FormatField False Nothing Nothing TotalField])
, "Hello %(date)!" `gives` (defaultStringFormatStyle [FormatLiteral "Hello ", FormatField False Nothing Nothing DescriptionField, FormatLiteral "!"])
, "%-(date)" `gives` (defaultStringFormatStyle [FormatField True Nothing Nothing DescriptionField])
, "%20(date)" `gives` (defaultStringFormatStyle [FormatField False (Just 20) Nothing DescriptionField])
, "%.10(date)" `gives` (defaultStringFormatStyle [FormatField False Nothing (Just 10) DescriptionField])
, "%20.10(date)" `gives` (defaultStringFormatStyle [FormatField False (Just 20) (Just 10) DescriptionField])
, "%20(account) %.10(total)" `gives` (defaultStringFormatStyle [FormatField False (Just 20) Nothing AccountField
,FormatLiteral " "
,FormatField False Nothing (Just 10) TotalField
])
, test "newline not parsed" $ expectLeft $ parseStringFormat "\n"
]
]