dev: AmountStyle: rename, reorder fields more mnemonically

Since this type is about to change anyway.
This commit is contained in:
Simon Michael 2023-08-30 08:10:31 +01:00
parent 9f0840456d
commit 85845e51b2
9 changed files with 39 additions and 39 deletions

View File

@ -246,7 +246,7 @@ csvDisplay = oneLine{displayThousandsSep=False}
-- Amount styles
-- | Default amount style
amountstyle = AmountStyle L False (Precision 0) (Just '.') Nothing
amountstyle = AmountStyle L False Nothing (Just '.') (Precision 0)
-------------------------------------------------------------------------------
-- Amount
@ -400,7 +400,7 @@ withInternalPrecision = flip setAmountInternalPrecision
-- | Set (or clear) an amount's display decimal point.
setAmountDecimalPoint :: Maybe Char -> Amount -> Amount
setAmountDecimalPoint mc a@Amount{ astyle=s } = a{ astyle=s{asdecimalpoint=mc} }
setAmountDecimalPoint mc a@Amount{ astyle=s } = a{ astyle=s{asdecimalmark=mc} }
-- | Set (or clear) an amount's display decimal point, flipped.
withDecimalPoint :: Amount -> Maybe Char -> Amount
@ -547,7 +547,7 @@ showAmountDebug Amount{..} =
-- using the display settings from its commodity. Also returns the width of the
-- number.
showamountquantity :: Amount -> WideBuilder
showamountquantity amt@Amount{astyle=AmountStyle{asdecimalpoint=mdec, asdigitgroups=mgrps}} =
showamountquantity amt@Amount{astyle=AmountStyle{asdecimalmark=mdec, asdigitgroups=mgrps}} =
signB <> intB <> fracB
where
Decimal e n = amountRoundedQuantity amt

View File

@ -1005,26 +1005,26 @@ tests_Balancing =
--
testCase "1091a" $ do
commodityStylesFromAmounts [
nullamt{aquantity=1000, astyle=AmountStyle L False (Precision 3) (Just ',') Nothing}
,nullamt{aquantity=1000, astyle=AmountStyle L False (Precision 2) (Just '.') (Just (DigitGroups ',' [3]))}
nullamt{aquantity=1000, astyle=AmountStyle L False Nothing (Just ',') (Precision 3)}
,nullamt{aquantity=1000, astyle=AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 2)}
]
@?=
-- The commodity style should have period as decimal mark
-- and comma as digit group mark.
Right (M.fromList [
("", AmountStyle L False (Precision 3) (Just '.') (Just (DigitGroups ',' [3])))
("", AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 3))
])
-- same journal, entries in reverse order
,testCase "1091b" $ do
commodityStylesFromAmounts [
nullamt{aquantity=1000, astyle=AmountStyle L False (Precision 2) (Just '.') (Just (DigitGroups ',' [3]))}
,nullamt{aquantity=1000, astyle=AmountStyle L False (Precision 3) (Just ',') Nothing}
nullamt{aquantity=1000, astyle=AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 2)}
,nullamt{aquantity=1000, astyle=AmountStyle L False Nothing (Just ',') (Precision 3)}
]
@?=
-- The commodity style should have period as decimal mark
-- and comma as digit group mark.
Right (M.fromList [
("", AmountStyle L False (Precision 3) (Just '.') (Just (DigitGroups ',' [3])))
("", AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 3))
])
]

View File

@ -858,7 +858,7 @@ canonicalStyleFrom = foldl' canonicalStyle amountstyle
-- with the first digit group style seen,
-- with the maximum precision of all.
canonicalStyle :: AmountStyle -> AmountStyle -> AmountStyle
canonicalStyle a b = a{asprecision=prec, asdecimalpoint=decmark, asdigitgroups=mgrps}
canonicalStyle a b = a{asprecision=prec, asdecimalmark=decmark, asdigitgroups=mgrps}
where
-- precision is maximum of all precisions
prec = max (asprecision a) (asprecision b)
@ -874,7 +874,7 @@ canonicalStyle a b = a{asprecision=prec, asdecimalpoint=decmark, asdigitgroups=m
-- urgh.. refactor..
decmark = case mgrps of
Just _ -> Just defdecmark
Nothing -> asdecimalpoint a <|> asdecimalpoint b <|> Just defdecmark
Nothing -> asdecimalmark a <|> asdecimalmark b <|> Just defdecmark
-- -- | Apply this journal's historical price records to unpriced amounts where possible.
-- journalApplyPriceDirectives :: Journal -> Journal

View File

@ -249,14 +249,14 @@ deriving instance Generic (DecimalRaw a)
data AmountPrice = UnitPrice !Amount | TotalPrice !Amount
deriving (Eq,Ord,Generic,Show)
-- | Display style for an amount.
-- (See also Amount.AmountDisplayOpts)
-- | The display style for an amount.
-- (See also Amount.AmountDisplayOpts).
data AmountStyle = AmountStyle {
ascommodityside :: !Side, -- ^ does the symbol appear on the left or the right ?
ascommodityspaced :: !Bool, -- ^ space between symbol and quantity ?
asprecision :: !AmountPrecision, -- ^ number of digits displayed after the decimal point
asdecimalpoint :: !(Maybe Char), -- ^ character used as decimal point: period or comma. Nothing means "unspecified, use default"
asdigitgroups :: !(Maybe DigitGroupStyle) -- ^ style for displaying digit groups, if any
ascommodityside :: !Side, -- ^ show the symbol on the left or the right ?
ascommodityspaced :: !Bool, -- ^ show a space between symbol and quantity ?
asdigitgroups :: !(Maybe DigitGroupStyle), -- ^ show the integer part with these digit group marks, or not
asdecimalmark :: !(Maybe Char), -- ^ show this character (should be . or ,) as decimal mark, or use the default (.)
asprecision :: !AmountPrecision -- ^ show this number of digits after the decimal point
} deriving (Eq,Ord,Read,Generic)
instance Show AmountStyle where
@ -264,9 +264,9 @@ instance Show AmountStyle where
[ "AmountStylePP"
, show ascommodityside
, show ascommodityspaced
, show asprecision
, show asdecimalpoint
, show asdigitgroups
, show asdecimalmark
, show asprecision
]
-- | The "display precision" for a hledger amount, by which we mean

View File

@ -386,7 +386,7 @@ getYear = fmap jparsedefaultyear get
getDecimalMarkStyle :: JournalParser m (Maybe AmountStyle)
getDecimalMarkStyle = do
Journal{jparsedecimalmark} <- get
let mdecmarkStyle = (\c -> Just $ amountstyle{asdecimalpoint=Just c}) =<< jparsedecimalmark
let mdecmarkStyle = (\c -> Just $ amountstyle{asdecimalmark=Just c}) =<< jparsedecimalmark
return mdecmarkStyle
setDefaultCommodityAndStyle :: (CommoditySymbol,AmountStyle) -> JournalParser m ()
@ -802,7 +802,7 @@ simpleamountp mult =
offAfterNum <- getOffset
let numRegion = (offBeforeNum, offAfterNum)
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion suggestedStyle ambiguousRawNum mExponent
let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps}
let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalmark=mdec, asdigitgroups=mgrps}
return nullamt{acommodity=c, aquantity=sign (sign2 q), astyle=s, aprice=Nothing}
-- An amount with commodity symbol on the right or no commodity symbol.
@ -824,7 +824,7 @@ simpleamountp mult =
-- XXX amounts of this commodity in periodic transaction rules and auto posting rules ? #1461
let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion msuggestedStyle ambiguousRawNum mExponent
let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps}
let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalmark=mdec, asdigitgroups=mgrps}
return nullamt{acommodity=c, aquantity=sign q, astyle=s, aprice=Nothing}
-- no symbol amount
Nothing -> do
@ -841,7 +841,7 @@ simpleamountp mult =
defcs <- getDefaultCommodityAndStyle
let (c,s) = case (mult, defcs) of
(False, Just (defc,defs)) -> (defc, defs{asprecision=max (asprecision defs) prec})
_ -> ("", amountstyle{asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps})
_ -> ("", amountstyle{asprecision=prec, asdecimalmark=mdec, asdigitgroups=mgrps})
return nullamt{acommodity=c, aquantity=sign q, astyle=s, aprice=Nothing}
-- For reducing code duplication. Doesn't parse anything. Has the type
@ -1066,7 +1066,7 @@ disambiguateNumber msuggestedStyle (AmbiguousNumber grp1 sep grp2) =
where
isValidDecimalBy :: Char -> AmountStyle -> Bool
isValidDecimalBy c = \case
AmountStyle{asdecimalpoint = Just d} -> d == c
AmountStyle{asdecimalmark = Just d} -> d == c
AmountStyle{asdigitgroups = Just (DigitGroups g _)} -> g /= c
AmountStyle{asprecision = Precision 0} -> False
_ -> True
@ -1568,28 +1568,28 @@ tests_Common = testGroup "Common" [
,testCase "ends with decimal mark" $ assertParseEq amountp "$1." (usd 1 `withPrecision` Precision 0)
,testCase "unit price" $ assertParseEq amountp "$10 @ €0.5"
-- not precise enough:
-- (usd 10 `withPrecision` 0 `at` (eur 0.5 `withPrecision` 1)) -- `withStyle` asdecimalpoint=Just '.'
-- (usd 10 `withPrecision` 0 `at` (eur 0.5 `withPrecision` 1)) -- `withStyle` asdecimalmark=Just '.'
nullamt{
acommodity="$"
,aquantity=10 -- need to test internal precision with roundTo ? I think not
,astyle=amountstyle{asprecision=Precision 0, asdecimalpoint=Nothing}
,astyle=amountstyle{asprecision=Precision 0, asdecimalmark=Nothing}
,aprice=Just $ UnitPrice $
nullamt{
acommodity=""
,aquantity=0.5
,astyle=amountstyle{asprecision=Precision 1, asdecimalpoint=Just '.'}
,astyle=amountstyle{asprecision=Precision 1, asdecimalmark=Just '.'}
}
}
,testCase "total price" $ assertParseEq amountp "$10 @@ €5"
nullamt{
acommodity="$"
,aquantity=10
,astyle=amountstyle{asprecision=Precision 0, asdecimalpoint=Nothing}
,astyle=amountstyle{asprecision=Precision 0, asdecimalmark=Nothing}
,aprice=Just $ TotalPrice $
nullamt{
acommodity=""
,aquantity=5
,astyle=amountstyle{asprecision=Precision 0, asdecimalpoint=Nothing}
,astyle=amountstyle{asprecision=Precision 0, asdecimalmark=Nothing}
}
}
,testCase "unit price, parenthesised" $ assertParse amountp "$10 (@) €0.5"

View File

@ -490,7 +490,7 @@ commoditydirectiveonelinep = do
lift skipNonNewlineSpaces
_ <- lift followingcommentp
let comm = Commodity{csymbol=acommodity, cformat=Just $ dbg6 "style from commodity directive" astyle}
if isNothing $ asdecimalpoint astyle
if isNothing $ asdecimalmark astyle
then customFailure $ parseErrorAt off pleaseincludedecimalpoint
else modify' (\j -> j{jcommodities=M.insert acommodity comm $ jcommodities j})
@ -533,7 +533,7 @@ formatdirectivep expectedsym = do
_ <- lift followingcommentp
if acommodity==expectedsym
then
if isNothing $ asdecimalpoint astyle
if isNothing $ asdecimalmark astyle
then customFailure $ parseErrorAt off pleaseincludedecimalpoint
else return $ dbg6 "style from format subdirective" astyle
else customFailure $ parseErrorAt off $
@ -648,7 +648,7 @@ defaultcommoditydirectivep = do
off <- getOffset
Amount{acommodity,astyle} <- amountp
lift restofline
if isNothing $ asdecimalpoint astyle
if isNothing $ asdecimalmark astyle
then customFailure $ parseErrorAt off pleaseincludedecimalpoint
else setDefaultCommodityAndStyle (acommodity, astyle)

View File

@ -617,7 +617,7 @@ balanceReportTableAsText ReportOpts{..} =
tests_MultiBalanceReport = testGroup "MultiBalanceReport" [
let
amt0 = Amount {acommodity="$", aquantity=0, aprice=Nothing, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asprecision = Precision 2, asdecimalpoint = Just '.', asdigitgroups = Nothing}}
amt0 = Amount {acommodity="$", aquantity=0, aprice=Nothing, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asdigitgroups = Nothing, asdecimalmark = Just '.', asprecision = Precision 2}}
(rspec,journal) `gives` r = do
let rspec' = rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
(eitems, etotal) = r

View File

@ -162,7 +162,7 @@ entriesReportAsSql txns = TB.toLazyText $ mconcat
toSql s = TB.fromText "'" <> TB.fromText (T.replace "'" "''" s) <> TB.fromText "'"
csv = concatMap (transactionToCSV . transactionMapPostingAmounts (mapMixedAmount setDecimalPoint)) txns
where
setDecimalPoint a = a{astyle=(astyle a){asdecimalpoint=Just '.'}}
setDecimalPoint a = a{astyle=(astyle a){asdecimalmark=Just '.'}}
entriesReportAsCsv :: EntriesReport -> CSV
entriesReportAsCsv txns =

View File

@ -23,7 +23,7 @@ $ hledger -f- reg --output-format=json
"astyle": {
"ascommodityside": "R",
"ascommodityspaced": true,
"asdecimalpoint": ".",
"asdecimalmark": ".",
"asdigitgroups": null,
"asprecision": 1
}
@ -51,7 +51,7 @@ $ hledger -f- reg --output-format=json
"astyle": {
"ascommodityside": "R",
"ascommodityspaced": true,
"asdecimalpoint": ".",
"asdecimalmark": ".",
"asdigitgroups": null,
"asprecision": 1
}
@ -80,7 +80,7 @@ $ hledger -f- bal --output-format=json
"astyle": {
"ascommodityside": "R",
"ascommodityspaced": true,
"asdecimalpoint": ".",
"asdecimalmark": ".",
"asdigitgroups": null,
"asprecision": 1
}
@ -100,7 +100,7 @@ $ hledger -f- bal --output-format=json
"astyle": {
"ascommodityside": "R",
"ascommodityspaced": true,
"asdecimalpoint": ".",
"asdecimalmark": ".",
"asdigitgroups": null,
"asprecision": 1
}