dev: AmountStyle: make setting the precision optional
This simplifies the code for styling amounts with or without precision. But it complicates the semantics (Nothing is useful only when setting style). Not sure if it's the best way.
This commit is contained in:
parent
85845e51b2
commit
97be1646f1
@ -246,7 +246,7 @@ csvDisplay = oneLine{displayThousandsSep=False}
|
|||||||
-- Amount styles
|
-- Amount styles
|
||||||
|
|
||||||
-- | Default amount style
|
-- | Default amount style
|
||||||
amountstyle = AmountStyle L False Nothing (Just '.') (Precision 0)
|
amountstyle = AmountStyle L False Nothing (Just '.') (Just $ Precision 0)
|
||||||
|
|
||||||
-------------------------------------------------------------------------------
|
-------------------------------------------------------------------------------
|
||||||
-- Amount
|
-- Amount
|
||||||
@ -275,11 +275,11 @@ missingamt = nullamt{acommodity="AUTO"}
|
|||||||
-- usd/eur/gbp round their argument to a whole number of pennies/cents.
|
-- usd/eur/gbp round their argument to a whole number of pennies/cents.
|
||||||
-- XXX these are a bit clashy
|
-- XXX these are a bit clashy
|
||||||
num n = nullamt{acommodity="", aquantity=n}
|
num n = nullamt{acommodity="", aquantity=n}
|
||||||
hrs n = nullamt{acommodity="h", aquantity=n, astyle=amountstyle{asprecision=Precision 2, ascommodityside=R}}
|
hrs n = nullamt{acommodity="h", aquantity=n, astyle=amountstyle{asprecision=Just $ Precision 2, ascommodityside=R}}
|
||||||
usd n = nullamt{acommodity="$", aquantity=roundTo 2 n, astyle=amountstyle{asprecision=Precision 2}}
|
usd n = nullamt{acommodity="$", aquantity=roundTo 2 n, astyle=amountstyle{asprecision=Just $ Precision 2}}
|
||||||
eur n = nullamt{acommodity="€", aquantity=roundTo 2 n, astyle=amountstyle{asprecision=Precision 2}}
|
eur n = nullamt{acommodity="€", aquantity=roundTo 2 n, astyle=amountstyle{asprecision=Just $ Precision 2}}
|
||||||
gbp n = nullamt{acommodity="£", aquantity=roundTo 2 n, astyle=amountstyle{asprecision=Precision 2}}
|
gbp n = nullamt{acommodity="£", aquantity=roundTo 2 n, astyle=amountstyle{asprecision=Just $ Precision 2}}
|
||||||
per n = nullamt{acommodity="%", aquantity=n, astyle=amountstyle{asprecision=Precision 1, ascommodityside=R, ascommodityspaced=True}}
|
per n = nullamt{acommodity="%", aquantity=n, astyle=amountstyle{asprecision=Just $ Precision 1, ascommodityside=R, ascommodityspaced=True}}
|
||||||
amt `at` priceamt = amt{aprice=Just $ UnitPrice priceamt}
|
amt `at` priceamt = amt{aprice=Just $ UnitPrice priceamt}
|
||||||
amt @@ priceamt = amt{aprice=Just $ TotalPrice priceamt}
|
amt @@ priceamt = amt{aprice=Just $ TotalPrice priceamt}
|
||||||
|
|
||||||
@ -337,12 +337,13 @@ multiplyAmount n = transformAmount (*n)
|
|||||||
isNegativeAmount :: Amount -> Bool
|
isNegativeAmount :: Amount -> Bool
|
||||||
isNegativeAmount Amount{aquantity=q} = q < 0
|
isNegativeAmount Amount{aquantity=q} = q < 0
|
||||||
|
|
||||||
-- | Round an Amount's Quantity to its specified display precision. If that is
|
-- | Round an Amount's Quantity (internally) to match its display precision.
|
||||||
-- NaturalPrecision, this does nothing.
|
-- If that is unset or NaturalPrecision, this does nothing.
|
||||||
amountRoundedQuantity :: Amount -> Quantity
|
amountRoundedQuantity :: Amount -> Quantity
|
||||||
amountRoundedQuantity Amount{aquantity=q, astyle=AmountStyle{asprecision=p}} = case p of
|
amountRoundedQuantity Amount{aquantity=q, astyle=AmountStyle{asprecision=mp}} = case mp of
|
||||||
NaturalPrecision -> q
|
Nothing -> q
|
||||||
Precision p' -> roundTo p' q
|
Just NaturalPrecision -> q
|
||||||
|
Just (Precision p) -> roundTo p q
|
||||||
|
|
||||||
-- | Apply a test to both an Amount and its total price, if it has one.
|
-- | Apply a test to both an Amount and its total price, if it has one.
|
||||||
testAmountAndTotalPrice :: (Amount -> Bool) -> Amount -> Bool
|
testAmountAndTotalPrice :: (Amount -> Bool) -> Amount -> Bool
|
||||||
@ -350,14 +351,17 @@ testAmountAndTotalPrice f amt = case aprice amt of
|
|||||||
Just (TotalPrice price) -> f amt && f price
|
Just (TotalPrice price) -> f amt && f price
|
||||||
_ -> f amt
|
_ -> f amt
|
||||||
|
|
||||||
-- | Do this Amount and (and its total price, if it has one) appear to be zero when rendered with its
|
-- | Do this Amount and (and its total price, if it has one) appear to be zero
|
||||||
-- display precision ?
|
-- when rendered with its display precision ?
|
||||||
|
-- The display precision should usually have a specific value here;
|
||||||
|
-- if unset, it will be treated like NaturalPrecision.
|
||||||
amountLooksZero :: Amount -> Bool
|
amountLooksZero :: Amount -> Bool
|
||||||
amountLooksZero = testAmountAndTotalPrice looksZero
|
amountLooksZero = testAmountAndTotalPrice looksZero
|
||||||
where
|
where
|
||||||
looksZero Amount{aquantity=Decimal e q, astyle=AmountStyle{asprecision=p}} = case p of
|
looksZero Amount{aquantity=Decimal e q, astyle=AmountStyle{asprecision=p}} = case p of
|
||||||
Precision d -> if e > d then abs q <= 5*10^(e-d-1) else q == 0
|
Just (Precision d) -> if e > d then abs q <= 5*10^(e-d-1) else q == 0
|
||||||
NaturalPrecision -> q == 0
|
Just NaturalPrecision -> q == 0
|
||||||
|
Nothing -> q == 0
|
||||||
|
|
||||||
-- | Is this Amount (and its total price, if it has one) exactly zero, ignoring its display precision ?
|
-- | Is this Amount (and its total price, if it has one) exactly zero, ignoring its display precision ?
|
||||||
amountIsZero :: Amount -> Bool
|
amountIsZero :: Amount -> Bool
|
||||||
@ -369,16 +373,16 @@ withPrecision = flip amountSetPrecision
|
|||||||
|
|
||||||
-- | Set an amount's display precision.
|
-- | Set an amount's display precision.
|
||||||
amountSetPrecision :: AmountPrecision -> Amount -> Amount
|
amountSetPrecision :: AmountPrecision -> Amount -> Amount
|
||||||
amountSetPrecision p a@Amount{astyle=s} = a{astyle=s{asprecision=p}}
|
amountSetPrecision p a@Amount{astyle=s} = a{astyle=s{asprecision=Just p}}
|
||||||
|
|
||||||
-- | Increase an amount's display precision, if needed, to enough decimal places
|
-- | Increase an amount's display precision, if needed, to enough decimal places
|
||||||
-- to show it exactly (showing all significant decimal digits, excluding trailing
|
-- to show it exactly (showing all significant decimal digits, without trailing zeros).
|
||||||
-- zeros).
|
-- If the amount's display precision is unset, it is will be treated as precision 0.
|
||||||
amountSetFullPrecision :: Amount -> Amount
|
amountSetFullPrecision :: Amount -> Amount
|
||||||
amountSetFullPrecision a = amountSetPrecision p a
|
amountSetFullPrecision a = amountSetPrecision p a
|
||||||
where
|
where
|
||||||
p = max displayprecision naturalprecision
|
p = max displayprecision naturalprecision
|
||||||
displayprecision = asprecision $ astyle a
|
displayprecision = fromMaybe (Precision 0) $ asprecision $ astyle a
|
||||||
naturalprecision = Precision . decimalPlaces . normalizeDecimal $ aquantity a
|
naturalprecision = Precision . decimalPlaces . normalizeDecimal $ aquantity a
|
||||||
|
|
||||||
-- | Set an amount's internal precision, ie rounds the Decimal representing
|
-- | Set an amount's internal precision, ie rounds the Decimal representing
|
||||||
@ -389,7 +393,7 @@ amountSetFullPrecision a = amountSetPrecision p a
|
|||||||
-- Intended mainly for internal use, eg when comparing amounts in tests.
|
-- Intended mainly for internal use, eg when comparing amounts in tests.
|
||||||
setAmountInternalPrecision :: Word8 -> Amount -> Amount
|
setAmountInternalPrecision :: Word8 -> Amount -> Amount
|
||||||
setAmountInternalPrecision p a@Amount{ aquantity=q, astyle=s } = a{
|
setAmountInternalPrecision p a@Amount{ aquantity=q, astyle=s } = a{
|
||||||
astyle=s{asprecision=Precision p}
|
astyle=s{asprecision=Just $ Precision p}
|
||||||
,aquantity=roundTo p q
|
,aquantity=roundTo p q
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -449,27 +453,31 @@ styleAmountExceptPrecision styles a@Amount{astyle=AmountStyle{asprecision=origp}
|
|||||||
Just s -> a{astyle=s{asprecision=origp}}
|
Just s -> a{astyle=s{asprecision=origp}}
|
||||||
Nothing -> a
|
Nothing -> a
|
||||||
|
|
||||||
-- v2.9
|
-- v3
|
||||||
|
|
||||||
-- | Given some commodity display styles, find and apply the appropriate
|
-- | Given some commodity display styles, find and apply the appropriate
|
||||||
-- display style to this amount, and do the same for its cost amount if any
|
-- display style to this amount, and do the same for its cost amount if any
|
||||||
-- (and then stop; we assume costs don't have costs).
|
-- (and then stop; we assume costs don't have costs).
|
||||||
-- The main amount's display precision is set according to its style;
|
-- The main amount's display precision may or may not be changed, as specified by the style.
|
||||||
-- the cost amount's display precision is left unchanged, regardless of its style.
|
-- the cost amount's display precision is left unchanged, ignoring what the style says.
|
||||||
-- If no style is found for an amount, it is left unchanged.
|
-- If no style is found for an amount, it is left unchanged.
|
||||||
amountSetStyles :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount
|
amountSetStyles :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount
|
||||||
amountSetStyles styles = amountSetMainStyle styles <&> amountSetCostStyle styles
|
amountSetStyles styles = amountSetMainStyle styles <&> amountSetCostStyle styles
|
||||||
|
|
||||||
-- | Find and apply the appropriate display style, if any, to this amount.
|
-- | Find and apply the appropriate display style, if any, to this amount.
|
||||||
-- The display precision is also set.
|
-- The display precision may or may not be changed, as specified by the style.
|
||||||
amountSetMainStyle :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount
|
amountSetMainStyle :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount
|
||||||
amountSetMainStyle styles a@Amount{acommodity=comm} =
|
amountSetMainStyle styles a@Amount{acommodity=comm, astyle=AmountStyle{asprecision=morigp}} =
|
||||||
case M.lookup comm styles of
|
case M.lookup comm styles of
|
||||||
Nothing -> a
|
Nothing -> a
|
||||||
Just s -> a{astyle=s}
|
Just s@AmountStyle{asprecision=mp} -> a{astyle=s'}
|
||||||
|
where
|
||||||
|
s' = case mp of
|
||||||
|
Nothing -> s{asprecision=morigp}
|
||||||
|
_ -> s
|
||||||
|
|
||||||
-- | Find and apply the appropriate display style, if any, to this amount's cost, if any.
|
-- | Find and apply the appropriate display style, if any, to this amount's cost, if any.
|
||||||
-- The display precision is left unchanged.
|
-- The display precision is left unchanged, ignoring what the style says.
|
||||||
amountSetCostStyle :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount
|
amountSetCostStyle :: M.Map CommoditySymbol AmountStyle -> Amount -> Amount
|
||||||
amountSetCostStyle styles a@Amount{aprice=mcost} =
|
amountSetCostStyle styles a@Amount{aprice=mcost} =
|
||||||
case mcost of
|
case mcost of
|
||||||
@ -856,7 +864,7 @@ styleMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmo
|
|||||||
styleMixedAmount = mixedAmountSetStyles
|
styleMixedAmount = mixedAmountSetStyles
|
||||||
{-# DEPRECATED styleMixedAmount "please use mixedAmountSetStyles instead" #-}
|
{-# DEPRECATED styleMixedAmount "please use mixedAmountSetStyles instead" #-}
|
||||||
|
|
||||||
-- v2.9
|
-- v3
|
||||||
|
|
||||||
mixedAmountSetStyles :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
|
mixedAmountSetStyles :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
|
||||||
mixedAmountSetStyles styles = mapMixedAmountUnsafe (amountSetStyles styles)
|
mixedAmountSetStyles styles = mapMixedAmountUnsafe (amountSetStyles styles)
|
||||||
@ -1085,8 +1093,8 @@ tests_Amount = testGroup "Amount" [
|
|||||||
(usd (-1.23) + usd (-1.23)) @?= usd (-2.46)
|
(usd (-1.23) + usd (-1.23)) @?= usd (-2.46)
|
||||||
sum [usd 1.23,usd (-1.23),usd (-1.23),-(usd (-1.23))] @?= usd 0
|
sum [usd 1.23,usd (-1.23),usd (-1.23),-(usd (-1.23))] @?= usd 0
|
||||||
-- highest precision is preserved
|
-- highest precision is preserved
|
||||||
asprecision (astyle $ sum [usd 1 `withPrecision` Precision 1, usd 1 `withPrecision` Precision 3]) @?= Precision 3
|
asprecision (astyle $ sum [usd 1 `withPrecision` Precision 1, usd 1 `withPrecision` Precision 3]) @?= Just (Precision 3)
|
||||||
asprecision (astyle $ sum [usd 1 `withPrecision` Precision 3, usd 1 `withPrecision` Precision 1]) @?= Precision 3
|
asprecision (astyle $ sum [usd 1 `withPrecision` Precision 3, usd 1 `withPrecision` Precision 1]) @?= Just (Precision 3)
|
||||||
-- adding different commodities assumes conversion rate 1
|
-- adding different commodities assumes conversion rate 1
|
||||||
assertBool "" $ amountLooksZero (usd 1.23 - eur 1.23)
|
assertBool "" $ amountLooksZero (usd 1.23 - eur 1.23)
|
||||||
|
|
||||||
|
|||||||
@ -337,8 +337,8 @@ costInferrerFor t pt = maybe id infercost inferFromAndTo
|
|||||||
|
|
||||||
unitprice = aquantity fromamount `divideAmount` toamount
|
unitprice = aquantity fromamount `divideAmount` toamount
|
||||||
unitprecision = case (asprecision $ astyle fromamount, asprecision $ astyle toamount) of
|
unitprecision = case (asprecision $ astyle fromamount, asprecision $ astyle toamount) of
|
||||||
(Precision a, Precision b) -> Precision . max 2 $ saturatedAdd a b
|
(Just (Precision a), Just (Precision b)) -> Precision . max 2 $ saturatedAdd a b
|
||||||
_ -> NaturalPrecision
|
_ -> NaturalPrecision
|
||||||
saturatedAdd a b = if maxBound - a < b then maxBound else a + b
|
saturatedAdd a b = if maxBound - a < b then maxBound else a + b
|
||||||
|
|
||||||
|
|
||||||
@ -1005,26 +1005,26 @@ tests_Balancing =
|
|||||||
--
|
--
|
||||||
testCase "1091a" $ do
|
testCase "1091a" $ do
|
||||||
commodityStylesFromAmounts [
|
commodityStylesFromAmounts [
|
||||||
nullamt{aquantity=1000, astyle=AmountStyle L False Nothing (Just ',') (Precision 3)}
|
nullamt{aquantity=1000, astyle=AmountStyle L False Nothing (Just ',') (Just $ Precision 3)}
|
||||||
,nullamt{aquantity=1000, astyle=AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 2)}
|
,nullamt{aquantity=1000, astyle=AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Just $ Precision 2)}
|
||||||
]
|
]
|
||||||
@?=
|
@?=
|
||||||
-- The commodity style should have period as decimal mark
|
-- The commodity style should have period as decimal mark
|
||||||
-- and comma as digit group mark.
|
-- and comma as digit group mark.
|
||||||
Right (M.fromList [
|
Right (M.fromList [
|
||||||
("", AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 3))
|
("", AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Just $ Precision 3))
|
||||||
])
|
])
|
||||||
-- same journal, entries in reverse order
|
-- same journal, entries in reverse order
|
||||||
,testCase "1091b" $ do
|
,testCase "1091b" $ do
|
||||||
commodityStylesFromAmounts [
|
commodityStylesFromAmounts [
|
||||||
nullamt{aquantity=1000, astyle=AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 2)}
|
nullamt{aquantity=1000, astyle=AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Just $ Precision 2)}
|
||||||
,nullamt{aquantity=1000, astyle=AmountStyle L False Nothing (Just ',') (Precision 3)}
|
,nullamt{aquantity=1000, astyle=AmountStyle L False Nothing (Just ',') (Just $ Precision 3)}
|
||||||
]
|
]
|
||||||
@?=
|
@?=
|
||||||
-- The commodity style should have period as decimal mark
|
-- The commodity style should have period as decimal mark
|
||||||
-- and comma as digit group mark.
|
-- and comma as digit group mark.
|
||||||
Right (M.fromList [
|
Right (M.fromList [
|
||||||
("", AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Precision 3))
|
("", AmountStyle L False (Just (DigitGroups ',' [3])) (Just '.') (Just $ Precision 3))
|
||||||
])
|
])
|
||||||
|
|
||||||
]
|
]
|
||||||
|
|||||||
@ -355,8 +355,8 @@ transactionInferCostsFromEquity dryrun acctTypes t = first (annotateErrorWithTra
|
|||||||
| dbgamtmatch 2 a2 a (amountsMatch (-a2) a) && dbgcostmatch 1 a1 a (amountsMatch a1 (amountCost a)) -> Just costfulp
|
| dbgamtmatch 2 a2 a (amountsMatch (-a2) a) && dbgcostmatch 1 a1 a (amountsMatch a1 (amountCost a)) -> Just costfulp
|
||||||
| otherwise -> Nothing
|
| otherwise -> Nothing
|
||||||
where
|
where
|
||||||
dbgamtmatch n a b = dbg7 ("conversion posting " <>show n<>" "<>showAmount a<>" balances amount "<>showAmountWithoutPrice b <>" of costful posting "<>showAmount b<>" at precision "<>amountShowPrecision a<>" ?")
|
dbgamtmatch n a b = dbg7 ("conversion posting " <>show n<>" "<>showAmount a<>" balances amount "<>showAmountWithoutPrice b <>" of costful posting "<>showAmount b<>" at precision "<>dbgShowAmountPrecision a<>" ?")
|
||||||
dbgcostmatch n a b = dbg7 ("and\nconversion posting "<>show n<>" "<>showAmount a<>" matches cost " <>showAmount (amountCost b)<>" of costful posting "<>showAmount b<>" at precision "<>amountShowPrecision a<>" ?")
|
dbgcostmatch n a b = dbg7 ("and\nconversion posting "<>show n<>" "<>showAmount a<>" matches cost " <>showAmount (amountCost b)<>" of costful posting "<>showAmount b<>" at precision "<>dbgShowAmountPrecision a<>" ?")
|
||||||
|
|
||||||
-- Add a cost to a posting if it matches (negative) one of the
|
-- Add a cost to a posting if it matches (negative) one of the
|
||||||
-- supplied conversion amounts, adding the other amount as the cost.
|
-- supplied conversion amounts, adding the other amount as the cost.
|
||||||
@ -376,7 +376,11 @@ transactionInferCostsFromEquity dryrun acctTypes t = first (annotateErrorWithTra
|
|||||||
Nothing -> Left $ annotateWithPostings [p] "Conversion postings must have a single-commodity amount:"
|
Nothing -> Left $ annotateWithPostings [p] "Conversion postings must have a single-commodity amount:"
|
||||||
|
|
||||||
-- Do these amounts look the same when compared at the first's display precision ?
|
-- Do these amounts look the same when compared at the first's display precision ?
|
||||||
amountsMatch a b = amountLooksZero $ amountSetPrecision (asprecision $ astyle a) $ a - b
|
-- (Or if that's unset, compare as-is)
|
||||||
|
amountsMatch a b =
|
||||||
|
case asprecision $ astyle a of
|
||||||
|
Just p -> amountLooksZero $ amountSetPrecision p $ a - b
|
||||||
|
Nothing -> amountLooksZero $ a - b
|
||||||
|
|
||||||
-- Delete a posting from the indexed list of postings based on either its
|
-- Delete a posting from the indexed list of postings based on either its
|
||||||
-- index or its posting amount.
|
-- index or its posting amount.
|
||||||
@ -392,10 +396,11 @@ transactionInferCostsFromEquity dryrun acctTypes t = first (annotateErrorWithTra
|
|||||||
deleteUniqueMatch _ [] = Nothing
|
deleteUniqueMatch _ [] = Nothing
|
||||||
annotateWithPostings xs str = T.unlines $ str : postingsAsLines False xs
|
annotateWithPostings xs str = T.unlines $ str : postingsAsLines False xs
|
||||||
|
|
||||||
amountShowPrecision a =
|
dbgShowAmountPrecision a =
|
||||||
case asprecision $ astyle a of
|
case asprecision $ astyle a of
|
||||||
Precision n -> show n
|
Just (Precision n) -> show n
|
||||||
NaturalPrecision -> show $ decimalPlaces $ normalizeDecimal $ aquantity a
|
Just NaturalPrecision -> show $ decimalPlaces $ normalizeDecimal $ aquantity a
|
||||||
|
Nothing -> "unset"
|
||||||
|
|
||||||
-- Using the provided account types map, sort the given indexed postings
|
-- Using the provided account types map, sort the given indexed postings
|
||||||
-- into three lists of posting numbers (stored in two pairs), like so:
|
-- into three lists of posting numbers (stored in two pairs), like so:
|
||||||
|
|||||||
@ -256,7 +256,9 @@ data AmountStyle = AmountStyle {
|
|||||||
ascommodityspaced :: !Bool, -- ^ show a space between symbol and quantity ?
|
ascommodityspaced :: !Bool, -- ^ show a space between symbol and quantity ?
|
||||||
asdigitgroups :: !(Maybe DigitGroupStyle), -- ^ show the integer part with these digit group marks, or not
|
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 (.)
|
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
|
asprecision :: !(Maybe AmountPrecision) -- ^ show this number of digits after the decimal point, or show as-is (leave precision unchanged)
|
||||||
|
-- XXX Making asprecision a maybe simplifies code for styling with or without precision,
|
||||||
|
-- but complicates the semantics (Nothing is useful only when setting style).
|
||||||
} deriving (Eq,Ord,Read,Generic)
|
} deriving (Eq,Ord,Read,Generic)
|
||||||
|
|
||||||
instance Show AmountStyle where
|
instance Show AmountStyle where
|
||||||
|
|||||||
@ -110,8 +110,8 @@ amountPriceDirectiveFromCost d amt@Amount{acommodity=fromcomm, aquantity=fromq}
|
|||||||
where
|
where
|
||||||
style' = (astyle a) { asprecision = precision' }
|
style' = (astyle a) { asprecision = precision' }
|
||||||
precision' = case asprecision (astyle a) of
|
precision' = case asprecision (astyle a) of
|
||||||
NaturalPrecision -> NaturalPrecision
|
Just (Precision p) -> Just $ Precision $ (numDigitsInt $ truncate n) + p
|
||||||
Precision p -> Precision $ (numDigitsInt $ truncate n) + p
|
mp -> mp
|
||||||
|
|
||||||
------------------------------------------------------------------------------
|
------------------------------------------------------------------------------
|
||||||
-- Converting things to value
|
-- Converting things to value
|
||||||
|
|||||||
@ -802,7 +802,7 @@ simpleamountp mult =
|
|||||||
offAfterNum <- getOffset
|
offAfterNum <- getOffset
|
||||||
let numRegion = (offBeforeNum, offAfterNum)
|
let numRegion = (offBeforeNum, offAfterNum)
|
||||||
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion suggestedStyle ambiguousRawNum mExponent
|
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion suggestedStyle ambiguousRawNum mExponent
|
||||||
let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalmark=mdec, asdigitgroups=mgrps}
|
let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=Just prec, asdecimalmark=mdec, asdigitgroups=mgrps}
|
||||||
return nullamt{acommodity=c, aquantity=sign (sign2 q), astyle=s, aprice=Nothing}
|
return nullamt{acommodity=c, aquantity=sign (sign2 q), astyle=s, aprice=Nothing}
|
||||||
|
|
||||||
-- An amount with commodity symbol on the right or no commodity symbol.
|
-- 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
|
-- XXX amounts of this commodity in periodic transaction rules and auto posting rules ? #1461
|
||||||
let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle
|
let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle
|
||||||
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion msuggestedStyle ambiguousRawNum mExponent
|
(q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion msuggestedStyle ambiguousRawNum mExponent
|
||||||
let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalmark=mdec, asdigitgroups=mgrps}
|
let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=Just prec, asdecimalmark=mdec, asdigitgroups=mgrps}
|
||||||
return nullamt{acommodity=c, aquantity=sign q, astyle=s, aprice=Nothing}
|
return nullamt{acommodity=c, aquantity=sign q, astyle=s, aprice=Nothing}
|
||||||
-- no symbol amount
|
-- no symbol amount
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
@ -840,8 +840,8 @@ simpleamountp mult =
|
|||||||
-- (unless it's a multiplier in an automated posting)
|
-- (unless it's a multiplier in an automated posting)
|
||||||
defcs <- getDefaultCommodityAndStyle
|
defcs <- getDefaultCommodityAndStyle
|
||||||
let (c,s) = case (mult, defcs) of
|
let (c,s) = case (mult, defcs) of
|
||||||
(False, Just (defc,defs)) -> (defc, defs{asprecision=max (asprecision defs) prec})
|
(False, Just (defc,defs)) -> (defc, defs{asprecision=max (asprecision defs) (Just prec)})
|
||||||
_ -> ("", amountstyle{asprecision=prec, asdecimalmark=mdec, asdigitgroups=mgrps})
|
_ -> ("", amountstyle{asprecision=Just prec, asdecimalmark=mdec, asdigitgroups=mgrps})
|
||||||
return nullamt{acommodity=c, aquantity=sign q, astyle=s, aprice=Nothing}
|
return nullamt{acommodity=c, aquantity=sign q, astyle=s, aprice=Nothing}
|
||||||
|
|
||||||
-- For reducing code duplication. Doesn't parse anything. Has the type
|
-- For reducing code duplication. Doesn't parse anything. Has the type
|
||||||
@ -1068,7 +1068,7 @@ disambiguateNumber msuggestedStyle (AmbiguousNumber grp1 sep grp2) =
|
|||||||
isValidDecimalBy c = \case
|
isValidDecimalBy c = \case
|
||||||
AmountStyle{asdecimalmark = Just d} -> d == c
|
AmountStyle{asdecimalmark = Just d} -> d == c
|
||||||
AmountStyle{asdigitgroups = Just (DigitGroups g _)} -> g /= c
|
AmountStyle{asdigitgroups = Just (DigitGroups g _)} -> g /= c
|
||||||
AmountStyle{asprecision = Precision 0} -> False
|
AmountStyle{asprecision = Just (Precision 0)} -> False
|
||||||
_ -> True
|
_ -> True
|
||||||
|
|
||||||
-- | Parse and interpret the structure of a number without external hints.
|
-- | Parse and interpret the structure of a number without external hints.
|
||||||
@ -1572,24 +1572,24 @@ tests_Common = testGroup "Common" [
|
|||||||
nullamt{
|
nullamt{
|
||||||
acommodity="$"
|
acommodity="$"
|
||||||
,aquantity=10 -- need to test internal precision with roundTo ? I think not
|
,aquantity=10 -- need to test internal precision with roundTo ? I think not
|
||||||
,astyle=amountstyle{asprecision=Precision 0, asdecimalmark=Nothing}
|
,astyle=amountstyle{asprecision=Just $ Precision 0, asdecimalmark=Nothing}
|
||||||
,aprice=Just $ UnitPrice $
|
,aprice=Just $ UnitPrice $
|
||||||
nullamt{
|
nullamt{
|
||||||
acommodity="€"
|
acommodity="€"
|
||||||
,aquantity=0.5
|
,aquantity=0.5
|
||||||
,astyle=amountstyle{asprecision=Precision 1, asdecimalmark=Just '.'}
|
,astyle=amountstyle{asprecision=Just $ Precision 1, asdecimalmark=Just '.'}
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
,testCase "total price" $ assertParseEq amountp "$10 @@ €5"
|
,testCase "total price" $ assertParseEq amountp "$10 @@ €5"
|
||||||
nullamt{
|
nullamt{
|
||||||
acommodity="$"
|
acommodity="$"
|
||||||
,aquantity=10
|
,aquantity=10
|
||||||
,astyle=amountstyle{asprecision=Precision 0, asdecimalmark=Nothing}
|
,astyle=amountstyle{asprecision=Just $ Precision 0, asdecimalmark=Nothing}
|
||||||
,aprice=Just $ TotalPrice $
|
,aprice=Just $ TotalPrice $
|
||||||
nullamt{
|
nullamt{
|
||||||
acommodity="€"
|
acommodity="€"
|
||||||
,aquantity=5
|
,aquantity=5
|
||||||
,astyle=amountstyle{asprecision=Precision 0, asdecimalmark=Nothing}
|
,astyle=amountstyle{asprecision=Just $ Precision 0, asdecimalmark=Nothing}
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
,testCase "unit price, parenthesised" $ assertParse amountp "$10 (@) €0.5"
|
,testCase "unit price, parenthesised" $ assertParse amountp "$10 (@) €0.5"
|
||||||
|
|||||||
@ -192,8 +192,8 @@ timedotentryp = do
|
|||||||
mcs <- getDefaultCommodityAndStyle
|
mcs <- getDefaultCommodityAndStyle
|
||||||
let
|
let
|
||||||
(c,s) = case mcs of
|
(c,s) = case mcs of
|
||||||
Just (defc,defs) -> (defc, defs{asprecision=max (asprecision defs) (Precision 2)})
|
Just (defc,defs) -> (defc, defs{asprecision=max (asprecision defs) (Just $ Precision 2)})
|
||||||
_ -> ("", amountstyle{asprecision=Precision 2})
|
_ -> ("", amountstyle{asprecision=Just $ Precision 2})
|
||||||
-- lift $ traceparse' "timedotentryp end"
|
-- lift $ traceparse' "timedotentryp end"
|
||||||
return $ nullposting{paccount=a
|
return $ nullposting{paccount=a
|
||||||
,pamount=mixedAmount $ nullamt{acommodity=c, aquantity=hours, astyle=s}
|
,pamount=mixedAmount $ nullamt{acommodity=c, aquantity=hours, astyle=s}
|
||||||
|
|||||||
@ -617,7 +617,8 @@ balanceReportTableAsText ReportOpts{..} =
|
|||||||
tests_MultiBalanceReport = testGroup "MultiBalanceReport" [
|
tests_MultiBalanceReport = testGroup "MultiBalanceReport" [
|
||||||
|
|
||||||
let
|
let
|
||||||
amt0 = Amount {acommodity="$", aquantity=0, aprice=Nothing, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asdigitgroups = Nothing, asdecimalmark = Just '.', asprecision = Precision 2}}
|
amt0 = Amount {acommodity="$", aquantity=0, aprice=Nothing,
|
||||||
|
astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asdigitgroups = Nothing, asdecimalmark = Just '.', asprecision = Just $ Precision 2}}
|
||||||
(rspec,journal) `gives` r = do
|
(rspec,journal) `gives` r = do
|
||||||
let rspec' = rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
|
let rspec' = rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
|
||||||
(eitems, etotal) = r
|
(eitems, etotal) = r
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user