mirror of
https://github.com/simonmichael/hledger.git
synced 2024-12-28 21:02:04 +03:00
tests: convert & re-enable StringFormat tests
This commit is contained in:
parent
51618adc37
commit
54db19e857
@ -55,6 +55,7 @@ easytests_Data = tests "Data" [
|
||||
,easytests_Journal
|
||||
,easytests_Ledger
|
||||
,easytests_Posting
|
||||
,easytests_StringFormat
|
||||
,easytests_Timeclock
|
||||
,easytests_Transaction
|
||||
]
|
||||
|
@ -2,7 +2,7 @@
|
||||
-- hledger's report item fields. The formats are used by
|
||||
-- report-specific renderers like renderBalanceReportItem.
|
||||
|
||||
{-# LANGUAGE FlexibleContexts, TypeFamilies, PackageImports #-}
|
||||
{-# LANGUAGE FlexibleContexts, OverloadedStrings, TypeFamilies, PackageImports #-}
|
||||
|
||||
module Hledger.Data.StringFormat (
|
||||
parseStringFormat
|
||||
@ -10,7 +10,7 @@ module Hledger.Data.StringFormat (
|
||||
, StringFormat(..)
|
||||
, StringFormatComponent(..)
|
||||
, ReportItemField(..)
|
||||
, tests_Hledger_Data_StringFormat
|
||||
, easytests_StringFormat
|
||||
) where
|
||||
|
||||
import Prelude ()
|
||||
@ -18,7 +18,7 @@ import "base-compat-batteries" Prelude.Compat
|
||||
import Numeric
|
||||
import Data.Char (isPrint)
|
||||
import Data.Maybe
|
||||
import qualified Test.HUnit as U (test)
|
||||
import qualified Data.Text as T
|
||||
import Text.Megaparsec
|
||||
import Text.Megaparsec.Char
|
||||
|
||||
@ -90,7 +90,7 @@ defaultStringFormatStyle = BottomAligned
|
||||
|
||||
stringformatp :: SimpleStringParser StringFormat
|
||||
stringformatp = do
|
||||
alignspec <- optional (try $ char '%' >> oneOf "^_,")
|
||||
alignspec <- optional (try $ char '%' >> oneOf ("^_,"::String))
|
||||
let constructor =
|
||||
case alignspec of
|
||||
Just '^' -> TopAligned
|
||||
@ -137,47 +137,45 @@ fieldp = do
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
testFormat :: StringFormatComponent -> String -> String -> Assertion
|
||||
testFormat fs value expected = assertEqual name expected actual
|
||||
where
|
||||
(name, actual) = case fs of
|
||||
FormatLiteral l -> ("literal", formatString False Nothing Nothing l)
|
||||
FormatField leftJustify min max _ -> ("field", formatString leftJustify min max value)
|
||||
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
|
||||
|
||||
testParser :: String -> StringFormat -> Assertion
|
||||
testParser s expected = case (parseStringFormat s) of
|
||||
Left error -> assertFailure $ show error
|
||||
Right actual -> assertEqual ("Input: " ++ s) expected actual
|
||||
easytests_StringFormat = tests "StringFormat" [
|
||||
|
||||
tests_Hledger_Data_StringFormat = U.test [ formattingTests ++ parserTests ]
|
||||
|
||||
formattingTests = [
|
||||
testFormat (FormatLiteral " ") "" " "
|
||||
, testFormat (FormatField False Nothing Nothing DescriptionField) "description" "description"
|
||||
, testFormat (FormatField False (Just 20) Nothing DescriptionField) "description" " description"
|
||||
, testFormat (FormatField False Nothing (Just 20) DescriptionField) "description" "description"
|
||||
, testFormat (FormatField True Nothing (Just 20) DescriptionField) "description" "description"
|
||||
, testFormat (FormatField True (Just 20) Nothing DescriptionField) "description" "description "
|
||||
, testFormat (FormatField True (Just 20) (Just 20) DescriptionField) "description" "description "
|
||||
, testFormat (FormatField True Nothing (Just 3) DescriptionField) "description" "des"
|
||||
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"
|
||||
]
|
||||
|
||||
parserTests = [
|
||||
testParser "" (defaultStringFormatStyle [])
|
||||
, testParser "D" (defaultStringFormatStyle [FormatLiteral "D"])
|
||||
, testParser "%(date)" (defaultStringFormatStyle [FormatField False Nothing Nothing DescriptionField])
|
||||
, testParser "%(total)" (defaultStringFormatStyle [FormatField False Nothing Nothing TotalField])
|
||||
, testParser "^%(total)" (TopAligned [FormatField False Nothing Nothing TotalField])
|
||||
, testParser "_%(total)" (BottomAligned [FormatField False Nothing Nothing TotalField])
|
||||
, testParser ",%(total)" (OneLine [FormatField False Nothing Nothing TotalField])
|
||||
, testParser "Hello %(date)!" (defaultStringFormatStyle [FormatLiteral "Hello ", FormatField False Nothing Nothing DescriptionField, FormatLiteral "!"])
|
||||
, testParser "%-(date)" (defaultStringFormatStyle [FormatField True Nothing Nothing DescriptionField])
|
||||
, testParser "%20(date)" (defaultStringFormatStyle [FormatField False (Just 20) Nothing DescriptionField])
|
||||
, testParser "%.10(date)" (defaultStringFormatStyle [FormatField False Nothing (Just 10) DescriptionField])
|
||||
, testParser "%20.10(date)" (defaultStringFormatStyle [FormatField False (Just 20) (Just 10) DescriptionField])
|
||||
, testParser "%20(account) %.10(total)\n" (defaultStringFormatStyle [FormatField False (Just 20) Nothing AccountField
|
||||
, FormatLiteral " "
|
||||
, FormatField False Nothing (Just 10) TotalField
|
||||
, FormatLiteral "\n"
|
||||
])
|
||||
]
|
||||
,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])
|
||||
-- TODO
|
||||
-- , "^%(total)" `gives` (TopAligned [FormatField False Nothing Nothing TotalField])
|
||||
-- , "_%(total)" `gives` (BottomAligned [FormatField False Nothing Nothing TotalField])
|
||||
-- , ",%(total)" `gives` (OneLine [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"
|
||||
]
|
||||
]
|
||||
|
Loading…
Reference in New Issue
Block a user