lib: clarify zero-checking function names
isZeroAmount -> amountLooksZero isReallyZeroAmount -> amountIsZero isZeroMixedAmount -> mixedAmountLooksZero isReallyZeroMixedAmount -> mixedAmountIsZero isReallyZeroMixedAmountCost dropped
This commit is contained in:
parent
74fae2e1de
commit
660ba7e1d9
@ -63,6 +63,8 @@ module Hledger.Data.Amount (
|
||||
-- ** arithmetic
|
||||
costOfAmount,
|
||||
amountToCost,
|
||||
amountIsZero,
|
||||
amountLooksZero,
|
||||
divideAmount,
|
||||
multiplyAmount,
|
||||
divideAmountAndPrice,
|
||||
@ -110,11 +112,8 @@ module Hledger.Data.Amount (
|
||||
averageMixedAmounts,
|
||||
isNegativeAmount,
|
||||
isNegativeMixedAmount,
|
||||
isZeroAmount,
|
||||
isReallyZeroAmount,
|
||||
isZeroMixedAmount,
|
||||
isReallyZeroMixedAmount,
|
||||
isReallyZeroMixedAmountCost,
|
||||
mixedAmountIsZero,
|
||||
mixedAmountLooksZero,
|
||||
mixedAmountTotalPriceToUnitPrice,
|
||||
-- ** rendering
|
||||
styleMixedAmount,
|
||||
@ -269,14 +268,14 @@ isNegativeAmount Amount{aquantity=q} = q < 0
|
||||
|
||||
digits = "123456789" :: String
|
||||
|
||||
-- | Does this amount appear to be zero when displayed with its given precision ?
|
||||
isZeroAmount :: Amount -> Bool
|
||||
isZeroAmount -- a==missingamt = False
|
||||
= not . any (`elem` digits) . showAmountWithoutPriceOrCommodity
|
||||
-- | Does mixed amount appear to be zero when rendered with its
|
||||
-- display precision ?
|
||||
amountLooksZero :: Amount -> Bool
|
||||
amountLooksZero = not . any (`elem` digits) . showAmountWithoutPriceOrCommodity
|
||||
|
||||
-- | Is this amount "really" zero, regardless of the display precision ?
|
||||
isReallyZeroAmount :: Amount -> Bool
|
||||
isReallyZeroAmount Amount{aquantity=q} = q == 0
|
||||
-- | Is this amount exactly zero, ignoring its display precision ?
|
||||
amountIsZero :: Amount -> Bool
|
||||
amountIsZero Amount{aquantity=q} = q == 0
|
||||
|
||||
-- | Get the string representation of an amount, based on its commodity's
|
||||
-- display settings except using the specified precision.
|
||||
@ -520,7 +519,7 @@ normaliseHelper squashprices (Mixed as)
|
||||
newzero = case filter (/= "") (map acommodity zeros) of
|
||||
_:_ -> last zeros
|
||||
_ -> nullamt
|
||||
(zeros, nonzeros) = partition isReallyZeroAmount $
|
||||
(zeros, nonzeros) = partition amountIsZero $
|
||||
map sumSimilarAmountsUsingFirstPrice $
|
||||
groupBy groupfn $
|
||||
sortBy sortfn
|
||||
@ -619,26 +618,20 @@ isNegativeMixedAmount m =
|
||||
as | all isNegativeAmount as -> Just True
|
||||
_ -> Nothing -- multiple amounts with different signs
|
||||
|
||||
-- XXX rename to mixedAmountLooksZero, mixedAmountIsZero, mixedAmountCostIsZero ?
|
||||
-- | Does this mixed amount appear to be zero when rendered with its
|
||||
-- display precision ?
|
||||
mixedAmountLooksZero :: MixedAmount -> Bool
|
||||
mixedAmountLooksZero = all amountLooksZero . amounts . normaliseMixedAmountSquashPricesForDisplay
|
||||
|
||||
-- | Does this mixed amount appear to be zero when displayed with its given precision ?
|
||||
isZeroMixedAmount :: MixedAmount -> Bool
|
||||
isZeroMixedAmount = all isZeroAmount . amounts . normaliseMixedAmountSquashPricesForDisplay
|
||||
|
||||
-- | Is this mixed amount "really" zero ? See isReallyZeroAmount.
|
||||
isReallyZeroMixedAmount :: MixedAmount -> Bool
|
||||
isReallyZeroMixedAmount = all isReallyZeroAmount . amounts . normaliseMixedAmountSquashPricesForDisplay
|
||||
|
||||
-- | Is this mixed amount "really" zero, after converting to cost
|
||||
-- commodities where possible ?
|
||||
isReallyZeroMixedAmountCost :: MixedAmount -> Bool
|
||||
isReallyZeroMixedAmountCost = isReallyZeroMixedAmount . costOfMixedAmount
|
||||
-- | Is this mixed amount exactly zero, ignoring display precisions ?
|
||||
mixedAmountIsZero :: MixedAmount -> Bool
|
||||
mixedAmountIsZero = all amountIsZero . amounts . normaliseMixedAmountSquashPricesForDisplay
|
||||
|
||||
-- -- | MixedAmount derived Eq instance in Types.hs doesn't know that we
|
||||
-- -- want $0 = EUR0 = 0. Yet we don't want to drag all this code over there.
|
||||
-- -- For now, use this when cross-commodity zero equality is important.
|
||||
-- mixedAmountEquals :: MixedAmount -> MixedAmount -> Bool
|
||||
-- mixedAmountEquals a b = amounts a' == amounts b' || (isZeroMixedAmount a' && isZeroMixedAmount b')
|
||||
-- mixedAmountEquals a b = amounts a' == amounts b' || (mixedAmountLooksZero a' && mixedAmountLooksZero b')
|
||||
-- where a' = normaliseMixedAmountSquashPricesForDisplay a
|
||||
-- b' = normaliseMixedAmountSquashPricesForDisplay b
|
||||
|
||||
@ -755,9 +748,9 @@ tests_Amount = tests "Amount" [
|
||||
costOfAmount (eur 1){aprice=Just $ TotalPrice $ usd 2} @?= usd 2
|
||||
costOfAmount (eur (-1)){aprice=Just $ TotalPrice $ usd 2} @?= usd (-2)
|
||||
|
||||
,test "isZeroAmount" $ do
|
||||
assertBool "" $ isZeroAmount amount
|
||||
assertBool "" $ isZeroAmount $ usd 0
|
||||
,test "amountLooksZero" $ do
|
||||
assertBool "" $ amountLooksZero amount
|
||||
assertBool "" $ amountLooksZero $ usd 0
|
||||
|
||||
,test "negating amounts" $ do
|
||||
negate (usd 1) @?= (usd 1){aquantity= -1}
|
||||
@ -772,7 +765,7 @@ tests_Amount = tests "Amount" [
|
||||
asprecision (astyle $ sum [usd 1 `withPrecision` 1, usd 1 `withPrecision` 3]) @?= 3
|
||||
asprecision (astyle $ sum [usd 1 `withPrecision` 3, usd 1 `withPrecision` 1]) @?= 3
|
||||
-- adding different commodities assumes conversion rate 1
|
||||
assertBool "" $ isZeroAmount (usd 1.23 - eur 1.23)
|
||||
assertBool "" $ amountLooksZero (usd 1.23 - eur 1.23)
|
||||
|
||||
,test "showAmount" $ do
|
||||
showAmount (usd 0 + gbp 0) @?= "0"
|
||||
@ -825,7 +818,7 @@ tests_Amount = tests "Amount" [
|
||||
|
||||
,test "normaliseMixedAmountSquashPricesForDisplay" $ do
|
||||
normaliseMixedAmountSquashPricesForDisplay (Mixed []) @?= Mixed [nullamt]
|
||||
assertBool "" $ isZeroMixedAmount $ normaliseMixedAmountSquashPricesForDisplay
|
||||
assertBool "" $ mixedAmountLooksZero $ normaliseMixedAmountSquashPricesForDisplay
|
||||
(Mixed [usd 10
|
||||
,usd 10 @@ eur 7
|
||||
,usd (-10)
|
||||
|
||||
@ -253,7 +253,7 @@ isPostingInDateSpan' PrimaryDate s = spanContainsDate s . postingDate
|
||||
isPostingInDateSpan' SecondaryDate s = spanContainsDate s . postingDate2
|
||||
|
||||
isEmptyPosting :: Posting -> Bool
|
||||
isEmptyPosting = isZeroMixedAmount . pamount
|
||||
isEmptyPosting = mixedAmountLooksZero . pamount
|
||||
|
||||
-- AccountName stuff that depends on PostingType
|
||||
|
||||
|
||||
@ -357,7 +357,7 @@ transactionCheckBalanced mstyles t = errs
|
||||
-- check for mixed signs, detecting nonzeros at display precision
|
||||
canonicalise = maybe id canonicaliseMixedAmount mstyles
|
||||
signsOk ps =
|
||||
case filter (not.isZeroMixedAmount) $ map (canonicalise.costOfMixedAmount.pamount) ps of
|
||||
case filter (not.mixedAmountLooksZero) $ map (canonicalise.costOfMixedAmount.pamount) ps of
|
||||
nonzeros | length nonzeros >= 2
|
||||
-> length (nubSort $ mapMaybe isNegativeMixedAmount nonzeros) > 1
|
||||
_ -> True
|
||||
@ -367,7 +367,7 @@ transactionCheckBalanced mstyles t = errs
|
||||
(rsum, bvsum) = (sumPostings rps, sumPostings bvps)
|
||||
(rsumcost, bvsumcost) = (costOfMixedAmount rsum, costOfMixedAmount bvsum)
|
||||
(rsumdisplay, bvsumdisplay) = (canonicalise rsumcost, canonicalise bvsumcost)
|
||||
(rsumok, bvsumok) = (isZeroMixedAmount rsumdisplay, isZeroMixedAmount bvsumdisplay)
|
||||
(rsumok, bvsumok) = (mixedAmountLooksZero rsumdisplay, mixedAmountLooksZero bvsumdisplay)
|
||||
|
||||
-- generate error messages, showing amounts with their original precision
|
||||
errs = filter (not.null) [rmsg, bvmsg]
|
||||
|
||||
@ -606,9 +606,9 @@ matchesPosting (Real v) p = v == isReal p
|
||||
matchesPosting q@(Depth _) Posting{paccount=a} = q `matchesAccount` a
|
||||
matchesPosting q@(Amt _ _) Posting{pamount=amt} = q `matchesMixedAmount` amt
|
||||
-- matchesPosting q@(Amt _ _) Posting{pamount=amt} = q `matchesMixedAmount` amt
|
||||
-- matchesPosting (Empty v) Posting{pamount=a} = v == isZeroMixedAmount a
|
||||
-- matchesPosting (Empty v) Posting{pamount=a} = v == mixedAmountLooksZero a
|
||||
-- matchesPosting (Empty False) Posting{pamount=a} = True
|
||||
-- matchesPosting (Empty True) Posting{pamount=a} = isZeroMixedAmount a
|
||||
-- matchesPosting (Empty True) Posting{pamount=a} = mixedAmountLooksZero a
|
||||
matchesPosting (Empty _) _ = True
|
||||
matchesPosting (Sym r) Posting{pamount=Mixed as} = any (matchesCommodity (Sym r)) $ map acommodity as
|
||||
matchesPosting (Tag n v) p = case (n, v) of
|
||||
|
||||
@ -898,7 +898,7 @@ getAmount rules record currency p1IsVirtual n =
|
||||
assignments''
|
||||
| length assignments' > 1 && not (null nonzeros) = nonzeros
|
||||
| otherwise = assignments'
|
||||
where nonzeros = filter (not . isZeroMixedAmount . snd) assignments'
|
||||
where nonzeros = filter (not . mixedAmountLooksZero . snd) assignments'
|
||||
|
||||
in case -- dbg0 ("amounts for posting "++show n)
|
||||
assignments'' of
|
||||
|
||||
@ -110,9 +110,9 @@ balanceReport ropts@ReportOpts{..} q j =
|
||||
clipAccounts (queryDepth q) valuedaccttree
|
||||
where
|
||||
balance = if flat_ ropts then aebalance else aibalance
|
||||
filterzeros = if empty_ then id else filter (not . isZeroMixedAmount . balance)
|
||||
filterempty = filter (\a -> anumpostings a > 0 || not (isZeroMixedAmount (balance a)))
|
||||
prunezeros = if empty_ then id else fromMaybe nullacct . pruneAccounts (isZeroMixedAmount . balance)
|
||||
filterzeros = if empty_ then id else filter (not . mixedAmountLooksZero . balance)
|
||||
filterempty = filter (\a -> anumpostings a > 0 || not (mixedAmountLooksZero (balance a)))
|
||||
prunezeros = if empty_ then id else fromMaybe nullacct . pruneAccounts (mixedAmountLooksZero . balance)
|
||||
markboring = if no_elide_ then id else markBoringParentAccounts
|
||||
|
||||
-- Make a report row for each account.
|
||||
@ -165,7 +165,7 @@ sortAccountItemsLike sortedas items =
|
||||
markBoringParentAccounts :: Account -> Account
|
||||
markBoringParentAccounts = tieAccountParents . mapAccounts mark
|
||||
where
|
||||
mark a | length (asubs a) == 1 && isZeroMixedAmount (aebalance a) = a{aboring=True}
|
||||
mark a | length (asubs a) == 1 && mixedAmountLooksZero (aebalance a) = a{aboring=True}
|
||||
| otherwise = a
|
||||
|
||||
balanceReportItem :: ReportOpts -> Query -> Account -> BalanceReportItem
|
||||
@ -204,9 +204,9 @@ unifyMixedAmount :: MixedAmount -> Amount
|
||||
unifyMixedAmount mixedAmount = foldl combine (num 0) (amounts mixedAmount)
|
||||
where
|
||||
combine amount result =
|
||||
if isReallyZeroAmount amount
|
||||
if amountIsZero amount
|
||||
then result
|
||||
else if isReallyZeroAmount result
|
||||
else if amountIsZero result
|
||||
then amount
|
||||
else if acommodity amount == acommodity result
|
||||
then amount + result
|
||||
@ -218,7 +218,7 @@ perdivide :: MixedAmount -> MixedAmount -> MixedAmount
|
||||
perdivide a b =
|
||||
let a' = unifyMixedAmount a
|
||||
b' = unifyMixedAmount b
|
||||
in if isReallyZeroAmount a' || isReallyZeroAmount b' || acommodity a' == acommodity b'
|
||||
in if amountIsZero a' || amountIsZero b' || acommodity a' == acommodity b'
|
||||
then mixed [per $ if aquantity b' == 0 then 0 else (aquantity a' / abs (aquantity b') * 100)]
|
||||
else error' "Cannot calculate percentages if accounts have different commodities. (Hint: Try --cost, -V or similar flags.)"
|
||||
|
||||
|
||||
@ -291,7 +291,7 @@ budgetReportAsText ropts@ReportOpts{..} budgetr =
|
||||
percentage :: Change -> BudgetGoal -> Maybe Percentage
|
||||
percentage actual budget =
|
||||
case (maybecost $ normaliseMixedAmount actual, maybecost $ normaliseMixedAmount budget) of
|
||||
(Mixed [a], Mixed [b]) | (acommodity a == acommodity b || isZeroAmount a) && not (isZeroAmount b)
|
||||
(Mixed [a], Mixed [b]) | (acommodity a == acommodity b || amountLooksZero a) && not (amountLooksZero b)
|
||||
-> Just $ 100 * aquantity a / aquantity b
|
||||
_ -> -- trace (pshow $ (maybecost actual, maybecost budget)) -- debug missing percentage
|
||||
Nothing
|
||||
|
||||
@ -249,7 +249,7 @@ multiBalanceReportWith ropts@ReportOpts{..} q j priceoracle =
|
||||
-- Total for a cumulative/historical report is always zero.
|
||||
, let rowtot = if balancetype_==PeriodChange then sum valuedrowbals else 0
|
||||
, let rowavg = averageMixedAmounts valuedrowbals
|
||||
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedrowbals
|
||||
, empty_ || depth == 0 || any (not . mixedAmountLooksZero) valuedrowbals
|
||||
]
|
||||
where
|
||||
avalue periodlast =
|
||||
|
||||
@ -253,7 +253,7 @@ summarisePostingsInDateSpan (DateSpan b e) wd depth showempty ps
|
||||
| otherwise = ["..."]
|
||||
summaryps | depth > 0 = [summaryp{paccount=a,pamount=balance a} | a <- clippedanames]
|
||||
| otherwise = [summaryp{paccount="...",pamount=sum $ map pamount ps}]
|
||||
summarypes = map (, e') $ (if showempty then id else filter (not . isZeroMixedAmount . pamount)) summaryps
|
||||
summarypes = map (, e') $ (if showempty then id else filter (not . mixedAmountLooksZero . pamount)) summaryps
|
||||
anames = nubSort $ map paccount ps
|
||||
-- aggregate balances by account, like ledgerFromJournal, then do depth-clipping
|
||||
accts = accountsFromPostings ps
|
||||
|
||||
@ -80,7 +80,7 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportopts_=ropts
|
||||
]
|
||||
|
||||
(_label,items) = accountTransactionsReport ropts' j q thisacctq
|
||||
items' = (if empty_ ropts' then id else filter (not . isZeroMixedAmount . fifth6)) $ -- without --empty, exclude no-change txns
|
||||
items' = (if empty_ ropts' then id else filter (not . mixedAmountLooksZero . fifth6)) $ -- without --empty, exclude no-change txns
|
||||
reverse -- most recent last
|
||||
items
|
||||
|
||||
|
||||
@ -339,7 +339,7 @@ amountAndCommentWizard PrevInput{..} EntryState{..} = do
|
||||
def = case (esArgs, mhistoricalp, followedhistoricalsofar) of
|
||||
(d:_,_,_) -> d
|
||||
(_,Just hp,True) -> showamt $ pamount hp
|
||||
_ | pnum > 1 && not (isZeroMixedAmount balancingamt) -> showamt balancingamtfirstcommodity
|
||||
_ | pnum > 1 && not (mixedAmountLooksZero balancingamt) -> showamt balancingamtfirstcommodity
|
||||
_ -> ""
|
||||
retryMsg "A valid hledger amount is required. Eg: 1, $2, 3 EUR, \"4 red apples\"." $
|
||||
parser parseAmountAndComment $
|
||||
|
||||
@ -274,11 +274,11 @@ compoundBalanceSubreport ropts@ReportOpts{..} userq j priceoracle subreportqfn s
|
||||
nonzeroaccounts =
|
||||
dbg1 "nonzeroaccounts" $
|
||||
mapMaybe (\(PeriodicReportRow act _ amts _ _) ->
|
||||
if not (all isZeroMixedAmount amts) then Just act else Nothing) rows
|
||||
if not (all mixedAmountLooksZero amts) then Just act else Nothing) rows
|
||||
rows' = filter (not . emptyRow) rows
|
||||
where
|
||||
emptyRow (PeriodicReportRow act _ amts _ _) =
|
||||
all isZeroMixedAmount amts && not (any (act `isAccountNamePrefixOf`) nonzeroaccounts)
|
||||
all mixedAmountLooksZero amts && not (any (act `isAccountNamePrefixOf`) nonzeroaccounts)
|
||||
|
||||
-- | Render a compound balance report as plain text suitable for console output.
|
||||
{- Eg:
|
||||
|
||||
Loading…
Reference in New Issue
Block a user