feat: bal: with --declared, include declared leaf accounts (#1765)
Together with -E, this shows a balance for both used and declared accounts (excluding empty parent accounts, which are usually not wanted in list-mode reports). This is somewhat consistent with --declared in the accounts and payees commands, except for the leaf account restriction. The idea of this is to be able to see a useful "complete" balance report, even when you don't have transactions in all of your declared accounts yet. I mainly want this for hledger-ui, but there's no harm in exposing it in the balance CLI as well.
This commit is contained in:
parent
5af1ac29c5
commit
6319d6148f
@ -92,7 +92,7 @@ module Hledger.Data.Journal (
|
|||||||
samplejournal,
|
samplejournal,
|
||||||
samplejournalMaybeExplicit,
|
samplejournalMaybeExplicit,
|
||||||
tests_Journal
|
tests_Journal
|
||||||
)
|
,journalLeafAccountNamesDeclared)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
import Control.Applicative ((<|>))
|
||||||
@ -313,6 +313,11 @@ journalAccountNamesImplied = expandAccountNames . journalAccountNamesUsed
|
|||||||
journalAccountNamesDeclared :: Journal -> [AccountName]
|
journalAccountNamesDeclared :: Journal -> [AccountName]
|
||||||
journalAccountNamesDeclared = nubSort . map fst . jdeclaredaccounts
|
journalAccountNamesDeclared = nubSort . map fst . jdeclaredaccounts
|
||||||
|
|
||||||
|
-- | Sorted unique account names declared by account directives in this journal,
|
||||||
|
-- which have no children.
|
||||||
|
journalLeafAccountNamesDeclared :: Journal -> [AccountName]
|
||||||
|
journalLeafAccountNamesDeclared = treeLeaves . accountNameTreeFrom . journalAccountNamesDeclared
|
||||||
|
|
||||||
-- | Sorted unique account names declared by account directives or posted to
|
-- | Sorted unique account names declared by account directives or posted to
|
||||||
-- by transactions in this journal.
|
-- by transactions in this journal.
|
||||||
journalAccountNamesDeclaredOrUsed :: Journal -> [AccountName]
|
journalAccountNamesDeclaredOrUsed :: Journal -> [AccountName]
|
||||||
|
|||||||
@ -1,5 +1,6 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-|
|
{-|
|
||||||
@ -26,7 +27,6 @@ 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" . startingBalancesFromPostings rspec j priceoracle
|
startbals = dbg5 "startbals" $
|
||||||
$ startingPostings rspec j priceoracle reportspan
|
startingBalances rspec j priceoracle $ 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' = startingBalancesFromPostings rspec j priceoracle $ filter (matchesPosting q) startps
|
startbals' = startingBalances rspec j priceoracle $ filter (matchesPosting q) startps
|
||||||
ropts = cbcsubreportoptions $ _rsReportOpts rspec
|
ropts = cbcsubreportoptions $ _rsReportOpts rspec
|
||||||
q = cbcsubreportquery j
|
q = cbcsubreportquery j
|
||||||
|
|
||||||
@ -183,10 +183,12 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr
|
|||||||
|
|
||||||
cbr = CompoundPeriodicReport "" (map fst colps) subreports overalltotals
|
cbr = CompoundPeriodicReport "" (map fst colps) subreports overalltotals
|
||||||
|
|
||||||
-- | Calculate starting balances from postings, if needed for -H.
|
-- XXX seems refactorable
|
||||||
startingBalancesFromPostings :: ReportSpec -> Journal -> PriceOracle -> [Posting]
|
-- | Calculate accounts' balances on the report start date, from these postings
|
||||||
|
-- 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
|
||||||
startingBalancesFromPostings rspec j priceoracle ps =
|
startingBalances 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)]
|
||||||
|
|
||||||
@ -261,24 +263,38 @@ 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
|
||||||
|
|
||||||
-- | Given a set of postings, eg for a single report column, gather
|
-- | From set of postings, eg for a single report column, calculate the balance change in each account.
|
||||||
-- the accounts that have postings and calculate the change amount for
|
-- Accounts and amounts will be depth-clipped appropriately if a depth limit is in effect.
|
||||||
-- each. Accounts and amounts will be depth-clipped appropriately if
|
--
|
||||||
-- a depth limit is in effect.
|
-- When --declared is used, accounts which have been declared with an account directive
|
||||||
acctChangesFromPostings :: ReportSpec -> [Posting] -> HashMap ClippedAccountName Account
|
-- are also included, with a 0 balance change. But only leaf accounts, since non-leaf
|
||||||
acctChangesFromPostings ReportSpec{_rsQuery=query,_rsReportOpts=ropts} ps =
|
-- empty declared accounts are less useful in reports. This is primarily for hledger-ui.
|
||||||
HM.fromList [(aname a, a) | a <- as]
|
acctChanges :: ReportSpec -> Journal -> [Posting] -> HashMap ClippedAccountName Account
|
||||||
|
acctChanges ReportSpec{_rsQuery=query,_rsReportOpts=ReportOpts{accountlistmode_, declared_}} j ps =
|
||||||
|
HM.fromList [(aname a, a) | a <- accts]
|
||||||
where
|
where
|
||||||
as = filterAccounts . drop 1 $ accountsFromPostings ps
|
-- With --declared, add the query-matching declared accounts
|
||||||
filterAccounts = case accountlistmode_ ropts of
|
-- (as dummy postings so they are processed like the rest).
|
||||||
ALTree -> filter ((depthq `matchesAccount`) . aname) -- exclude deeper balances
|
-- This function is used for calculating both pre-start changes and column changes,
|
||||||
ALFlat -> clipAccountsAndAggregate (queryDepth depthq) . -- aggregate deeper balances at the depth limit.
|
-- and the declared accounts are really only needed for the former,
|
||||||
filter ((0<) . anumpostings)
|
-- but it's harmless to have them in the column changes as well.
|
||||||
depthq = dbg3 "depthq" $ filterQuery queryIsDepth query
|
ps' = ps ++ if declared_ then declaredacctps else []
|
||||||
|
where
|
||||||
|
declaredacctps =
|
||||||
|
[nullposting{paccount=n} | n <- journalLeafAccountNamesDeclared j
|
||||||
|
, acctq `matchesAccount` n]
|
||||||
|
where acctq = dbg3 "acctq" $ filterQuery queryIsAcct query
|
||||||
|
|
||||||
|
filterbydepth = case accountlistmode_ of
|
||||||
|
ALTree -> filter ((depthq `matchesAccount`) . aname) -- a tree - just exclude deeper accounts
|
||||||
|
ALFlat -> clipAccountsAndAggregate (queryDepth depthq) -- a list - aggregate deeper accounts at the depth limit
|
||||||
|
. filter ((0<) . anumpostings) -- and exclude empty parent accounts
|
||||||
|
where depthq = dbg3 "depthq" $ filterQuery queryIsDepth query
|
||||||
|
|
||||||
|
accts = filterbydepth $ drop 1 $ accountsFromPostings ps'
|
||||||
|
|
||||||
-- | 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
|
||||||
@ -308,11 +324,12 @@ 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
|
||||||
|
|
||||||
-- Transpose to get each account's balance changes across all columns, then
|
-- In each column, get each account's balance changes
|
||||||
-- pad with zeros
|
colacctchanges = dbg5 "colacctchanges" $ map (second $ acctChanges rspec j) colps :: [(DateSpan, HashMap ClippedAccountName Account)]
|
||||||
|
-- Transpose it to get each account's balance changes across all columns
|
||||||
|
acctchanges = dbg5 "acctchanges" $ transposeMap colacctchanges :: HashMap AccountName (Map DateSpan Account)
|
||||||
|
-- Fill out the matrix with zeros in empty cells
|
||||||
allchanges = ((<>zeros) <$> acctchanges) <> (zeros <$ startbals)
|
allchanges = ((<>zeros) <$> acctchanges) <> (zeros <$ startbals)
|
||||||
acctchanges = dbg5 "acctchanges" $ transposeMap colacctchanges
|
|
||||||
colacctchanges = dbg5 "colacctchanges" $ map (second $ acctChangesFromPostings rspec) colps
|
|
||||||
|
|
||||||
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}
|
||||||
|
|||||||
@ -148,12 +148,13 @@ 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 -- ^ Whether to show costs for reports which normally don't show them
|
,show_costs_ :: Bool -- ^ Show costs for reports which normally don't show them ?
|
||||||
,sort_amount_ :: Bool
|
,sort_amount_ :: Bool
|
||||||
,percent_ :: Bool
|
,percent_ :: Bool
|
||||||
,invert_ :: Bool -- ^ if true, flip all amount signs in reports
|
,invert_ :: Bool -- ^ 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).
|
||||||
@ -197,6 +198,7 @@ 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
|
||||||
@ -250,6 +252,7 @@ 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
|
||||||
|
|||||||
@ -59,6 +59,7 @@ import Hledger.Utils.Regex
|
|||||||
import Hledger.Utils.String
|
import Hledger.Utils.String
|
||||||
import Hledger.Utils.Text
|
import Hledger.Utils.Text
|
||||||
import Hledger.Utils.Test
|
import Hledger.Utils.Test
|
||||||
|
import Data.Tree (foldTree, Tree)
|
||||||
|
|
||||||
|
|
||||||
-- tuples
|
-- tuples
|
||||||
@ -117,6 +118,11 @@ splitAtElement x l =
|
|||||||
split es = let (first,rest) = break (x==) es
|
split es = let (first,rest) = break (x==) es
|
||||||
in first : splitAtElement x rest
|
in first : splitAtElement x rest
|
||||||
|
|
||||||
|
-- trees
|
||||||
|
|
||||||
|
treeLeaves :: Tree a -> [a]
|
||||||
|
treeLeaves = foldTree (\a bs -> (if null bs then (a:) else id) $ concat bs)
|
||||||
|
|
||||||
-- text
|
-- text
|
||||||
|
|
||||||
-- time
|
-- time
|
||||||
|
|||||||
@ -308,6 +308,7 @@ 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)"
|
||||||
|
|||||||
@ -267,6 +267,19 @@ 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)
|
||||||
|
will be included in the balance report, even if they have no transactions.
|
||||||
|
(Since they will have a zero balance, you will also need `-E/--empty` to see them.)
|
||||||
|
|
||||||
|
More precisely, *leaf* declared accounts (with no subaccounts) will be included,
|
||||||
|
since those are usually the more useful in reports.
|
||||||
|
|
||||||
|
The idea of this is to be able to see a useful "complete" balance report,
|
||||||
|
even when you don't have transactions in all of your declared accounts yet.
|
||||||
|
|
||||||
### 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:
|
||||||
|
|||||||
@ -168,3 +168,32 @@ hledger -f - balance -N --output-format=csv --tree
|
|||||||
"Assets:Cash","$-1"
|
"Assets:Cash","$-1"
|
||||||
>>>= 0
|
>>>= 0
|
||||||
|
|
||||||
|
# 9. --declared includes all declared leaf accounts, even if they have no postings.
|
||||||
|
# They are filtered, depth-clipped, and form trees like the others.
|
||||||
|
hledger -f - balance -NE --declared --tree --depth 2 a
|
||||||
|
<<<
|
||||||
|
account a
|
||||||
|
account a:aa
|
||||||
|
account a:ab
|
||||||
|
account a:ac:aca
|
||||||
|
account b
|
||||||
|
>>>
|
||||||
|
0 a
|
||||||
|
0 aa
|
||||||
|
0 ab
|
||||||
|
>>>= 0
|
||||||
|
|
||||||
|
# 10. In list mode we can see that non-leaf declared accounts are excluded.
|
||||||
|
hledger -f - balance -NE --declared --flat
|
||||||
|
<<<
|
||||||
|
account a
|
||||||
|
account a:aa
|
||||||
|
account a:ab
|
||||||
|
account a:ac:aca
|
||||||
|
account b
|
||||||
|
>>>
|
||||||
|
0 a:aa
|
||||||
|
0 a:ab
|
||||||
|
0 a:ac:aca
|
||||||
|
0 b
|
||||||
|
>>>= 0
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user