mirror of
https://github.com/simonmichael/hledger.git
synced 2024-11-08 07:09:28 +03:00
journal: a new account sorting mechanism, and a bunch of sorting fixes
A bunch of account sorting changes that got intermingled. First, account codes have been dropped. They can still be parsed and will be ignored, for now. I don't know if anyone used them. Instead, account display order is now controlled by the order of account directives, if any. From the mail list: I'd like to drop account codes, introduced in hledger 1.9 to control the display order of accounts. In my experience, - they are tedious to maintain - they duplicate/compete with the natural tendency to arrange account directives to match your mental chart of accounts - they duplicate/compete with the tree structure created by account names and it gets worse if you think about using them more extensively, eg to classify accounts by type. Instead, I plan to just let the position (parse order) of account directives determine the display order of those declared accounts. Undeclared accounts will be displayed after declared accounts, sorted alphabetically as usual. Second, the various account sorting modes have been implemented more widely and more correctly. All sorting modes (alphabetically, by account declaration, by amount) should now work correctly in almost all commands and modes (non-tabular and tabular balance reports, tree and flat modes, the accounts command). Sorting bugs have been fixed, eg #875. Only the budget report (balance --budget) does not yet support sorting. Comprehensive functional tests for sorting in the accounts and balance commands have been added. If you are confused by some sorting behaviour, studying these tests is recommended, as sorting gets tricky.
This commit is contained in:
parent
598129ad6a
commit
3de8c11de1
@ -46,7 +46,7 @@ instance Eq Account where
|
||||
|
||||
nullacct = Account
|
||||
{ aname = ""
|
||||
, acode = Nothing
|
||||
, adeclarationorder = Nothing
|
||||
, aparent = Nothing
|
||||
, asubs = []
|
||||
, anumpostings = 0
|
||||
@ -67,9 +67,8 @@ accountsFromPostings ps =
|
||||
grouped = groupSort [(paccount p,pamount p) | p <- ps]
|
||||
counted = [(aname, length amts) | (aname, amts) <- grouped]
|
||||
summed = [(aname, sumStrict amts) | (aname, amts) <- grouped] -- always non-empty
|
||||
nametree = treeFromPaths $ map (expandAccountName . fst) summed
|
||||
acctswithnames = nameTreeToAccount "root" nametree
|
||||
acctswithnumps = mapAccounts setnumps acctswithnames where setnumps a = a{anumpostings=fromMaybe 0 $ lookup (aname a) counted}
|
||||
acctstree = accountTree "root" $ map fst summed
|
||||
acctswithnumps = mapAccounts setnumps acctstree where setnumps a = a{anumpostings=fromMaybe 0 $ lookup (aname a) counted}
|
||||
acctswithebals = mapAccounts setebalance acctswithnumps where setebalance a = a{aebalance=lookupJustDef nullmixedamt (aname a) summed}
|
||||
acctswithibals = sumAccounts acctswithebals
|
||||
acctswithparents = tieAccountParents acctswithibals
|
||||
@ -77,10 +76,14 @@ accountsFromPostings ps =
|
||||
in
|
||||
acctsflattened
|
||||
|
||||
-- | Convert an AccountName tree to an Account tree
|
||||
nameTreeToAccount :: AccountName -> FastTree AccountName -> Account
|
||||
nameTreeToAccount rootname (T m) =
|
||||
nullacct{ aname=rootname, asubs=map (uncurry nameTreeToAccount) $ M.assocs m }
|
||||
-- | Convert a list of account names to a tree of Account objects,
|
||||
-- with just the account names filled in.
|
||||
-- A single root account with the given name is added.
|
||||
accountTree :: AccountName -> [AccountName] -> Account
|
||||
accountTree rootname as = nullacct{aname=rootname, asubs=map (uncurry accountTree') $ M.assocs m }
|
||||
where
|
||||
T m = treeFromPaths $ map expandAccountName as :: FastTree AccountName
|
||||
accountTree' a (T m) = nullacct{aname=a, asubs=map (uncurry accountTree') $ M.assocs m}
|
||||
|
||||
-- | Tie the knot so all subaccounts' parents are set correctly.
|
||||
tieAccountParents :: Account -> Account
|
||||
@ -90,10 +93,6 @@ tieAccountParents = tie Nothing
|
||||
where
|
||||
a' = a{aparent=parent, asubs=map (tie (Just a')) asubs}
|
||||
|
||||
-- | Look up an account's numeric code, if any, from the Journal and set it.
|
||||
accountSetCodeFrom :: Journal -> Account -> Account
|
||||
accountSetCodeFrom j a = a{acode=fromMaybe Nothing $ lookup (aname a) (jdeclaredaccounts j)}
|
||||
|
||||
-- | Get this account's parent accounts, from the nearest up to the root.
|
||||
parentAccounts :: Account -> [Account]
|
||||
parentAccounts Account{aparent=Nothing} = []
|
||||
@ -189,7 +188,7 @@ filterAccounts p a
|
||||
| p a = a : concatMap (filterAccounts p) (asubs a)
|
||||
| otherwise = concatMap (filterAccounts p) (asubs a)
|
||||
|
||||
-- | Sort each level of an account tree by inclusive amount,
|
||||
-- | Sort each group of siblings in an account tree by inclusive amount,
|
||||
-- so that the accounts with largest normal balances are listed first.
|
||||
-- The provided normal balance sign determines whether normal balances
|
||||
-- are negative or positive, affecting the sort order. Ie,
|
||||
@ -199,24 +198,54 @@ sortAccountTreeByAmount :: NormalSign -> Account -> Account
|
||||
sortAccountTreeByAmount normalsign a
|
||||
| null $ asubs a = a
|
||||
| otherwise = a{asubs=
|
||||
sortBy (maybeflip $ comparing aibalance) $
|
||||
sortBy (maybeflip $ comparing (normaliseMixedAmountSquashPricesForDisplay . aibalance)) $
|
||||
map (sortAccountTreeByAmount normalsign) $ asubs a}
|
||||
where
|
||||
maybeflip | normalsign==NormallyNegative = id
|
||||
| otherwise = flip
|
||||
|
||||
-- | Sort each level of an account tree first by the account code
|
||||
-- if any, with the empty account code sorting last, and then by
|
||||
-- the account name.
|
||||
sortAccountTreeByAccountCodeAndName :: Account -> Account
|
||||
sortAccountTreeByAccountCodeAndName a
|
||||
-- | Look up an account's declaration order, if any, from the Journal and set it.
|
||||
-- This is the relative position of its account directive
|
||||
-- among the other account directives.
|
||||
accountSetDeclarationOrder :: Journal -> Account -> Account
|
||||
accountSetDeclarationOrder j a@Account{..} =
|
||||
a{adeclarationorder = findIndex (==aname) (jdeclaredaccounts j)}
|
||||
|
||||
-- | Sort account names by the order in which they were declared in
|
||||
-- the journal, at each level of the account tree (ie within each
|
||||
-- group of siblings). Undeclared accounts are sorted last and
|
||||
-- alphabetically.
|
||||
-- This is hledger's default sort for reports organised by account.
|
||||
-- The account list is converted to a tree temporarily, adding any
|
||||
-- missing parents; these can be kept (suitable for a tree-mode report)
|
||||
-- or removed (suitable for a flat-mode report).
|
||||
--
|
||||
sortAccountNamesByDeclaration :: Journal -> Bool -> [AccountName] -> [AccountName]
|
||||
sortAccountNamesByDeclaration j keepparents as =
|
||||
(if keepparents then id else filter (`elem` as)) $ -- maybe discard missing parents that were added
|
||||
map aname $ -- keep just the names
|
||||
drop 1 $ -- drop the root node that was added
|
||||
flattenAccounts $ -- convert to an account list
|
||||
sortAccountTreeByDeclaration $ -- sort by declaration order (and name)
|
||||
mapAccounts (accountSetDeclarationOrder j) $ -- add declaration order info
|
||||
accountTree "root" -- convert to an account tree
|
||||
as
|
||||
|
||||
-- | Sort each group of siblings in an account tree by declaration order, then account name.
|
||||
-- So each group will contain first the declared accounts,
|
||||
-- in the same order as their account directives were parsed,
|
||||
-- and then the undeclared accounts, sorted by account name.
|
||||
sortAccountTreeByDeclaration :: Account -> Account
|
||||
sortAccountTreeByDeclaration a
|
||||
| null $ asubs a = a
|
||||
| otherwise = a{asubs=
|
||||
sortBy (comparing accountCodeAndNameForSort) $ map sortAccountTreeByAccountCodeAndName $ asubs a}
|
||||
sortBy (comparing accountDeclarationOrderAndName) $
|
||||
map sortAccountTreeByDeclaration $ asubs a
|
||||
}
|
||||
|
||||
accountCodeAndNameForSort a = (acode', aname a)
|
||||
accountDeclarationOrderAndName a = (adeclarationorder', aname a)
|
||||
where
|
||||
acode' = fromMaybe maxBound (acode a)
|
||||
adeclarationorder' = fromMaybe maxBound (adeclarationorder a)
|
||||
|
||||
-- | Search an account list by name.
|
||||
lookupAccount :: AccountName -> [Account] -> Maybe Account
|
||||
|
@ -256,7 +256,7 @@ journalAccountNamesImplied = expandAccountNames . journalAccountNamesUsed
|
||||
|
||||
-- | Sorted unique account names declared by account directives in this journal.
|
||||
journalAccountNamesDeclared :: Journal -> [AccountName]
|
||||
journalAccountNamesDeclared = nub . sort . map fst . jdeclaredaccounts
|
||||
journalAccountNamesDeclared = nub . sort . jdeclaredaccounts
|
||||
|
||||
-- | Sorted unique account names declared by account directives or posted to
|
||||
-- by transactions in this journal.
|
||||
@ -493,7 +493,8 @@ journalFinalise t path txt assrt j@Journal{jfiles=fs} =
|
||||
journalApplyCommodityStyles $
|
||||
j {jfiles = (path,txt) : reverse fs
|
||||
,jlastreadtime = t
|
||||
,jtxns = reverse $ jtxns j -- NOTE: see addTransaction
|
||||
,jdeclaredaccounts = reverse $ jdeclaredaccounts j
|
||||
,jtxns = reverse $ jtxns j -- NOTE: see addTransaction
|
||||
,jtxnmodifiers = reverse $ jtxnmodifiers j -- NOTE: see addTransactionModifier
|
||||
,jperiodictxns = reverse $ jperiodictxns j -- NOTE: see addPeriodicTransaction
|
||||
,jmarketprices = reverse $ jmarketprices j -- NOTE: see addMarketPrice
|
||||
|
@ -63,7 +63,7 @@ ledgerFromJournal q j = nullledger{ljournal=j'', laccounts=as}
|
||||
(q',depthq) = (filterQuery (not . queryIsDepth) q, filterQuery queryIsDepth q)
|
||||
j' = filterJournalAmounts (filterQuery queryIsSym q) $ -- remove amount parts which the query's sym: terms would exclude
|
||||
filterJournalPostings q' j
|
||||
as = map (accountSetCodeFrom j) $ accountsFromPostings $ journalPostings j'
|
||||
as = accountsFromPostings $ journalPostings j'
|
||||
j'' = filterJournalPostings depthq j'
|
||||
|
||||
-- | List a ledger's account names.
|
||||
|
@ -358,11 +358,11 @@ data Journal = Journal {
|
||||
,jparseparentaccounts :: [AccountName] -- ^ the current stack of parent account names, specified by apply account directives
|
||||
,jparsealiases :: [AccountAlias] -- ^ the current account name aliases in effect, specified by alias directives (& options ?)
|
||||
-- ,jparsetransactioncount :: Integer -- ^ the current count of transactions parsed so far (only journal format txns, currently)
|
||||
,jparsetimeclockentries :: [TimeclockEntry] -- ^ timeclock sessions which have not been clocked out
|
||||
,jparsetimeclockentries :: [TimeclockEntry] -- ^ timeclock sessions which have not been clocked out
|
||||
-- principal data
|
||||
,jdeclaredaccounts :: [(AccountName, Maybe AccountCode)] -- ^ Accounts declared by account directives, in parse order.
|
||||
,jdeclaredaccounts :: [AccountName] -- ^ Accounts declared by account directives, in parse order (after journal finalisation)
|
||||
,jcommodities :: M.Map CommoditySymbol Commodity -- ^ commodities and formats declared by commodity directives
|
||||
,jinferredcommodities :: M.Map CommoditySymbol AmountStyle -- ^ commodities and formats inferred from journal amounts XXX misnamed
|
||||
,jinferredcommodities :: M.Map CommoditySymbol AmountStyle -- ^ commodities and formats inferred from journal amounts TODO misnamed - jusedstyles
|
||||
,jmarketprices :: [MarketPrice]
|
||||
,jtxnmodifiers :: [TransactionModifier]
|
||||
,jperiodictxns :: [PeriodicTransaction]
|
||||
@ -392,7 +392,7 @@ type StorageFormat = String
|
||||
-- which let you walk up or down the account tree.
|
||||
data Account = Account {
|
||||
aname :: AccountName, -- ^ this account's full name
|
||||
acode :: Maybe AccountCode, -- ^ this account's numeric code, if any (not always set)
|
||||
adeclarationorder :: Maybe Int , -- ^ the relative position of this account's account directive, if any. Normally a natural number.
|
||||
aebalance :: MixedAmount, -- ^ this account's balance, excluding subaccounts
|
||||
asubs :: [Account], -- ^ sub-accounts
|
||||
anumpostings :: Int, -- ^ number of postings to this account
|
||||
|
@ -261,8 +261,7 @@ accountdirectivep = do
|
||||
string "account"
|
||||
lift (skipSome spacenonewline)
|
||||
acct <- modifiedaccountnamep -- account directives can be modified by alias/apply account
|
||||
macode' :: Maybe String <- (optional $ lift $ skipSome spacenonewline >> some digitChar)
|
||||
let macode :: Maybe AccountCode = read <$> macode'
|
||||
_ :: Maybe String <- (optional $ lift $ skipSome spacenonewline >> some digitChar) -- compatibility: ignore account codes supported in 1.9/1.10
|
||||
newline
|
||||
skipMany indentedlinep
|
||||
pushDeclaredAccount acct
|
||||
|
@ -18,6 +18,7 @@ module Hledger.Reports.BalanceReport (
|
||||
BalanceReportItem,
|
||||
balanceReport,
|
||||
flatShowsExclusiveBalance,
|
||||
sortAccountItemsLike,
|
||||
|
||||
-- * Tests
|
||||
tests_BalanceReport
|
||||
@ -78,7 +79,7 @@ flatShowsExclusiveBalance = True
|
||||
balanceReport :: ReportOpts -> Query -> Journal -> BalanceReport
|
||||
balanceReport opts q j =
|
||||
(if invert_ opts then brNegate else id) $
|
||||
(items, total)
|
||||
(sorteditems, total)
|
||||
where
|
||||
-- dbg1 = const id -- exclude from debug output
|
||||
dbg1 s = let p = "balanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in debug output
|
||||
@ -89,7 +90,6 @@ balanceReport opts q j =
|
||||
dbg1 "accts" $
|
||||
take 1 $ clipAccountsAndAggregate (queryDepth q) $ flattenAccounts accts
|
||||
| flat_ opts = dbg1 "accts" $
|
||||
sortflat $
|
||||
filterzeros $
|
||||
filterempty $
|
||||
drop 1 $ clipAccountsAndAggregate (queryDepth q) $ flattenAccounts accts
|
||||
@ -98,27 +98,52 @@ balanceReport opts q j =
|
||||
drop 1 $ flattenAccounts $
|
||||
markboring $
|
||||
prunezeros $
|
||||
sorttree $
|
||||
sortAccountTreeByAmount (fromMaybe NormallyPositive $ normalbalance_ opts) $
|
||||
clipAccounts (queryDepth q) accts
|
||||
where
|
||||
balance = if flat_ opts then aebalance else aibalance
|
||||
balance = if flat_ opts then aebalance else aibalance
|
||||
filterzeros = if empty_ opts then id else filter (not . isZeroMixedAmount . balance)
|
||||
filterempty = filter (\a -> anumpostings a > 0 || not (isZeroMixedAmount (balance a)))
|
||||
prunezeros = if empty_ opts then id else fromMaybe nullacct . pruneAccounts (isZeroMixedAmount . balance)
|
||||
markboring = if no_elide_ opts then id else markBoringParentAccounts
|
||||
sortflat | sort_amount_ opts = sortBy (maybeflip $ comparing balance)
|
||||
| otherwise = sortBy (comparing accountCodeAndNameForSort)
|
||||
where
|
||||
maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
|
||||
sorttree | sort_amount_ opts = sortAccountTreeByAmount (fromMaybe NormallyPositive $ normalbalance_ opts)
|
||||
| otherwise = sortAccountTreeByAccountCodeAndName
|
||||
|
||||
items = dbg1 "items" $ map (balanceReportItem opts q) accts'
|
||||
|
||||
-- now sort items like MultiBalanceReport, except
|
||||
-- sorting a tree by amount was more easily done above
|
||||
sorteditems
|
||||
| sort_amount_ opts && tree_ opts = items
|
||||
| sort_amount_ opts = sortFlatBRByAmount items
|
||||
| otherwise = sortBRByAccountDeclaration items
|
||||
|
||||
where
|
||||
-- Sort the report rows, representing a flat account list, by row total.
|
||||
sortFlatBRByAmount :: [BalanceReportItem] -> [BalanceReportItem]
|
||||
sortFlatBRByAmount = sortBy (maybeflip $ comparing (normaliseMixedAmountSquashPricesForDisplay . fourth4))
|
||||
where
|
||||
maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
|
||||
|
||||
-- Sort the report rows by account declaration order then account name.
|
||||
sortBRByAccountDeclaration :: [BalanceReportItem] -> [BalanceReportItem]
|
||||
sortBRByAccountDeclaration rows = sortedrows
|
||||
where
|
||||
anamesandrows = [(first4 r, r) | r <- rows]
|
||||
anames = map fst anamesandrows
|
||||
sortedanames = sortAccountNamesByDeclaration j (tree_ opts) anames
|
||||
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
||||
|
||||
total | not (flat_ opts) = dbg1 "total" $ sum [amt | (_,_,indent,amt) <- items, indent == 0]
|
||||
| otherwise = dbg1 "total" $
|
||||
if flatShowsExclusiveBalance
|
||||
then sum $ map fourth4 items
|
||||
else sum $ map aebalance $ clipAccountsAndAggregate 1 accts'
|
||||
|
||||
-- | A sorting helper: sort a list of things (eg report rows) keyed by account name
|
||||
-- to match the provided ordering of those same account names.
|
||||
sortAccountItemsLike :: [AccountName] -> [(AccountName, b)] -> [b]
|
||||
sortAccountItemsLike sortedas items =
|
||||
concatMap (\a -> maybe [] (:[]) $ lookup a items) sortedas
|
||||
|
||||
-- | In an account tree with zero-balance leaves removed, mark the
|
||||
-- elidable parent accounts (those with one subaccount and no balance
|
||||
-- of their own).
|
||||
|
@ -178,69 +178,46 @@ combineBudgetAndActual
|
||||
acctsdone = map first6 rows1
|
||||
|
||||
-- combine and re-sort rows
|
||||
-- TODO: respect hierarchy in tree mode
|
||||
-- TODO: use MBR code
|
||||
-- TODO: respect --sort-amount
|
||||
-- TODO: add --sort-budget to sort by budget goal amount
|
||||
rows :: [PeriodicReportRow (Maybe Change, Maybe BudgetGoal)] =
|
||||
sortBy (comparing first6) $ rows1 ++ rows2
|
||||
-- massive duplication from multiBalanceReport to handle tree mode sorting ?
|
||||
-- dbg1 "sorteditems" $
|
||||
-- sortitems items
|
||||
|
||||
-- -- like MultiBalanceReport
|
||||
-- sortedrows
|
||||
-- | sort_amount_ opts && tree_ opts = sortTreeBURByAmount items
|
||||
-- | sort_amount_ opts = sortFlatBURByAmount items
|
||||
-- | otherwise = sortBURByAccountDeclaration items
|
||||
--
|
||||
-- where
|
||||
-- sortitems
|
||||
-- | sort_amount_ opts && accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAmount
|
||||
-- | sort_amount_ opts = sortFlatMultiBalanceReportRowsByAmount
|
||||
-- | not (sort_amount_ opts) && accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAccountCodeAndName
|
||||
-- | otherwise = sortFlatMultiBalanceReportRowsByAccountCodeAndName
|
||||
-- -- Sort the report rows, representing a tree of accounts, by row total at each level.
|
||||
-- sortTreeMBRByAmount rows = sortedrows
|
||||
-- where
|
||||
-- -- Sort the report rows, representing a flat account list, by row total.
|
||||
-- sortFlatMultiBalanceReportRowsByAmount = sortBy (maybeflip $ comparing fifth6)
|
||||
-- anamesandrows = [(first6 r, r) | r <- rows]
|
||||
-- anames = map fst anamesandrows
|
||||
-- atotals = [(a,tot) | (a,_,_,_,tot,_) <- rows]
|
||||
-- accounttree = accountTree "root" anames
|
||||
-- accounttreewithbals = mapAccounts setibalance accounttree
|
||||
-- where
|
||||
-- maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
|
||||
-- -- should not happen, but it's ugly; TODO
|
||||
-- setibalance a = a{aibalance=fromMaybe (error "sortTreeBURByAmount 1") $ lookup (aname a) atotals}
|
||||
-- sortedaccounttree = sortAccountTreeByAmount (fromMaybe NormallyPositive $ normalbalance_ opts) accounttreewithbals
|
||||
-- sortedanames = map aname $ drop 1 $ flattenAccounts sortedaccounttree
|
||||
-- sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
||||
--
|
||||
-- -- Sort the report rows, representing a tree of accounts, by row total at each level.
|
||||
-- -- To do this we recreate an Account tree with the row totals as balances,
|
||||
-- -- so we can do a hierarchical sort, flatten again, and then reorder the
|
||||
-- -- report rows similarly. Yes this is pretty long winded.
|
||||
-- sortTreeMultiBalanceReportRowsByAmount rows = sortedrows
|
||||
-- where
|
||||
-- anamesandrows = [(first6 r, r) | r <- rows]
|
||||
-- anames = map fst anamesandrows
|
||||
-- atotals = [(a,tot) | (a,_,_,_,tot,_) <- rows]
|
||||
-- nametree = treeFromPaths $ map expandAccountName anames
|
||||
-- accounttree = nameTreeToAccount "root" nametree
|
||||
-- accounttreewithbals = mapAccounts setibalance accounttree
|
||||
-- where
|
||||
-- -- this error should not happen, but it's ugly TODO
|
||||
-- setibalance a = a{aibalance=fromMaybe (error "sortTreeMultiBalanceReportRowsByAmount 1") $ lookup (aname a) atotals}
|
||||
-- sortedaccounttree = sortAccountTreeByAmount (fromMaybe NormallyPositive $ normalbalance_ opts) accounttreewithbals
|
||||
-- sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
|
||||
-- -- dropped the root account, also ignore any parent accounts not in rows
|
||||
-- sortedrows = concatMap (\a -> maybe [] (:[]) $ lookup (aname a) anamesandrows) sortedaccounts
|
||||
--
|
||||
-- -- Sort the report rows by account code if any, with the empty account code coming last, then account name.
|
||||
-- sortFlatMultiBalanceReportRowsByAccountCodeAndName = sortBy (comparing acodeandname)
|
||||
-- where
|
||||
-- acodeandname r = (acode', aname)
|
||||
-- where
|
||||
-- aname = first6 r
|
||||
-- macode = fromMaybe Nothing $ lookup aname $ jdeclaredaccounts j
|
||||
-- acode' = fromMaybe maxBound macode
|
||||
--
|
||||
-- -- Sort the report rows, representing a tree of accounts, by account code and then account name at each level.
|
||||
-- -- Convert a tree of account names, look up the account codes, sort and flatten the tree, reorder the rows.
|
||||
-- sortTreeMultiBalanceReportRowsByAccountCodeAndName rows = sortedrows
|
||||
-- where
|
||||
-- anamesandrows = [(first6 r, r) | r <- rows]
|
||||
-- anames = map fst anamesandrows
|
||||
-- nametree = treeFromPaths $ map expandAccountName anames
|
||||
-- accounttree = nameTreeToAccount "root" nametree
|
||||
-- accounttreewithcodes = mapAccounts (accountSetCodeFrom j) accounttree
|
||||
-- sortedaccounttree = sortAccountTreeByAccountCodeAndName accounttreewithcodes
|
||||
-- sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
|
||||
-- -- dropped the root account, also ignore any parent accounts not in rows
|
||||
-- sortedrows = concatMap (\a -> maybe [] (:[]) $ lookup (aname a) anamesandrows) sortedaccounts
|
||||
-- -- Sort the report rows, representing a flat account list, by row total.
|
||||
-- sortFlatBURByAmount = sortBy (maybeflip $ comparing fifth6)
|
||||
-- where
|
||||
-- maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
|
||||
--
|
||||
-- -- Sort the report rows by account declaration order then account name.
|
||||
-- sortBURByAccountDeclaration rows = sortedrows
|
||||
-- where
|
||||
-- anamesandrows = [(first6 r, r) | r <- rows]
|
||||
-- anames = map fst anamesandrows
|
||||
-- sortedanames = sortAccountNamesByDeclaration j (tree_ opts) anames
|
||||
-- sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
||||
|
||||
-- TODO: grand total & average shows 0% when there are no actual amounts, inconsistent with other cells
|
||||
totalrow =
|
||||
|
@ -175,64 +175,45 @@ multiBalanceReport opts q j =
|
||||
, empty_ opts || depth == 0 || any (not . isZeroMixedAmount) displayedBals
|
||||
]
|
||||
|
||||
-- TODO TBD: is it always ok to sort report rows after report has been generated ?
|
||||
-- Or does sorting sometimes need to be done as part of the report generation ?
|
||||
sorteditems :: [MultiBalanceReportRow] =
|
||||
dbg1 "sorteditems" $
|
||||
sortitems items
|
||||
where
|
||||
sortitems
|
||||
| sort_amount_ opts && accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAmount
|
||||
| sort_amount_ opts = sortFlatMultiBalanceReportRowsByAmount
|
||||
| not (sort_amount_ opts) && accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAccountCodeAndName
|
||||
| otherwise = sortFlatMultiBalanceReportRowsByAccountCodeAndName
|
||||
| sort_amount_ opts && accountlistmode_ opts == ALTree = sortTreeMBRByAmount
|
||||
| sort_amount_ opts = sortFlatMBRByAmount
|
||||
| otherwise = sortMBRByAccountDeclaration
|
||||
where
|
||||
-- Sort the report rows, representing a flat account list, by row total.
|
||||
sortFlatMultiBalanceReportRowsByAmount = sortBy (maybeflip $ comparing fifth6)
|
||||
where
|
||||
maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
|
||||
|
||||
-- Sort the report rows, representing a tree of accounts, by row total at each level.
|
||||
-- To do this we recreate an Account tree with the row totals as balances,
|
||||
-- so we can do a hierarchical sort, flatten again, and then reorder the
|
||||
-- report rows similarly. Yes this is pretty long winded.
|
||||
sortTreeMultiBalanceReportRowsByAmount rows = sortedrows
|
||||
-- Similar to sortMBRByAccountDeclaration/sortAccountNamesByDeclaration.
|
||||
sortTreeMBRByAmount rows = sortedrows
|
||||
where
|
||||
anamesandrows = [(first6 r, r) | r <- rows]
|
||||
anames = map fst anamesandrows
|
||||
atotals = [(a,tot) | (a,_,_,_,tot,_) <- rows]
|
||||
nametree = treeFromPaths $ map expandAccountName anames
|
||||
accounttree = nameTreeToAccount "root" nametree
|
||||
accounttree = accountTree "root" anames
|
||||
accounttreewithbals = mapAccounts setibalance accounttree
|
||||
where
|
||||
-- this error should not happen, but it's ugly TODO
|
||||
setibalance a = a{aibalance=fromMaybe (error "sortTreeMultiBalanceReportRowsByAmount 1") $ lookup (aname a) atotals}
|
||||
-- should not happen, but it's dangerous; TODO
|
||||
setibalance a = a{aibalance=fromMaybe (error "sortTreeMBRByAmount 1") $ lookup (aname a) atotals}
|
||||
sortedaccounttree = sortAccountTreeByAmount (fromMaybe NormallyPositive $ normalbalance_ opts) accounttreewithbals
|
||||
sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
|
||||
-- dropped the root account, also ignore any parent accounts not in rows
|
||||
sortedrows = concatMap (\a -> maybe [] (:[]) $ lookup (aname a) anamesandrows) sortedaccounts
|
||||
sortedanames = map aname $ drop 1 $ flattenAccounts sortedaccounttree
|
||||
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
||||
|
||||
-- Sort the report rows by account code if any, with the empty account code coming last, then account name.
|
||||
-- TODO keep children below their parent. Have to convert to tree ?
|
||||
sortFlatMultiBalanceReportRowsByAccountCodeAndName = sortBy (comparing acodeandname)
|
||||
-- Sort the report rows, representing a flat account list, by row total.
|
||||
sortFlatMBRByAmount = sortBy (maybeflip $ comparing (normaliseMixedAmountSquashPricesForDisplay . fifth6))
|
||||
where
|
||||
acodeandname r = (acode', aname)
|
||||
where
|
||||
aname = first6 r
|
||||
macode = fromMaybe Nothing $ lookup aname $ jdeclaredaccounts j
|
||||
acode' = fromMaybe maxBound macode
|
||||
maybeflip = if normalbalance_ opts == Just NormallyNegative then id else flip
|
||||
|
||||
-- Sort the report rows, representing a tree of accounts, by account code and then account name at each level.
|
||||
-- Convert a tree of account names, look up the account codes, sort and flatten the tree, reorder the rows.
|
||||
sortTreeMultiBalanceReportRowsByAccountCodeAndName rows = sortedrows
|
||||
where
|
||||
-- Sort the report rows by account declaration order then account name.
|
||||
sortMBRByAccountDeclaration rows = sortedrows
|
||||
where
|
||||
anamesandrows = [(first6 r, r) | r <- rows]
|
||||
anames = map fst anamesandrows
|
||||
nametree = treeFromPaths $ map expandAccountName anames
|
||||
accounttree = nameTreeToAccount "root" nametree
|
||||
accounttreewithcodes = mapAccounts (accountSetCodeFrom j) accounttree
|
||||
sortedaccounttree = sortAccountTreeByAccountCodeAndName accounttreewithcodes
|
||||
sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
|
||||
-- dropped the root account, also ignore any parent accounts not in rows
|
||||
sortedrows = concatMap (\a -> maybe [] (:[]) $ lookup (aname a) anamesandrows) sortedaccounts
|
||||
sortedanames = sortAccountNamesByDeclaration j (tree_ opts) anames
|
||||
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
||||
|
||||
totals :: [MixedAmount] =
|
||||
-- dbg1 "totals" $
|
||||
|
@ -820,35 +820,9 @@ Currently this mainly helps with account name autocompletion in eg
|
||||
hledger add, hledger-iadd, hledger-web, and ledger-mode.
|
||||
In future it will also help detect misspelled accounts.
|
||||
|
||||
Account names can be followed by a numeric account code:
|
||||
```journal
|
||||
account assets 1000
|
||||
account assets:bank:checking 1110
|
||||
account liabilities 2000
|
||||
account revenues 4000
|
||||
account expenses 6000
|
||||
```
|
||||
This affects how accounts are sorted in account and balance reports:
|
||||
accounts with codes are listed before accounts without codes, and in increasing code order
|
||||
(instead of listing all accounts alphabetically).
|
||||
Warning, this feature is incomplete; account codes do not yet affect sort order in
|
||||
|
||||
- the `accounts` command
|
||||
- the `balance` command's single-column mode
|
||||
- flat mode balance reports
|
||||
(to work around this, declare account codes on the subaccounts as well).
|
||||
- hledger-web's sidebar
|
||||
|
||||
Account codes should be all numeric digits, unique, and separated from the account name by at least two spaces (since account names may contain single spaces).
|
||||
By convention, often the first digit indicates the type of account,
|
||||
as in
|
||||
[this numbering scheme](http://www.dwmbeancounter.com/BCTutorSite/Courses/ChartAccounts/lesson02-6.html)
|
||||
and the example above.
|
||||
In future, we might use this to recognize account types.
|
||||
|
||||
An account directive can also have indented subdirectives following it, which are currently ignored. Here is the full syntax:
|
||||
```journal
|
||||
; account ACCTNAME [OPTIONALCODE]
|
||||
; account ACCTNAME
|
||||
; [OPTIONALSUBDIRECTIVES]
|
||||
|
||||
account assets:bank:checking 1110
|
||||
@ -856,6 +830,54 @@ account assets:bank:checking 1110
|
||||
some-tag:12345
|
||||
```
|
||||
|
||||
### Account display order
|
||||
|
||||
Account directives have another purpose: they set the display order of accounts in reports.
|
||||
For example, say you have these top-level accounts:
|
||||
```shell
|
||||
$ accounts -1
|
||||
assets
|
||||
equity
|
||||
expenses
|
||||
liabilities
|
||||
misc
|
||||
other
|
||||
revenues
|
||||
```
|
||||
|
||||
Ie without account declarations, they are displayed in alphabetical order.
|
||||
But if you add the following account directives to the journal:
|
||||
```journal
|
||||
account assets
|
||||
account liabilities
|
||||
account equity
|
||||
account revenues
|
||||
account expenses
|
||||
```
|
||||
|
||||
the display order changes to:
|
||||
```shell
|
||||
$ accounts -1
|
||||
assets
|
||||
liabilities
|
||||
equity
|
||||
revenues
|
||||
expenses
|
||||
misc
|
||||
other
|
||||
```
|
||||
|
||||
Ie, declared accounts first, in declaration order, followed by undeclared accounts in alphabetic order.
|
||||
|
||||
Warning: work in progress.
|
||||
This is supported by
|
||||
the accounts command
|
||||
and by tabular balance reports (`balancesheet`, `balance -Y`, etc).
|
||||
It is not yet supported by
|
||||
non-tabular balance reports,
|
||||
budget reports,
|
||||
or hledger-web's sidebar.
|
||||
|
||||
### Rewriting accounts
|
||||
|
||||
You can define account alias rules which rewrite your account names, or parts of them,
|
||||
|
@ -10,6 +10,7 @@ The @accounts@ command lists account names:
|
||||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE MultiWayIf #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
@ -19,17 +20,15 @@ module Hledger.Cli.Commands.Accounts (
|
||||
,accounts
|
||||
) where
|
||||
|
||||
import Data.List
|
||||
#if !(MIN_VERSION_base(4,11,0))
|
||||
import Data.Monoid
|
||||
#endif
|
||||
-- import Data.Text (Text)
|
||||
import Data.List
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.IO as T
|
||||
import System.Console.CmdArgs.Explicit as C
|
||||
|
||||
import Hledger
|
||||
import Prelude hiding (putStrLn)
|
||||
import Hledger.Utils.UTF8IOCompat (putStrLn)
|
||||
import Hledger.Cli.CliOptions
|
||||
|
||||
|
||||
@ -64,20 +63,39 @@ accountsmode = (defCommandMode $ ["accounts"] ++ aliases) {
|
||||
-- | The accounts command.
|
||||
accounts :: CliOpts -> Journal -> IO ()
|
||||
accounts CliOpts{rawopts_=rawopts, reportopts_=ropts} j = do
|
||||
|
||||
-- 1. identify the accounts we'll show
|
||||
d <- getCurrentDay
|
||||
let q = queryFromOpts d ropts
|
||||
let tree = tree_ ropts
|
||||
declared = boolopt "declared" rawopts
|
||||
used = boolopt "used" rawopts
|
||||
q = queryFromOpts d ropts
|
||||
-- a depth limit will clip and exclude account names later, but should not exclude accounts at this stage
|
||||
nodepthq = dbg1 "nodepthq" $ filterQuery (not . queryIsDepth) q
|
||||
depth = dbg1 "depth" $ queryDepth $ filterQuery queryIsDepth q
|
||||
matcheddeclaredaccts = dbg1 "matcheddeclaredaccts" $ nub $ sort $ filter (matchesAccount q) $ map fst $ jdeclaredaccounts j
|
||||
matchedps = dbg1 "ps" $ journalPostings $ filterJournalPostings nodepthq j
|
||||
matchedusedaccts = dbg1 "matchedusedaccts" $ nub $ sort $ filter (not . T.null) $ map (clipAccountName depth) $ map paccount matchedps
|
||||
used = boolopt "used" rawopts
|
||||
declared = boolopt "declared" rawopts
|
||||
as | declared && not used = matcheddeclaredaccts
|
||||
| not declared && used = matchedusedaccts
|
||||
| otherwise = nub $ sort $ matcheddeclaredaccts ++ matchedusedaccts
|
||||
as' | tree_ ropts = expandAccountNames as
|
||||
| otherwise = as
|
||||
render a | tree_ ropts = T.replicate (2 * (accountNameLevel a - 1)) " " <> accountLeafName a
|
||||
| otherwise = maybeAccountNameDrop ropts a
|
||||
mapM_ (putStrLn . T.unpack . render) as'
|
||||
matcheddeclaredaccts = dbg1 "matcheddeclaredaccts" $ filter (matchesAccount nodepthq) $ jdeclaredaccounts j
|
||||
matchedusedaccts = dbg5 "matchedusedaccts" $ map paccount $ journalPostings $ filterJournalPostings nodepthq j
|
||||
accts = dbg5 "accts to show" $ -- no need to nub/sort, accountTree will
|
||||
if | declared && not used -> matcheddeclaredaccts
|
||||
| not declared && used -> matchedusedaccts
|
||||
| otherwise -> matcheddeclaredaccts ++ matchedusedaccts
|
||||
|
||||
-- 2. sort them by declaration order and name, at each level of their tree structure
|
||||
sortedaccts = sortAccountNamesByDeclaration j tree accts
|
||||
|
||||
-- 3. if there's a depth limit, depth-clip and remove any no longer useful items
|
||||
clippedaccts =
|
||||
dbg1 "clippedaccts" $
|
||||
filter (matchesAccount q) $ -- clipping can leave accounts that no longer visibly match the query
|
||||
nub $ -- clipping can leave duplicates (adjacent, hopefully)
|
||||
filter (not . T.null) $ -- depth:0 can leave nulls
|
||||
map (clipAccountName depth) $ -- clip at depth if specified
|
||||
sortedaccts
|
||||
|
||||
-- 4. print what remains as a list or tree, maybe applying --drop in the former case
|
||||
mapM_ (T.putStrLn . render) clippedaccts
|
||||
where
|
||||
render a
|
||||
| tree_ ropts = T.replicate (2 * (accountNameLevel a - 1)) " " <> accountLeafName a
|
||||
| otherwise = maybeAccountNameDrop ropts a
|
||||
|
||||
|
133
tests/accounts/sorting.test
Normal file
133
tests/accounts/sorting.test
Normal file
@ -0,0 +1,133 @@
|
||||
# accounts report sorting.
|
||||
|
||||
# 1. Accounts are sorted alphabetically, at each tree level.
|
||||
# Flat mode. Unused parent accounts are not added (b).
|
||||
<
|
||||
2018/1/1
|
||||
(b:j) 1
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(a:k) 1
|
||||
|
||||
$ hledger -f- acc
|
||||
a:k
|
||||
b:i
|
||||
b:j
|
||||
c
|
||||
>=
|
||||
|
||||
|
||||
# 2. Tree mode. Missing parent accounts are added (b).
|
||||
$ hledger -f- acc --tree
|
||||
a
|
||||
k
|
||||
b
|
||||
i
|
||||
j
|
||||
c
|
||||
>=
|
||||
|
||||
# 3. With account directives, flat mode.
|
||||
# At each tree level, declared accounts are sorted first, in
|
||||
# declaration order, followed by undeclared accounts sorted alphabetically.
|
||||
# Unused parent accounts are not added (b).
|
||||
# The b:k, b:j declarations affect the subs of b, not b itself.
|
||||
<
|
||||
account b:k
|
||||
account b:j
|
||||
account d
|
||||
|
||||
2018/1/1
|
||||
(a:l) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(b:j) 1
|
||||
|
||||
2018/1/1
|
||||
(b:k) 1
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(d) 1
|
||||
|
||||
$ hledger -f- acc
|
||||
d
|
||||
a:l
|
||||
b:k
|
||||
b:j
|
||||
b:i
|
||||
c
|
||||
>=
|
||||
|
||||
# 4. With account directives, tree mode.
|
||||
# Missing parent accounts are added (b).
|
||||
$ hledger -f- acc --tree
|
||||
d
|
||||
a
|
||||
l
|
||||
b
|
||||
k
|
||||
j
|
||||
i
|
||||
c
|
||||
>=
|
||||
|
||||
# 5. With a depth limit:
|
||||
# deeper accounts are not excluded
|
||||
# account names are clipped
|
||||
# empty clipped names are removed
|
||||
# duplicate clipped names are removed
|
||||
# non-matched clipped names are removed.
|
||||
# Flat mode.
|
||||
$ hledger -f- acc d b l --depth 1
|
||||
d
|
||||
b
|
||||
>=
|
||||
|
||||
# # .
|
||||
# $ hledger -f- acc
|
||||
# >=
|
||||
|
||||
# # .
|
||||
# $ hledger -f- acc
|
||||
# >=
|
||||
|
||||
# # .
|
||||
# $ hledger -f- acc
|
||||
# >=
|
||||
|
||||
# # .
|
||||
# $ hledger -f- acc
|
||||
# >=
|
||||
|
||||
# # .
|
||||
# $ hledger -f- acc
|
||||
# >=
|
||||
|
||||
# # .
|
||||
# $ hledger -f- acc
|
||||
# >=
|
||||
|
||||
# # . With --drop: TODO not supported ?
|
||||
# empty modified names are removed
|
||||
# duplicate modified names are removed
|
||||
# non-matched modified names are removed ?
|
||||
# modified names are sorted somehow ?
|
||||
# $ hledger -f- acc --drop 1
|
||||
# l
|
||||
# k
|
||||
# j
|
||||
# i
|
||||
# >=
|
||||
|
@ -149,21 +149,3 @@ hledger -f - balance -b 2016/10 -e 2016/11
|
||||
>>>2
|
||||
>>>= 0
|
||||
|
||||
# not yet implemented, https://github.com/simonmichael/hledger/issues/727
|
||||
#7. Sorting by account code. Here, balance should display Equity first.
|
||||
# hledger -f- bal -N
|
||||
# <<<
|
||||
# account Equity 1000
|
||||
# account Assets 2000
|
||||
|
||||
# 2018/1/1
|
||||
# (Equity) 1
|
||||
|
||||
# 2018/1/1
|
||||
# (Assets) 1
|
||||
|
||||
# >>>
|
||||
# 1 Equity
|
||||
# 1 Assets
|
||||
# >>>2
|
||||
# >>>=0
|
||||
|
352
tests/balance/sorting.test
Normal file
352
tests/balance/sorting.test
Normal file
@ -0,0 +1,352 @@
|
||||
* balance report sorting.
|
||||
# These tests are based on accounts' and somewhat duplicatory if
|
||||
# sorting code is shared between commands, but might be worth having
|
||||
# all the same.
|
||||
** Tabular balance reports
|
||||
*** Default sort without account declarations
|
||||
|
||||
# 1. Rows are sorted alphabetically by account name, at each tree level.
|
||||
# Flat mode. Unused parent accounts are not added (b).
|
||||
<
|
||||
2018/1/1
|
||||
(b:j) 1
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(a:k) 1
|
||||
|
||||
$ hledger -f- bal -NY
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
=====++======
|
||||
a:k || 1
|
||||
b:i || 1
|
||||
b:j || 1
|
||||
c || 1
|
||||
>=
|
||||
|
||||
# 2. Tree mode. Missing parent accounts are added (b).
|
||||
$ hledger -f- bal -NY --tree
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
=====++======
|
||||
a || 1
|
||||
k || 1
|
||||
b || 2
|
||||
i || 1
|
||||
j || 1
|
||||
c || 1
|
||||
>=
|
||||
|
||||
*** Default sort with account declarations
|
||||
|
||||
# 3. With account directives, flat mode.
|
||||
# At each tree level, declared accounts are sorted first, in
|
||||
# declaration order, followed by undeclared accounts sorted alphabetically.
|
||||
# Unused parent accounts are not added (b).
|
||||
# The b:k, b:j declarations affect the subs of b, not b itself.
|
||||
<
|
||||
account b:k
|
||||
account b:j
|
||||
account d
|
||||
|
||||
2018/1/1
|
||||
(a:l) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(b:j) 1
|
||||
|
||||
2018/1/1
|
||||
(b:k) 1
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(d) 1
|
||||
|
||||
$ hledger -f- bal -NY
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
=====++======
|
||||
d || 1
|
||||
a:l || 1
|
||||
b:k || 1
|
||||
b:j || 1
|
||||
b:i || 1
|
||||
c || 1
|
||||
>=
|
||||
|
||||
# 4. With account directives, tree mode.
|
||||
# Missing parent accounts are added (b).
|
||||
$ hledger -f- bal -NY --tree
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
=====++======
|
||||
d || 1
|
||||
a || 1
|
||||
l || 1
|
||||
b || 3
|
||||
k || 1
|
||||
j || 1
|
||||
i || 1
|
||||
c || 1
|
||||
>=
|
||||
|
||||
# # .
|
||||
# <
|
||||
# $ hledger -f- bal -NY
|
||||
# >=
|
||||
|
||||
# . With --drop, the modified names are sorted. ?
|
||||
# XXX not supported ?
|
||||
# $ hledger -f- bal -NY --drop 2
|
||||
# Balance changes in 2018:
|
||||
#
|
||||
# || 2018
|
||||
# =====++======
|
||||
# c || 1
|
||||
# i || 1
|
||||
# j || 1
|
||||
# k || 1
|
||||
# >=
|
||||
|
||||
*** Sort by amount
|
||||
|
||||
# 5. Rows are sorted by decreasing amount (and then by account), at each tree level.
|
||||
# Tree mode.
|
||||
|
||||
<
|
||||
2018/1/1
|
||||
(b:j) 2
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(a:k) 1
|
||||
|
||||
$ hledger -f- bal -NY --sort-amount --tree
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
=====++======
|
||||
b || 3
|
||||
j || 2
|
||||
i || 1
|
||||
a || 1
|
||||
k || 1
|
||||
c || 1
|
||||
>=
|
||||
|
||||
# 6. Flat mode.
|
||||
$ hledger -f- bal -NY --flat --sort-amount
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
=====++======
|
||||
b:j || 2
|
||||
a:k || 1
|
||||
b:i || 1
|
||||
c || 1
|
||||
>=
|
||||
|
||||
# 7. When the larger amount is composed of differently-priced amounts,
|
||||
# it could get sorted as if smaller (bug in hledger 1.4-1.10). Flat mode.
|
||||
<
|
||||
2018/1/1
|
||||
(a) 2X @ 1Y
|
||||
(a) 2X @ 2Y
|
||||
|
||||
2018/1/1
|
||||
(b) 3X
|
||||
|
||||
$ hledger -f- bal -NY --sort-amount
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
===++======
|
||||
a || 4X
|
||||
b || 3X
|
||||
>=
|
||||
|
||||
# 8. Explicit --flat flag, should be the same as above.
|
||||
$ hledger -f- bal -NY --sort-amount --flat
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
===++======
|
||||
a || 4X
|
||||
b || 3X
|
||||
>=
|
||||
|
||||
# 9. Tree mode.
|
||||
$ hledger -f- bal -NY --sort-amount --tree
|
||||
Balance changes in 2018:
|
||||
|
||||
|| 2018
|
||||
===++======
|
||||
a || 4X
|
||||
b || 3X
|
||||
>=
|
||||
|
||||
** Non-tabular balance reports
|
||||
*** Default sort without account declarations
|
||||
|
||||
# 10. Rows are sorted alphabetically by account name, at each tree level.
|
||||
# Tree mode. Missing parent accounts are added (b).
|
||||
<
|
||||
2018/1/1
|
||||
(b:j) 1
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(a:k) 1
|
||||
|
||||
$ hledger -f- bal -N
|
||||
1 a:k
|
||||
2 b
|
||||
1 i
|
||||
1 j
|
||||
1 c
|
||||
>=
|
||||
|
||||
# 11. Flat mode. Unused parent accounts are not added (b).
|
||||
$ hledger -f- bal -N --flat
|
||||
1 a:k
|
||||
1 b:i
|
||||
1 b:j
|
||||
1 c
|
||||
>=
|
||||
|
||||
*** Default sort with account declarations
|
||||
|
||||
# 12. With account directives, tree mode.
|
||||
# At each tree level, declared accounts are sorted first, in
|
||||
# declaration order, followed by undeclared accounts sorted alphabetically.
|
||||
# Missing parent accounts are added (b).
|
||||
<
|
||||
account b:k
|
||||
account b:j
|
||||
account d
|
||||
|
||||
2018/1/1
|
||||
(a:l) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(b:j) 1
|
||||
|
||||
2018/1/1
|
||||
(b:k) 1
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(d) 1
|
||||
|
||||
$ hledger -f- bal -N
|
||||
1 d
|
||||
1 a:l
|
||||
3 b
|
||||
1 k
|
||||
1 j
|
||||
1 i
|
||||
1 c
|
||||
>=
|
||||
|
||||
# 13. With account directives, flat mode.
|
||||
# Unused parent accounts are not added (b).
|
||||
# The b:k, b:j declarations affect the subs of b, not b itself.
|
||||
$ hledger -f- bal -N --flat
|
||||
1 d
|
||||
1 a:l
|
||||
1 b:k
|
||||
1 b:j
|
||||
1 b:i
|
||||
1 c
|
||||
>=
|
||||
|
||||
*** Sort by amount
|
||||
|
||||
# 14. Rows are sorted by decreasing amount (and then by account), at each tree level.
|
||||
# Tree mode.
|
||||
|
||||
<
|
||||
2018/1/1
|
||||
(b:j) 2
|
||||
|
||||
2018/1/1
|
||||
(c) 1
|
||||
|
||||
2018/1/1
|
||||
(b:i) 1
|
||||
|
||||
2018/1/1
|
||||
(a:k) 1
|
||||
|
||||
$ hledger -f- bal -N --sort-amount --tree
|
||||
3 b
|
||||
2 j
|
||||
1 i
|
||||
1 a:k
|
||||
1 c
|
||||
>=
|
||||
|
||||
# 15. Flat mode.
|
||||
$ hledger -f- bal -N --flat --sort-amount
|
||||
2 b:j
|
||||
1 a:k
|
||||
1 b:i
|
||||
1 c
|
||||
>=
|
||||
|
||||
# 16. When the larger amount is composed of differently-priced amounts,
|
||||
# it could get sorted as if smaller (bug in hledger 1.4-1.10). Tree mode.
|
||||
<
|
||||
2018/1/1
|
||||
(a) 2X @ 1Y
|
||||
(a) 2X @ 2Y
|
||||
|
||||
2018/1/1
|
||||
(b) 3X
|
||||
|
||||
$ hledger -f- bal -N --sort-amount
|
||||
4X a
|
||||
3X b
|
||||
>=
|
||||
|
||||
# 17. Explicit --tree flag, should be the same as above.
|
||||
$ hledger -f- bal -N --sort-amount --tree
|
||||
4X a
|
||||
3X b
|
||||
>=
|
||||
|
||||
# 18. Flat mode.
|
||||
$ hledger -f- bal -N --sort-amount --flat
|
||||
4X a
|
||||
3X b
|
||||
>=
|
Loading…
Reference in New Issue
Block a user