lib,cli: Strip prices in MultiBalanceReport and PostingsReport whenever
we know we won't need them. Knowing whether we need them is accomplished by pulling the "show-costs" option used by the Close command up into ReportOpts.
This commit is contained in:
parent
b7a2479186
commit
f6feef7f80
@ -558,14 +558,22 @@ cumulativeSum value start = snd . M.mapAccumWithKey accumValued start
|
|||||||
postingAndAccountValuations :: ReportSpec -> Journal -> PriceOracle
|
postingAndAccountValuations :: ReportSpec -> Journal -> PriceOracle
|
||||||
-> (DateSpan -> Posting -> Posting, DateSpan -> Account -> Account)
|
-> (DateSpan -> Posting -> Posting, DateSpan -> Account -> Account)
|
||||||
postingAndAccountValuations ReportSpec{rsToday=today, rsOpts=ropts} j priceoracle = case value_ ropts of
|
postingAndAccountValuations ReportSpec{rsToday=today, rsOpts=ropts} j priceoracle = case value_ ropts of
|
||||||
Just (AtEnd _) -> (const id, avalue' (cost_ ropts) (value_ ropts))
|
-- If we're doing AtEnd valuation, we may need to value the same posting at different dates
|
||||||
_ -> (pvalue' (cost_ ropts) (value_ ropts), const id)
|
-- (for example, when preparing a ValueChange report). So we should only convert to cost and
|
||||||
|
-- maybe strip prices from the Posting, and should do valuation on the Accounts.
|
||||||
|
Just v@(AtEnd _) -> (pvalue Nothing, avalue v)
|
||||||
|
-- Otherwise, all costing and valuation should be done on the Postings.
|
||||||
|
_ -> (pvalue (value_ ropts), const id)
|
||||||
where
|
where
|
||||||
avalue' c v span a = a{aibalance = value (aibalance a), aebalance = value (aebalance a)}
|
-- For a Posting: convert to cost, apply valuation, then strip prices if we don't need them (See issue #1507).
|
||||||
where value = mixedAmountApplyCostValuation priceoracle styles (end span) today (error "multiBalanceReport: did not expect amount valuation to be called ") c v -- PARTIAL: should not happen
|
pvalue v span = maybeStripPrices . postingApplyCostValuation priceoracle styles (end span) today (cost_ ropts) v
|
||||||
pvalue' c v span = postingApplyCostValuation priceoracle styles (end span) today c v
|
-- For an Account: Apply valuation to both the inclusive and exclusive balances.
|
||||||
end = fromMaybe (error "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen
|
avalue v span a = a{aibalance = value (aibalance a), aebalance = value (aebalance a)}
|
||||||
. fmap (addDays (-1)) . spanEnd
|
where value = mixedAmountApplyValuation priceoracle styles (end span) today (error "multiBalanceReport: did not expect amount valuation to be called ") v -- PARTIAL: should not happen
|
||||||
|
|
||||||
|
maybeStripPrices = if show_costs_ ropts then id else postingStripPrices
|
||||||
|
end = maybe (error "multiBalanceReport: expected all spans to have an end date") -- PARTIAL: should not happen
|
||||||
|
(addDays (-1)) . spanEnd
|
||||||
styles = journalCommodityStyles j
|
styles = journalCommodityStyles j
|
||||||
|
|
||||||
-- tests
|
-- tests
|
||||||
|
|||||||
@ -91,8 +91,9 @@ postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items
|
|||||||
fromMaybe (error' "postingsReport: expected a non-empty journal") $ -- PARTIAL: shouldn't happen
|
fromMaybe (error' "postingsReport: expected a non-empty journal") $ -- PARTIAL: shouldn't happen
|
||||||
reportPeriodOrJournalLastDay rspec j
|
reportPeriodOrJournalLastDay rspec j
|
||||||
|
|
||||||
-- Posting report does not use prices after valuation, so remove them.
|
-- Strip prices from postings if we won't need them.
|
||||||
displaypsnoprices = map (\(p,md) -> (postingStripPrices p, md)) displayps
|
displaypsnoprices = map (\(p,md) -> (maybeStripPrices p, md)) displayps
|
||||||
|
where maybeStripPrices = if show_costs_ then id else postingStripPrices
|
||||||
|
|
||||||
-- Posting report items ready for display.
|
-- Posting report items ready for display.
|
||||||
items =
|
items =
|
||||||
|
|||||||
@ -119,6 +119,7 @@ data ReportOpts = ReportOpts {
|
|||||||
,drop_ :: Int
|
,drop_ :: Int
|
||||||
,row_total_ :: Bool
|
,row_total_ :: Bool
|
||||||
,no_total_ :: Bool
|
,no_total_ :: Bool
|
||||||
|
,show_costs_ :: Bool -- ^ Whether to show costs for reports which normally don't show them
|
||||||
,pretty_tables_ :: Bool
|
,pretty_tables_ :: Bool
|
||||||
,sort_amount_ :: Bool
|
,sort_amount_ :: Bool
|
||||||
,percent_ :: Bool
|
,percent_ :: Bool
|
||||||
@ -166,6 +167,7 @@ defreportopts = ReportOpts
|
|||||||
, drop_ = 0
|
, drop_ = 0
|
||||||
, row_total_ = False
|
, row_total_ = False
|
||||||
, no_total_ = False
|
, no_total_ = False
|
||||||
|
, show_costs_ = False
|
||||||
, pretty_tables_ = False
|
, pretty_tables_ = False
|
||||||
, sort_amount_ = False
|
, sort_amount_ = False
|
||||||
, percent_ = False
|
, percent_ = False
|
||||||
@ -215,6 +217,7 @@ rawOptsToReportOpts rawopts = do
|
|||||||
,drop_ = posintopt "drop" rawopts
|
,drop_ = posintopt "drop" rawopts
|
||||||
,row_total_ = boolopt "row-total" rawopts
|
,row_total_ = boolopt "row-total" rawopts
|
||||||
,no_total_ = boolopt "no-total" rawopts
|
,no_total_ = boolopt "no-total" rawopts
|
||||||
|
,show_costs_ = boolopt "show-costs" rawopts
|
||||||
,sort_amount_ = boolopt "sort-amount" rawopts
|
,sort_amount_ = boolopt "sort-amount" rawopts
|
||||||
,percent_ = boolopt "percent" rawopts
|
,percent_ = boolopt "percent" rawopts
|
||||||
,invert_ = boolopt "invert" rawopts
|
,invert_ = boolopt "invert" rawopts
|
||||||
|
|||||||
@ -388,11 +388,11 @@ balance opts@CliOpts{reportspec_=rspec} j = case reporttype_ of
|
|||||||
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
|
balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV
|
||||||
balanceReportAsCsv opts (items, total) =
|
balanceReportAsCsv opts (items, total) =
|
||||||
["account","balance"] :
|
["account","balance"] :
|
||||||
[[accountNameDrop (drop_ opts) a, wbToText $ showMixedAmountB oneLine b] | (a, _, _, b) <- items]
|
[[accountNameDrop (drop_ opts) a, wbToText $ showMixedAmountB (balanceOpts False opts) b] | (a, _, _, b) <- items]
|
||||||
++
|
++
|
||||||
if no_total_ opts
|
if no_total_ opts
|
||||||
then []
|
then []
|
||||||
else [["total", wbToText $ showMixedAmountB oneLine total]]
|
else [["total", wbToText $ showMixedAmountB (balanceOpts False opts) total]]
|
||||||
|
|
||||||
-- | Render a single-column balance report as plain text.
|
-- | Render a single-column balance report as plain text.
|
||||||
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
|
balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder
|
||||||
@ -461,12 +461,12 @@ renderComponent topaligned opts (acctname, depth, total) (FormatField ljust mmin
|
|||||||
DepthSpacerField -> Cell align [WideBuilder (TB.fromText $ T.replicate d " ") d]
|
DepthSpacerField -> Cell align [WideBuilder (TB.fromText $ T.replicate d " ") d]
|
||||||
where d = maybe id min mmax $ depth * fromMaybe 1 mmin
|
where d = maybe id min mmax $ depth * fromMaybe 1 mmin
|
||||||
AccountField -> textCell align $ formatText ljust mmin mmax acctname
|
AccountField -> textCell align $ formatText ljust mmin mmax acctname
|
||||||
TotalField -> Cell align . pure $ showamt total
|
TotalField -> Cell align . pure $ showMixedAmountB dopts total
|
||||||
_ -> Cell align [mempty]
|
_ -> Cell align [mempty]
|
||||||
where
|
where
|
||||||
align = if topaligned then (if ljust then TopLeft else TopRight)
|
align = if topaligned then (if ljust then TopLeft else TopRight)
|
||||||
else (if ljust then BottomLeft else BottomRight)
|
else (if ljust then BottomLeft else BottomRight)
|
||||||
showamt = showMixedAmountB noPrice{displayColour=color_ opts, displayMinWidth=mmin, displayMaxWidth=mmax}
|
dopts = (balanceOpts True opts){displayOneLine=False, displayMinWidth=mmin, displayMaxWidth=mmax}
|
||||||
|
|
||||||
-- rendering multi-column balance reports
|
-- rendering multi-column balance reports
|
||||||
|
|
||||||
@ -482,7 +482,7 @@ multiBalanceReportAsCsv opts@ReportOpts{average_, row_total_}
|
|||||||
++ ["average" | average_]
|
++ ["average" | average_]
|
||||||
) :
|
) :
|
||||||
[displayName a :
|
[displayName a :
|
||||||
map (wbToText . showMixedAmountB oneLine)
|
map (wbToText . showMixedAmountB (balanceOpts False opts))
|
||||||
(amts
|
(amts
|
||||||
++ [rowtot | row_total_]
|
++ [rowtot | row_total_]
|
||||||
++ [rowavg | average_])
|
++ [rowavg | average_])
|
||||||
@ -491,7 +491,7 @@ multiBalanceReportAsCsv opts@ReportOpts{average_, row_total_}
|
|||||||
if no_total_ opts
|
if no_total_ opts
|
||||||
then []
|
then []
|
||||||
else ["total" :
|
else ["total" :
|
||||||
map (wbToText . showMixedAmountB oneLine) (
|
map (wbToText . showMixedAmountB (balanceOpts False opts)) (
|
||||||
coltotals
|
coltotals
|
||||||
++ [tot | row_total_]
|
++ [tot | row_total_]
|
||||||
++ [avg | average_]
|
++ [avg | average_]
|
||||||
@ -656,13 +656,19 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balancetype_}
|
|||||||
-- console output. Amounts with more than two commodities will be elided
|
-- console output. Amounts with more than two commodities will be elided
|
||||||
-- unless --no-elide is used.
|
-- unless --no-elide is used.
|
||||||
balanceReportTableAsText :: ReportOpts -> Table T.Text T.Text MixedAmount -> TB.Builder
|
balanceReportTableAsText :: ReportOpts -> Table T.Text T.Text MixedAmount -> TB.Builder
|
||||||
balanceReportTableAsText ReportOpts{..} =
|
balanceReportTableAsText ropts@ReportOpts{..} =
|
||||||
Tab.renderTableB def{tableBorders=False, prettyTable=pretty_tables_}
|
Tab.renderTableB def{tableBorders=False, prettyTable=pretty_tables_}
|
||||||
(Tab.textCell TopLeft) (Tab.textCell TopRight) showamt
|
(Tab.textCell TopLeft) (Tab.textCell TopRight) $
|
||||||
where
|
Cell TopRight . pure . showMixedAmountB (balanceOpts True ropts)
|
||||||
showamt = Cell TopRight . pure . showMixedAmountB oneLine{displayColour=color_, displayMaxWidth=mmax}
|
|
||||||
mmax = if no_elide_ then Nothing else Just 32
|
|
||||||
|
|
||||||
|
-- | Amount display options to use for balance reports
|
||||||
|
balanceOpts :: Bool -> ReportOpts -> AmountDisplayOpts
|
||||||
|
balanceOpts isTable ReportOpts{..} = oneLine
|
||||||
|
{ displayColour = isTable && color_
|
||||||
|
, 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" [
|
||||||
|
|
||||||
|
|||||||
@ -82,14 +82,9 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
-- should we show the amount(s) on the equity posting(s) ?
|
-- should we show the amount(s) on the equity posting(s) ?
|
||||||
explicit = boolopt "explicit" rawopts
|
explicit = boolopt "explicit" rawopts
|
||||||
|
|
||||||
-- should we preserve cost information ?
|
|
||||||
normalise = case boolopt "show-costs" rawopts of
|
|
||||||
True -> normaliseMixedAmount
|
|
||||||
False -> normaliseMixedAmount . mixedAmountStripPrices
|
|
||||||
|
|
||||||
-- the balances to close
|
-- the balances to close
|
||||||
(acctbals,_) = balanceReport rspec_ j
|
(acctbals,_) = balanceReport rspec_ j
|
||||||
totalamt = maSum $ map (\(_,_,_,b) -> normalise b) acctbals
|
totalamt = maSum $ map (\(_,_,_,b) -> b) 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)
|
||||||
@ -117,13 +112,13 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
|
|
||||||
| -- 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 $ normalise mb
|
, let bs = amounts $ normaliseMixedAmount 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)
|
||||||
| bs <- groupBy ((==) `on` acommodity) bs]
|
| bs <- groupBy ((==) `on` acommodity) bs]
|
||||||
, (b, islast) <- bs'
|
, (b, islast) <- bs'
|
||||||
]
|
]
|
||||||
|
|
||||||
-- or a final multicommodity posting transferring all balances to equity
|
-- or a final multicommodity posting transferring all balances to equity
|
||||||
-- (print will show this as multiple single-commodity postings)
|
-- (print will show this as multiple single-commodity postings)
|
||||||
++ [posting{paccount=closingacct, pamount=if explicit then mapMixedAmount precise totalamt else missingmixedamt} | not interleaved]
|
++ [posting{paccount=closingacct, pamount=if explicit then mapMixedAmount precise totalamt else missingmixedamt} | not interleaved]
|
||||||
@ -143,7 +138,7 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
|||||||
++ [posting{paccount=openingacct, pamount=Mixed [precise $ negate b]} | interleaved]
|
++ [posting{paccount=openingacct, pamount=Mixed [precise $ negate b]} | interleaved]
|
||||||
|
|
||||||
| (a,_,_,mb) <- acctbals
|
| (a,_,_,mb) <- acctbals
|
||||||
, let bs = amounts $ normalise 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)
|
||||||
| bs <- groupBy ((==) `on` acommodity) bs
|
| bs <- groupBy ((==) `on` acommodity) bs
|
||||||
|
|||||||
@ -93,8 +93,9 @@ postingsReportItemAsCsvRecord (_, _, _, p, b) = [idx,date,code,desc,acct,amt,bal
|
|||||||
BalancedVirtualPosting -> wrap "[" "]"
|
BalancedVirtualPosting -> wrap "[" "]"
|
||||||
VirtualPosting -> wrap "(" ")"
|
VirtualPosting -> wrap "(" ")"
|
||||||
_ -> id
|
_ -> id
|
||||||
amt = wbToText . showMixedAmountB oneLine $ pamount p
|
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
||||||
bal = wbToText $ showMixedAmountB oneLine b
|
amt = wbToText . showMixedAmountB oneLine{displayPrice=True} $ pamount p
|
||||||
|
bal = wbToText $ showMixedAmountB oneLine{displayPrice=True} 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
|
||||||
@ -107,7 +108,8 @@ postingsReportAsText opts items = TB.toLazyText $ foldMap first3 linesWithWidths
|
|||||||
-- balwidth = maximum $ 12 : map third3 linesWithWidths
|
-- balwidth = maximum $ 12 : map third3 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)
|
||||||
widths = map wbWidth . concatMap (showAmountsLinesB noPrice)
|
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
||||||
|
widths = map wbWidth . concatMap (showAmountsLinesB oneLine{displayPrice=True})
|
||||||
itemamt (_,_,_,Posting{pamount=a},_) = amounts a
|
itemamt (_,_,_,Posting{pamount=a},_) = amounts a
|
||||||
itembal (_,_,_,_,a) = amounts a
|
itembal (_,_,_,_,a) = amounts a
|
||||||
|
|
||||||
@ -190,7 +192,9 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
|
|||||||
_ -> (id,acctwidth)
|
_ -> (id,acctwidth)
|
||||||
amt = showAmountsLinesB dopts . (\x -> if null x then [nullamt] else x) . amounts $ pamount p
|
amt = showAmountsLinesB dopts . (\x -> if null x then [nullamt] else x) . amounts $ pamount p
|
||||||
bal = showAmountsLinesB dopts $ amounts b
|
bal = showAmountsLinesB dopts $ amounts b
|
||||||
dopts = noPrice{displayColour=color_ . rsOpts $ reportspec_ opts}
|
-- Since postingsReport strips prices from all Amounts when not used, we can display prices.
|
||||||
|
dopts = 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
|
||||||
|
|||||||
@ -210,7 +210,19 @@ hledger -f - balance --no-total -E
|
|||||||
-1Y b
|
-1Y b
|
||||||
>>>= 0
|
>>>= 0
|
||||||
|
|
||||||
# 18. the above with -B
|
# 18. Without -E, a should be hidden because its balance is zero, even though it has a non-zero cost.
|
||||||
|
hledger -f - balance --no-total
|
||||||
|
<<<
|
||||||
|
1/1
|
||||||
|
a 1X @@ 1Y
|
||||||
|
a 1X @@ 1Y
|
||||||
|
a -2X @@ 1Y
|
||||||
|
b
|
||||||
|
>>>
|
||||||
|
-1Y b
|
||||||
|
>>>= 0
|
||||||
|
|
||||||
|
# 19. the above with -B
|
||||||
hledger -f - balance --no-total -E -B
|
hledger -f - balance --no-total -E -B
|
||||||
<<<
|
<<<
|
||||||
1/1
|
1/1
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user