Revert "feat: bal: with --declared, include all declared accounts (#1765)"

This reverts commit a5e19b7391.
(It breaks filtering by account.)
This commit is contained in:
Simon Michael 2021-11-22 12:04:45 -10:00
parent b7e79ef3b2
commit 94d92b9760
5 changed files with 25 additions and 48 deletions

View File

@ -1,6 +1,5 @@
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-| {-|
@ -27,6 +26,7 @@ module Hledger.Reports.MultiBalanceReport (
getPostingsByColumn, getPostingsByColumn,
getPostings, getPostings,
startingPostings, startingPostings,
startingBalancesFromPostings,
generateMultiBalanceReport, generateMultiBalanceReport,
balanceReportTableAsText, balanceReportTableAsText,
@ -122,8 +122,8 @@ multiBalanceReportWith rspec' j priceoracle = report
-- The matched accounts with a starting balance. All of these should appear -- The matched accounts with a starting balance. All of these should appear
-- in the report, even if they have no postings during the report period. -- in the report, even if they have no postings during the report period.
startbals = dbg5 "startbals" $ startbals = dbg5 "startbals" . startingBalancesFromPostings rspec j priceoracle
startingBalances rspec j priceoracle $ startingPostings rspec j priceoracle reportspan $ startingPostings rspec j priceoracle reportspan
-- Generate and postprocess the report, negating balances and taking percentages if needed -- Generate and postprocess the report, negating balances and taking percentages if needed
report = dbg4 "multiBalanceReportWith" $ report = dbg4 "multiBalanceReportWith" $
@ -166,7 +166,7 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr
-- Filter the column postings according to each subreport -- Filter the column postings according to each subreport
colps' = map (second $ filter (matchesPosting q)) colps colps' = map (second $ filter (matchesPosting q)) colps
-- We need to filter historical postings directly, rather than their accumulated balances. (#1698) -- We need to filter historical postings directly, rather than their accumulated balances. (#1698)
startbals' = startingBalances rspec j priceoracle $ filter (matchesPosting q) startps startbals' = startingBalancesFromPostings rspec j priceoracle $ filter (matchesPosting q) startps
ropts = cbcsubreportoptions $ _rsReportOpts rspec ropts = cbcsubreportoptions $ _rsReportOpts rspec
q = cbcsubreportquery j q = cbcsubreportquery j
@ -183,12 +183,10 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr
cbr = CompoundPeriodicReport "" (map fst colps) subreports overalltotals cbr = CompoundPeriodicReport "" (map fst colps) subreports overalltotals
-- XXX seems refactorable -- | Calculate starting balances from postings, if needed for -H.
-- | Calculate accounts' balances on the report start date, from these postings startingBalancesFromPostings :: ReportSpec -> Journal -> PriceOracle -> [Posting]
-- which should be all postings before that data, and possibly also from account declarations.
startingBalances :: ReportSpec -> Journal -> PriceOracle -> [Posting]
-> HashMap AccountName Account -> HashMap AccountName Account
startingBalances rspec j priceoracle ps = startingBalancesFromPostings rspec j priceoracle ps =
M.findWithDefault nullacct emptydatespan M.findWithDefault nullacct emptydatespan
<$> calculateReportMatrix rspec j priceoracle mempty [(emptydatespan, ps)] <$> calculateReportMatrix rspec j priceoracle mempty [(emptydatespan, ps)]
@ -263,27 +261,24 @@ getPostings rspec@ReportSpec{_rsQuery=query, _rsReportOpts=ropts} j priceoracle
-- handles the hledger-ui+future txns case above). -- handles the hledger-ui+future txns case above).
depthless = dbg3 "depthless" $ filterQuery (not . queryIsDepth) query depthless = dbg3 "depthless" $ filterQuery (not . queryIsDepth) query
-- | From set of postings, eg for a single report column, calculate the balance change in each account. -- | Given a set of postings, eg for a single report column, gather
-- Accounts and amounts will be depth-clipped appropriately if a depth limit is in effect. -- the accounts that have postings and calculate the change amount for
-- -- each. Accounts and amounts will be depth-clipped appropriately if
-- When --declared is used, accounts which have been declared with an account directive are included, -- a depth limit is in effect.
-- with a 0 balance change. These are really only needed when calculating starting balances, but acctChangesFromPostings :: ReportSpec -> [Posting] -> HashMap ClippedAccountName Account
-- it's harmless to have them in the column changes as well. acctChangesFromPostings ReportSpec{_rsQuery=query,_rsReportOpts=ropts} ps =
acctChanges :: ReportSpec -> Journal -> [Posting] -> HashMap ClippedAccountName Account
acctChanges ReportSpec{_rsQuery=query,_rsReportOpts=ropts} j ps =
HM.fromList [(aname a, a) | a <- as] HM.fromList [(aname a, a) | a <- as]
where where
as = filterAccounts $ as = filterAccounts . drop 1 $ accountsFromPostings ps
drop 1 (accountsFromPostings ps)
++ if declared_ ropts then [nullacct{aname} | aname <- journalAccountNamesDeclared j] else []
filterAccounts = case accountlistmode_ ropts of filterAccounts = case accountlistmode_ ropts of
ALTree -> filter ((depthq `matchesAccount`) . aname) -- exclude deeper balances ALTree -> filter ((depthq `matchesAccount`) . aname) -- exclude deeper balances
ALFlat -> clipAccountsAndAggregate (queryDepth depthq) -- aggregate deeper balances at the depth limit ALFlat -> clipAccountsAndAggregate (queryDepth depthq) . -- aggregate deeper balances at the depth limit.
-- . filter ((0<) . anumpostings) -- exclude unposted accounts filter ((0<) . anumpostings)
depthq = dbg3 "depthq" $ filterQuery queryIsDepth query depthq = dbg3 "depthq" $ filterQuery queryIsDepth query
-- | Gather the account balance changes into a regular matrix, then -- | Gather the account balance changes into a regular matrix, then
-- accumulate and value amounts, as specified by the report options. -- accumulate and value amounts, as specified by the report options.
--
-- Makes sure all report columns have an entry. -- Makes sure all report columns have an entry.
calculateReportMatrix :: ReportSpec -> Journal -> PriceOracle calculateReportMatrix :: ReportSpec -> Journal -> PriceOracle
-> HashMap ClippedAccountName Account -> HashMap ClippedAccountName Account
@ -313,12 +308,11 @@ calculateReportMatrix rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle startb
startingBalance = HM.lookupDefault nullacct name startbals startingBalance = HM.lookupDefault nullacct name startbals
valuedStart = avalue (DateSpan Nothing historicalDate) startingBalance valuedStart = avalue (DateSpan Nothing historicalDate) startingBalance
-- In each column, get each account's balance changes -- Transpose to get each account's balance changes across all columns, then
colacctchanges = dbg5 "colacctchanges" $ map (second $ acctChanges rspec j) colps :: [(DateSpan, HashMap ClippedAccountName Account)] -- pad with zeros
-- Transpose it to get each account's balance changes across all columns allchanges = ((<>zeros) <$> acctchanges) <> (zeros <$ startbals)
acctchanges = dbg5 "acctchanges" $ transposeMap colacctchanges :: HashMap AccountName (Map DateSpan Account) acctchanges = dbg5 "acctchanges" $ transposeMap colacctchanges
-- Fill out the matrix with zeros in empty cells colacctchanges = dbg5 "colacctchanges" $ map (second $ acctChangesFromPostings rspec) colps
allchanges = ((<>zeros) <$> acctchanges) <> (zeros <$ startbals)
avalue = acctApplyBoth . mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle avalue = acctApplyBoth . mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle
acctApplyBoth f a = a{aibalance = f $ aibalance a, aebalance = f $ aebalance a} acctApplyBoth f a = a{aibalance = f $ aibalance a, aebalance = f $ aebalance a}

View File

@ -148,13 +148,12 @@ data ReportOpts = ReportOpts {
-- (Not a regexp, nor a full hledger query, for now.) -- (Not a regexp, nor a full hledger query, for now.)
,accountlistmode_ :: AccountListMode ,accountlistmode_ :: AccountListMode
,drop_ :: Int ,drop_ :: Int
,declared_ :: Bool -- ^ Include accounts declared but not yet posted to ?
,row_total_ :: Bool ,row_total_ :: Bool
,no_total_ :: Bool ,no_total_ :: Bool
,show_costs_ :: Bool -- ^ Show costs for reports which normally don't show them ? ,show_costs_ :: Bool -- ^ Whether to show costs for reports which normally don't show them
,sort_amount_ :: Bool ,sort_amount_ :: Bool
,percent_ :: Bool ,percent_ :: Bool
,invert_ :: Bool -- ^ Flip all amount signs in reports ? ,invert_ :: Bool -- ^ if true, flip all amount signs in reports
,normalbalance_ :: Maybe NormalSign ,normalbalance_ :: Maybe NormalSign
-- ^ This can be set when running balance reports on a set of accounts -- ^ This can be set when running balance reports on a set of accounts
-- with the same normal balance type (eg all assets, or all incomes). -- with the same normal balance type (eg all assets, or all incomes).
@ -198,7 +197,6 @@ defreportopts = ReportOpts
, budgetpat_ = Nothing , budgetpat_ = Nothing
, accountlistmode_ = ALFlat , accountlistmode_ = ALFlat
, drop_ = 0 , drop_ = 0
, declared_ = False
, row_total_ = False , row_total_ = False
, no_total_ = False , no_total_ = False
, show_costs_ = False , show_costs_ = False
@ -252,7 +250,6 @@ rawOptsToReportOpts d rawopts =
,budgetpat_ = maybebudgetpatternopt rawopts ,budgetpat_ = maybebudgetpatternopt rawopts
,accountlistmode_ = accountlistmodeopt rawopts ,accountlistmode_ = accountlistmodeopt rawopts
,drop_ = posintopt "drop" rawopts ,drop_ = posintopt "drop" rawopts
,declared_ = boolopt "declared" 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 ,show_costs_ = boolopt "show-costs" rawopts

View File

@ -308,7 +308,6 @@ balancemode = hledgerCommandMode
] ]
++ flattreeflags True ++ ++ flattreeflags True ++
[flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "omit N leading account name parts (in flat mode)" [flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "omit N leading account name parts (in flat mode)"
,flagNone ["declared"] (setboolopt "declared") "include accounts which have been declared but not yet used"
,flagNone ["average","A"] (setboolopt "average") "show a row average column (in multicolumn reports)" ,flagNone ["average","A"] (setboolopt "average") "show a row average column (in multicolumn reports)"
,flagNone ["related","r"] (setboolopt "related") "show postings' siblings instead" ,flagNone ["related","r"] (setboolopt "related") "show postings' siblings instead"
,flagNone ["row-total","T"] (setboolopt "row-total") "show a row total column (in multicolumn reports)" ,flagNone ["row-total","T"] (setboolopt "row-total") "show a row total column (in multicolumn reports)"

View File

@ -267,12 +267,6 @@ Here are some ways to handle that:
[csv-mode]: https://elpa.gnu.org/packages/csv-mode.html [csv-mode]: https://elpa.gnu.org/packages/csv-mode.html
[visidata]: https://www.visidata.org [visidata]: https://www.visidata.org
### Showing declared accounts
With `--declared`, accounts which have been declared with an [account directive](#declaring-accounts),
even if they have no transactions yet, will be included in the balance report with a zero balance,
and will be visible with `-E/--empty`.
### Commodity layout ### Commodity layout
With `--layout`, you can control how amounts with more than one commodity are displayed: With `--layout`, you can control how amounts with more than one commodity are displayed:

View File

@ -168,10 +168,3 @@ hledger -f - balance -N --output-format=csv --tree
"Assets:Cash","$-1" "Assets:Cash","$-1"
>>>= 0 >>>= 0
# 9. --declared includes all declared accounts, with a zero balance if they have no postings.
hledger -f - balance -N --declared -E
<<<
account a
>>>
0 a
>>>= 0