mirror of
https://github.com/simonmichael/hledger.git
synced 2024-11-08 07:09:28 +03:00
lib,cli: No longer strip prices in journalApplyValuationFromOptsWith and mixedAmountApplyValuationAfterSumFromOptsWith (#1577).
These were theoretically an efficiency improvement, but have been error-prone. We instead handle stripping prices at the point of consumption.
This commit is contained in:
parent
613efba1bc
commit
bb7d04c031
@ -407,8 +407,9 @@ displayedAccounts ReportSpec{rsQuery=query,rsOpts=ropts} valuedaccts
|
|||||||
|| not (isZeroRow balance amts)) -- Throw out anything with zero balance
|
|| not (isZeroRow balance amts)) -- Throw out anything with zero balance
|
||||||
where
|
where
|
||||||
d = accountNameLevel name
|
d = accountNameLevel name
|
||||||
balance | ALTree <- accountlistmode_ ropts, d == depth = aibalance
|
balance | ALTree <- accountlistmode_ ropts, d == depth = maybeStripPrices . aibalance
|
||||||
| otherwise = aebalance
|
| otherwise = maybeStripPrices . aebalance
|
||||||
|
where maybeStripPrices = if show_costs_ ropts then id else mixedAmountStripPrices
|
||||||
|
|
||||||
-- Accounts interesting because they are a fork for interesting subaccounts
|
-- Accounts interesting because they are a fork for interesting subaccounts
|
||||||
interestingParents = dbg5 "interestingParents" $ case accountlistmode_ ropts of
|
interestingParents = dbg5 "interestingParents" $ case accountlistmode_ ropts of
|
||||||
|
@ -506,10 +506,9 @@ journalApplyValuationFromOpts rspec j =
|
|||||||
-- | Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.
|
-- | Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.
|
||||||
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
|
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
|
||||||
journalApplyValuationFromOptsWith rspec@ReportSpec{rsOpts=ropts} j priceoracle =
|
journalApplyValuationFromOptsWith rspec@ReportSpec{rsOpts=ropts} j priceoracle =
|
||||||
journalMapPostings (valuation . maybeStripPrices) $ costing j
|
journalMapPostings valuation $ costing j
|
||||||
where
|
where
|
||||||
valuation p = maybe id (postingApplyValuation priceoracle styles (periodEnd p) (rsToday rspec)) (value_ ropts) p
|
valuation p = maybe id (postingApplyValuation priceoracle styles (periodEnd p) (rsToday rspec)) (value_ ropts) p
|
||||||
maybeStripPrices = if show_costs_ ropts then id else postingStripPrices
|
|
||||||
costing = case cost_ ropts of
|
costing = case cost_ ropts of
|
||||||
Cost -> journalToCost
|
Cost -> journalToCost
|
||||||
NoCost -> id
|
NoCost -> id
|
||||||
@ -528,12 +527,11 @@ mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceO
|
|||||||
-> (DateSpan -> MixedAmount -> MixedAmount)
|
-> (DateSpan -> MixedAmount -> MixedAmount)
|
||||||
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
||||||
case valuationAfterSum ropts of
|
case valuationAfterSum ropts of
|
||||||
Just mc -> \span -> valuation mc span . maybeStripPrices . costing
|
Just mc -> \span -> valuation mc span . costing
|
||||||
Nothing -> const id
|
Nothing -> const id
|
||||||
where
|
where
|
||||||
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
||||||
where err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
|
where err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
|
||||||
maybeStripPrices = if show_costs_ ropts then id else mixedAmountStripPrices
|
|
||||||
costing = case cost_ ropts of
|
costing = case cost_ ropts of
|
||||||
Cost -> styleMixedAmount styles . mixedAmountCost
|
Cost -> styleMixedAmount styles . mixedAmountCost
|
||||||
NoCost -> id
|
NoCost -> id
|
||||||
|
@ -654,8 +654,6 @@ balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts
|
|||||||
balanceOpts isTable ReportOpts{..} = oneLine
|
balanceOpts isTable ReportOpts{..} = oneLine
|
||||||
{ displayColour = isTable && color_
|
{ displayColour = isTable && color_
|
||||||
, displayMaxWidth = if isTable && not no_elide_ then Just 32 else Nothing
|
, displayMaxWidth = if isTable && not no_elide_ then Just 32 else Nothing
|
||||||
, displayPrice = True -- multiBalanceReport strips prices from Amounts if they are not being used,
|
|
||||||
-- so we can display prices here without fear.
|
|
||||||
}
|
}
|
||||||
|
|
||||||
tests_Balance = tests "Balance" [
|
tests_Balance = tests "Balance" [
|
||||||
|
@ -83,8 +83,9 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
explicit = boolopt "explicit" rawopts
|
explicit = boolopt "explicit" rawopts
|
||||||
|
|
||||||
-- the balances to close
|
-- the balances to close
|
||||||
(acctbals,_) = balanceReport rspec_ j
|
(acctbals',_) = balanceReport rspec_ j
|
||||||
totalamt = maSum $ map (\(_,_,_,b) -> b) acctbals
|
acctbals = map (\(a,_,_,b) -> (a, if show_costs_ ropts then b else mixedAmountStripPrices b)) acctbals'
|
||||||
|
totalamt = maSum $ map snd acctbals
|
||||||
|
|
||||||
-- since balance assertion amounts are required to be exact, the
|
-- since balance assertion amounts are required to be exact, the
|
||||||
-- amounts in opening/closing transactions should be too (#941, #1137)
|
-- amounts in opening/closing transactions should be too (#941, #1137)
|
||||||
@ -111,7 +112,7 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
++ [posting{paccount=closingacct, pamount=mixedAmount $ precise b} | interleaved]
|
++ [posting{paccount=closingacct, pamount=mixedAmount $ precise b} | interleaved]
|
||||||
|
|
||||||
| -- get the balances for each commodity and transaction price
|
| -- get the balances for each commodity and transaction price
|
||||||
(a,_,_,mb) <- acctbals
|
(a,mb) <- acctbals
|
||||||
, let bs = amounts mb
|
, let bs = amounts mb
|
||||||
-- mark the last balance in each commodity with True
|
-- mark the last balance in each commodity with True
|
||||||
, let bs' = concat [reverse $ zip (reverse bs) (True : repeat False)
|
, let bs' = concat [reverse $ zip (reverse bs) (True : repeat False)
|
||||||
@ -137,7 +138,7 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
]
|
]
|
||||||
++ [posting{paccount=openingacct, pamount=mixedAmount . precise $ negate b} | interleaved]
|
++ [posting{paccount=openingacct, pamount=mixedAmount . precise $ negate b} | interleaved]
|
||||||
|
|
||||||
| (a,_,_,mb) <- acctbals
|
| (a,mb) <- acctbals
|
||||||
, let bs = amounts $ normaliseMixedAmount mb
|
, let bs = amounts $ normaliseMixedAmount mb
|
||||||
-- mark the last balance in each commodity with the unpriced sum in that commodity (for a balance assertion)
|
-- mark the last balance in each commodity with the unpriced sum in that commodity (for a balance assertion)
|
||||||
, let bs' = concat [reverse $ zip (reverse bs) (Just commoditysum : repeat Nothing)
|
, let bs' = concat [reverse $ zip (reverse bs) (Just commoditysum : repeat Nothing)
|
||||||
|
@ -89,8 +89,8 @@ postingsReportItemAsCsvRecord (_, _, _, p, b) = [idx,date,code,desc,acct,amt,bal
|
|||||||
VirtualPosting -> wrap "(" ")"
|
VirtualPosting -> wrap "(" ")"
|
||||||
_ -> id
|
_ -> id
|
||||||
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
||||||
amt = wbToText . showMixedAmountB oneLine{displayPrice=True} $ pamount p
|
amt = wbToText . showMixedAmountB oneLine $ pamount p
|
||||||
bal = wbToText $ showMixedAmountB oneLine{displayPrice=True} b
|
bal = wbToText $ showMixedAmountB oneLine b
|
||||||
|
|
||||||
-- | Render a register report as plain text suitable for console output.
|
-- | Render a register report as plain text suitable for console output.
|
||||||
postingsReportAsText :: CliOpts -> PostingsReport -> TL.Text
|
postingsReportAsText :: CliOpts -> PostingsReport -> TL.Text
|
||||||
@ -104,7 +104,7 @@ postingsReportAsText opts items = TB.toLazyText $ foldMap first3 linesWithWidths
|
|||||||
amtwidth = maximumStrict $ 12 : widths (map itemamt items)
|
amtwidth = maximumStrict $ 12 : widths (map itemamt items)
|
||||||
balwidth = maximumStrict $ 12 : widths (map itembal items)
|
balwidth = maximumStrict $ 12 : widths (map itembal items)
|
||||||
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
||||||
widths = map wbWidth . concatMap (showMixedAmountLinesB oneLine{displayPrice=True})
|
widths = map wbWidth . concatMap (showMixedAmountLinesB oneLine)
|
||||||
itemamt (_,_,_,Posting{pamount=a},_) = a
|
itemamt (_,_,_,Posting{pamount=a},_) = a
|
||||||
itembal (_,_,_,_,a) = a
|
itembal (_,_,_,_,a) = a
|
||||||
|
|
||||||
@ -187,9 +187,7 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
|
|||||||
_ -> (id,acctwidth)
|
_ -> (id,acctwidth)
|
||||||
amt = showamt $ pamount p
|
amt = showamt $ pamount p
|
||||||
bal = showamt b
|
bal = showamt b
|
||||||
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
showamt = showMixedAmountLinesB oneLine{displayColour=color_ . rsOpts $ reportspec_ opts}
|
||||||
showamt = showMixedAmountLinesB oneLine{displayColour=color_, displayPrice=True}
|
|
||||||
where ReportOpts{..} = rsOpts $ reportspec_ opts
|
|
||||||
-- Since this will usually be called with the knot tied between this(amt|bal)width and
|
-- Since this will usually be called with the knot tied between this(amt|bal)width and
|
||||||
-- preferred(amt|bal)width, make sure the former do not depend on the latter to avoid loops.
|
-- preferred(amt|bal)width, make sure the former do not depend on the latter to avoid loops.
|
||||||
thisamtwidth = maximumDef 0 $ map wbWidth amt
|
thisamtwidth = maximumDef 0 $ map wbWidth amt
|
||||||
|
Loading…
Reference in New Issue
Block a user