2018-02-15 22:38:34 +03:00
|
|
|
{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
|
2008-10-03 06:04:15 +04:00
|
|
|
{-|
|
|
|
|
|
2009-04-04 00:55:49 +04:00
|
|
|
|
2012-10-21 21:18:18 +04:00
|
|
|
An 'Account' has a name, a list of subaccounts, an optional parent
|
|
|
|
account, and subaccounting-excluding and -including balances.
|
2008-10-03 06:04:15 +04:00
|
|
|
|
|
|
|
-}
|
|
|
|
|
2010-05-20 03:08:53 +04:00
|
|
|
module Hledger.Data.Account
|
2007-02-15 05:08:18 +03:00
|
|
|
where
|
2020-07-09 03:30:10 +03:00
|
|
|
import Data.List (find, sortOn)
|
2017-11-28 04:22:44 +03:00
|
|
|
import Data.List.Extra (groupSort, groupOn)
|
2020-07-09 03:30:10 +03:00
|
|
|
import Data.Maybe (fromMaybe)
|
|
|
|
import Data.Ord (Down(..))
|
2012-10-21 21:18:18 +04:00
|
|
|
import qualified Data.Map as M
|
|
|
|
import Safe (headMay, lookupJustDef)
|
2011-05-28 08:11:44 +04:00
|
|
|
import Text.Printf
|
|
|
|
|
2012-10-21 21:18:18 +04:00
|
|
|
import Hledger.Data.AccountName
|
2010-05-20 03:08:53 +04:00
|
|
|
import Hledger.Data.Amount
|
2020-07-09 03:30:10 +03:00
|
|
|
import Hledger.Data.Posting ()
|
2011-05-28 08:11:44 +04:00
|
|
|
import Hledger.Data.Types
|
2012-10-21 21:18:18 +04:00
|
|
|
import Hledger.Utils
|
2007-02-15 05:08:18 +03:00
|
|
|
|
|
|
|
|
2012-10-21 21:18:18 +04:00
|
|
|
-- deriving instance Show Account
|
2007-03-11 01:29:09 +03:00
|
|
|
instance Show Account where
|
2014-04-04 04:44:47 +04:00
|
|
|
show Account{..} = printf "Account %s (boring:%s, postings:%d, ebalance:%s, ibalance:%s)"
|
lib: replace pretty-show with pretty-simple
pretty-simple, already used in .ghci, will hopefully give nicer debug
output, including for values which don't have Read-able Show output.
This should mean that we can start removing custom string-like Show
instances that were a workaround for pretty-show.
We are using the latest version (4.0.0.0) to get compact output.
Here's some old pretty-show output:
CsvRules
{ rdirectives = [ ( "skip" , "1" ) ]
, rcsvfieldindexes = [ ( "date" , 1 ) , ( "amount" , 2 ) ]
, rassignments = [ ( "amount" , "%2" ) , ( "date" , "%1" ) ]
, rconditionalblocks = []
}
And the new pretty-simple output:
CsvRules
{ rdirectives=
[ ( "skip", "1" ) ]
, rcsvfieldindexes=
[ ( "date", 1 ), ( "amount", 2 ) ]
, rassignments=
[ ( "amount", "%2" ), ( "date", "%1" ) ]
, rconditionalblocks= []
}
Non-compact pretty-simple output would be:
CsvRules
{ rdirectives=
[
( "skip"
, "1B"
)
]
, rcsvfieldindexes=
[
( "date"
, 1
)
,
( "amount"
, 2
)
]
, rassignments=
[
( "amount"
, "%2"
)
,
( "date"
, "%1"
)
]
, rconditionalblocks=[]
}
Also:
- Account's Show instance no longer converts : to _ in account names
- drop unused pretty-show dependency from hledger, hledger-ui packages
- regenerate hledger-lib with the older hpack that's shipped in stack
2020-11-10 18:08:29 +03:00
|
|
|
aname
|
2012-11-14 21:25:02 +04:00
|
|
|
(if aboring then "y" else "n" :: String)
|
2014-04-04 04:44:47 +04:00
|
|
|
anumpostings
|
2012-10-21 21:18:18 +04:00
|
|
|
(showMixedAmount aebalance)
|
|
|
|
(showMixedAmount aibalance)
|
2007-03-11 01:29:09 +03:00
|
|
|
|
2008-10-18 04:52:49 +04:00
|
|
|
instance Eq Account where
|
2012-10-21 21:18:18 +04:00
|
|
|
(==) a b = aname a == aname b -- quick equality test for speed
|
|
|
|
-- and
|
|
|
|
-- [ aname a == aname b
|
|
|
|
-- -- , aparent a == aparent b -- avoid infinite recursion
|
|
|
|
-- , asubs a == asubs b
|
|
|
|
-- , aebalance a == aebalance b
|
|
|
|
-- , aibalance a == aibalance b
|
|
|
|
-- ]
|
|
|
|
|
|
|
|
nullacct = Account
|
2019-01-14 14:44:51 +03:00
|
|
|
{ aname = ""
|
|
|
|
, adeclarationinfo = Nothing
|
|
|
|
, asubs = []
|
|
|
|
, aparent = Nothing
|
|
|
|
, aboring = False
|
|
|
|
, anumpostings = 0
|
|
|
|
, aebalance = nullmixedamt
|
|
|
|
, aibalance = nullmixedamt
|
2012-10-21 21:18:18 +04:00
|
|
|
}
|
|
|
|
|
2016-08-09 01:56:50 +03:00
|
|
|
-- | Derive 1. an account tree and 2. each account's total exclusive
|
|
|
|
-- and inclusive changes from a list of postings.
|
|
|
|
-- This is the core of the balance command (and of *ledger).
|
|
|
|
-- The accounts are returned as a list in flattened tree order,
|
|
|
|
-- and also reference each other as a tree.
|
|
|
|
-- (The first account is the root of the tree.)
|
2012-10-21 21:18:18 +04:00
|
|
|
accountsFromPostings :: [Posting] -> [Account]
|
|
|
|
accountsFromPostings ps =
|
|
|
|
let
|
2017-11-28 04:22:44 +03:00
|
|
|
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
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
acctstree = accountTree "root" $ map fst summed
|
|
|
|
acctswithnumps = mapAccounts setnumps acctstree where setnumps a = a{anumpostings=fromMaybe 0 $ lookup (aname a) counted}
|
2014-03-26 22:14:20 +04:00
|
|
|
acctswithebals = mapAccounts setebalance acctswithnumps where setebalance a = a{aebalance=lookupJustDef nullmixedamt (aname a) summed}
|
2012-10-21 21:18:18 +04:00
|
|
|
acctswithibals = sumAccounts acctswithebals
|
|
|
|
acctswithparents = tieAccountParents acctswithibals
|
|
|
|
acctsflattened = flattenAccounts acctswithparents
|
|
|
|
in
|
|
|
|
acctsflattened
|
|
|
|
|
2019-07-15 13:28:52 +03:00
|
|
|
-- | Convert a list of account names to a tree of Account objects,
|
|
|
|
-- with just the account names filled in.
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
-- 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
|
2019-01-14 14:44:51 +03:00
|
|
|
accountTree' a (T m) =
|
|
|
|
nullacct{
|
|
|
|
aname=a
|
|
|
|
,asubs=map (uncurry accountTree') $ M.assocs m
|
|
|
|
}
|
2012-10-21 21:18:18 +04:00
|
|
|
|
|
|
|
-- | Tie the knot so all subaccounts' parents are set correctly.
|
|
|
|
tieAccountParents :: Account -> Account
|
|
|
|
tieAccountParents = tie Nothing
|
|
|
|
where
|
|
|
|
tie parent a@Account{..} = a'
|
|
|
|
where
|
|
|
|
a' = a{aparent=parent, asubs=map (tie (Just a')) asubs}
|
|
|
|
|
|
|
|
-- | Get this account's parent accounts, from the nearest up to the root.
|
|
|
|
parentAccounts :: Account -> [Account]
|
|
|
|
parentAccounts Account{aparent=Nothing} = []
|
|
|
|
parentAccounts Account{aparent=Just a} = a:parentAccounts a
|
|
|
|
|
|
|
|
-- | List the accounts at each level of the account tree.
|
|
|
|
accountsLevels :: Account -> [[Account]]
|
|
|
|
accountsLevels = takeWhile (not . null) . iterate (concatMap asubs) . (:[])
|
|
|
|
|
|
|
|
-- | Map a (non-tree-structure-modifying) function over this and sub accounts.
|
|
|
|
mapAccounts :: (Account -> Account) -> Account -> Account
|
|
|
|
mapAccounts f a = f a{asubs = map (mapAccounts f) $ asubs a}
|
|
|
|
|
|
|
|
-- | Is the predicate true on any of this account or its subaccounts ?
|
|
|
|
anyAccounts :: (Account -> Bool) -> Account -> Bool
|
|
|
|
anyAccounts p a
|
|
|
|
| p a = True
|
|
|
|
| otherwise = any (anyAccounts p) $ asubs a
|
|
|
|
|
|
|
|
-- | Add subaccount-inclusive balances to an account tree.
|
|
|
|
sumAccounts :: Account -> Account
|
|
|
|
sumAccounts a
|
|
|
|
| null $ asubs a = a{aibalance=aebalance a}
|
|
|
|
| otherwise = a{aibalance=ibal, asubs=subs}
|
|
|
|
where
|
|
|
|
subs = map sumAccounts $ asubs a
|
|
|
|
ibal = sum $ aebalance a : map aibalance subs
|
|
|
|
|
|
|
|
-- | Remove all subaccounts below a certain depth.
|
|
|
|
clipAccounts :: Int -> Account -> Account
|
2014-09-11 00:07:53 +04:00
|
|
|
clipAccounts 0 a = a{asubs=[]}
|
2012-10-21 21:18:18 +04:00
|
|
|
clipAccounts d a = a{asubs=subs}
|
|
|
|
where
|
|
|
|
subs = map (clipAccounts (d-1)) $ asubs a
|
|
|
|
|
2014-03-26 06:27:18 +04:00
|
|
|
-- | Remove subaccounts below the specified depth, aggregating their balance at the depth limit
|
|
|
|
-- (accounts at the depth limit will have any sub-balances merged into their exclusive balance).
|
2020-07-17 09:00:47 +03:00
|
|
|
-- If the depth is Nothing, return the original accounts
|
|
|
|
clipAccountsAndAggregate :: Maybe Int -> [Account] -> [Account]
|
|
|
|
clipAccountsAndAggregate Nothing as = as
|
|
|
|
clipAccountsAndAggregate (Just d) as = combined
|
2014-03-26 06:27:18 +04:00
|
|
|
where
|
2020-07-17 09:00:47 +03:00
|
|
|
clipped = [a{aname=clipOrEllipsifyAccountName (Just d) $ aname a} | a <- as]
|
|
|
|
combined = [a{aebalance=sum $ map aebalance same}
|
2017-11-28 04:22:44 +03:00
|
|
|
| same@(a:_) <- groupOn aname clipped]
|
2014-03-26 06:27:18 +04:00
|
|
|
{-
|
|
|
|
test cases, assuming d=1:
|
|
|
|
|
|
|
|
assets:cash 1 1
|
|
|
|
assets:checking 1 1
|
|
|
|
->
|
|
|
|
as: [assets:cash 1 1, assets:checking 1 1]
|
|
|
|
clipped: [assets 1 1, assets 1 1]
|
|
|
|
combined: [assets 2 2]
|
|
|
|
|
|
|
|
assets 0 2
|
|
|
|
assets:cash 1 1
|
|
|
|
assets:checking 1 1
|
|
|
|
->
|
|
|
|
as: [assets 0 2, assets:cash 1 1, assets:checking 1 1]
|
|
|
|
clipped: [assets 0 2, assets 1 1, assets 1 1]
|
|
|
|
combined: [assets 2 2]
|
|
|
|
|
|
|
|
assets 0 2
|
|
|
|
assets:bank 1 2
|
|
|
|
assets:bank:checking 1 1
|
|
|
|
->
|
|
|
|
as: [assets 0 2, assets:bank 1 2, assets:bank:checking 1 1]
|
|
|
|
clipped: [assets 0 2, assets 1 2, assets 1 1]
|
|
|
|
combined: [assets 2 2]
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2012-10-21 21:18:18 +04:00
|
|
|
-- | Remove all leaf accounts and subtrees matching a predicate.
|
|
|
|
pruneAccounts :: (Account -> Bool) -> Account -> Maybe Account
|
|
|
|
pruneAccounts p = headMay . prune
|
|
|
|
where
|
|
|
|
prune a
|
2014-04-04 05:04:28 +04:00
|
|
|
| null prunedsubs = if p a then [] else [a']
|
|
|
|
| otherwise = [a']
|
2012-10-21 21:18:18 +04:00
|
|
|
where
|
|
|
|
prunedsubs = concatMap prune $ asubs a
|
2014-04-04 05:04:28 +04:00
|
|
|
a' = a{asubs=prunedsubs}
|
2012-10-21 21:18:18 +04:00
|
|
|
|
|
|
|
-- | Flatten an account tree into a list, which is sometimes
|
|
|
|
-- convenient. Note since accounts link to their parents/subs, the
|
2015-09-03 02:20:41 +03:00
|
|
|
-- tree's structure remains intact and can still be used. It's a tree/list!
|
2012-10-21 21:18:18 +04:00
|
|
|
flattenAccounts :: Account -> [Account]
|
|
|
|
flattenAccounts a = squish a []
|
2015-09-03 02:20:41 +03:00
|
|
|
where squish a as = a : Prelude.foldr squish as (asubs a)
|
2012-10-21 21:18:18 +04:00
|
|
|
|
|
|
|
-- | Filter an account tree (to a list).
|
|
|
|
filterAccounts :: (Account -> Bool) -> Account -> [Account]
|
|
|
|
filterAccounts p a
|
|
|
|
| p a = a : concatMap (filterAccounts p) (asubs a)
|
|
|
|
| otherwise = concatMap (filterAccounts p) (asubs a)
|
|
|
|
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
-- | Sort each group of siblings in an account tree by inclusive amount,
|
2019-07-15 13:28:52 +03:00
|
|
|
-- so that the accounts with largest normal balances are listed first.
|
2017-09-30 05:19:07 +03:00
|
|
|
-- The provided normal balance sign determines whether normal balances
|
2018-01-21 06:42:05 +03:00
|
|
|
-- are negative or positive, affecting the sort order. Ie,
|
|
|
|
-- if balances are normally negative, then the most negative balances
|
|
|
|
-- sort first, and vice versa.
|
2018-01-16 00:05:20 +03:00
|
|
|
sortAccountTreeByAmount :: NormalSign -> Account -> Account
|
2020-07-09 03:30:10 +03:00
|
|
|
sortAccountTreeByAmount normalsign = mapAccounts $ \a -> a{asubs=sortSubs $ asubs a}
|
2017-09-30 05:19:07 +03:00
|
|
|
where
|
2020-07-09 03:30:10 +03:00
|
|
|
sortSubs = case normalsign of
|
2020-12-14 09:41:19 +03:00
|
|
|
NormallyPositive -> sortOn (\a -> (Down $ amt a, aname a))
|
|
|
|
NormallyNegative -> sortOn (\a -> (amt a, aname a))
|
|
|
|
amt = normaliseMixedAmountSquashPricesForDisplay . aibalance
|
2017-09-28 22:49:03 +03:00
|
|
|
|
2019-01-14 14:44:51 +03:00
|
|
|
-- | Add extra info for this account derived from the Journal's
|
|
|
|
-- account directives, if any (comment, tags, declaration order..).
|
|
|
|
accountSetDeclarationInfo :: Journal -> Account -> Account
|
2019-01-14 15:43:13 +03:00
|
|
|
accountSetDeclarationInfo j a@Account{..} =
|
|
|
|
a{ adeclarationinfo=lookup aname $ jdeclaredaccounts j }
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
|
|
|
|
-- | 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
|
2019-07-15 13:28:52 +03:00
|
|
|
-- alphabetically.
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
-- This is hledger's default sort for reports organised by account.
|
|
|
|
-- The account list is converted to a tree temporarily, adding any
|
2019-07-15 13:28:52 +03:00
|
|
|
-- missing parents; these can be kept (suitable for a tree-mode report)
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
-- 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)
|
2019-01-14 14:44:51 +03:00
|
|
|
mapAccounts (accountSetDeclarationInfo j) $ -- add declaration order info
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
accountTree "root" -- convert to an account tree
|
|
|
|
as
|
|
|
|
|
|
|
|
-- | Sort each group of siblings in an account tree by declaration order, then account name.
|
2019-07-15 13:28:52 +03:00
|
|
|
-- 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.
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
sortAccountTreeByDeclaration :: Account -> Account
|
|
|
|
sortAccountTreeByDeclaration a
|
2018-01-21 06:42:05 +03:00
|
|
|
| null $ asubs a = a
|
|
|
|
| otherwise = a{asubs=
|
2019-07-15 13:28:52 +03:00
|
|
|
sortOn accountDeclarationOrderAndName $
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
map sortAccountTreeByDeclaration $ asubs a
|
|
|
|
}
|
2018-01-21 06:42:05 +03:00
|
|
|
|
2019-01-14 14:44:51 +03:00
|
|
|
accountDeclarationOrderAndName :: Account -> (Int, AccountName)
|
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.
2018-09-23 10:45:07 +03:00
|
|
|
accountDeclarationOrderAndName a = (adeclarationorder', aname a)
|
2018-01-21 06:42:05 +03:00
|
|
|
where
|
2019-01-14 14:44:51 +03:00
|
|
|
adeclarationorder' = maybe maxBound adideclarationorder $ adeclarationinfo a
|
2018-01-21 06:42:05 +03:00
|
|
|
|
2012-10-21 21:18:18 +04:00
|
|
|
-- | Search an account list by name.
|
|
|
|
lookupAccount :: AccountName -> [Account] -> Maybe Account
|
|
|
|
lookupAccount a = find ((==a).aname)
|
|
|
|
|
|
|
|
-- debug helpers
|
|
|
|
|
|
|
|
printAccounts :: Account -> IO ()
|
|
|
|
printAccounts = putStrLn . showAccounts
|
|
|
|
|
|
|
|
showAccounts = unlines . map showAccountDebug . flattenAccounts
|
|
|
|
|
|
|
|
showAccountsBoringFlag = unlines . map (show . aboring) . flattenAccounts
|
|
|
|
|
|
|
|
showAccountDebug a = printf "%-25s %4s %4s %s"
|
|
|
|
(aname a)
|
|
|
|
(showMixedAmount $ aebalance a)
|
|
|
|
(showMixedAmount $ aibalance a)
|
2012-11-14 21:25:02 +04:00
|
|
|
(if aboring a then "b" else " " :: String)
|