bal: --sort-amount sorts tree-mode multi-column balance reports
This commit is contained in:
parent
d527384261
commit
b5602fd771
@ -184,11 +184,19 @@ filterAccounts p a
|
|||||||
| p a = a : concatMap (filterAccounts p) (asubs a)
|
| p a = a : concatMap (filterAccounts p) (asubs a)
|
||||||
| otherwise = concatMap (filterAccounts p) (asubs a)
|
| otherwise = concatMap (filterAccounts p) (asubs a)
|
||||||
|
|
||||||
-- | Sort an account tree by inclusive amount.
|
-- | Sort each level of an account tree by inclusive amount,
|
||||||
sortAccountTreeByAmount :: Account -> Account
|
-- so that the accounts with largest normal balances are listed first.
|
||||||
sortAccountTreeByAmount a
|
-- The provided normal balance sign determines whether normal balances
|
||||||
|
-- are negative or positive.
|
||||||
|
sortAccountTreeByAmount :: NormalBalance -> Account -> Account
|
||||||
|
sortAccountTreeByAmount normalsign a
|
||||||
| null $ asubs a = a
|
| null $ asubs a = a
|
||||||
| otherwise = a{asubs=sortBy (flip $ comparing aibalance) $ map sortAccountTreeByAmount $ asubs a}
|
| otherwise = a{asubs=
|
||||||
|
sortBy (maybeflip $ comparing aibalance) $
|
||||||
|
map (sortAccountTreeByAmount normalsign) $ asubs a}
|
||||||
|
where
|
||||||
|
maybeflip | normalsign==NormalNegative = id
|
||||||
|
| otherwise = flip
|
||||||
|
|
||||||
-- | Search an account list by name.
|
-- | Search an account list by name.
|
||||||
lookupAccount :: AccountName -> [Account] -> Maybe Account
|
lookupAccount :: AccountName -> [Account] -> Maybe Account
|
||||||
|
|||||||
@ -356,6 +356,15 @@ data Account = Account {
|
|||||||
aboring :: Bool -- ^ used in the accounts report to label elidable parents
|
aboring :: Bool -- ^ used in the accounts report to label elidable parents
|
||||||
} deriving (Typeable, Data, Generic)
|
} deriving (Typeable, Data, Generic)
|
||||||
|
|
||||||
|
-- | Whether an account's balance is normally a positive number (in accounting terms,
|
||||||
|
-- normally a debit balance), as for asset and expense accounts, or a negative number
|
||||||
|
-- (in accounting terms, normally a credit balance), as for liability, equity and
|
||||||
|
-- income accounts. Cf https://en.wikipedia.org/wiki/Normal_balance .
|
||||||
|
data NormalBalance =
|
||||||
|
NormalPositive -- ^ normally debit - assets, expenses...
|
||||||
|
| NormalNegative -- ^ normally credit - liabilities, equity, income...
|
||||||
|
deriving (Show, Data, Eq)
|
||||||
|
|
||||||
-- | A Ledger has the journal it derives from, and the accounts
|
-- | A Ledger has the journal it derives from, and the accounts
|
||||||
-- derived from that. Accounts are accessible both list-wise and
|
-- derived from that. Accounts are accessible both list-wise and
|
||||||
-- tree-wise, since each one knows its parent and subs; the first
|
-- tree-wise, since each one knows its parent and subs; the first
|
||||||
|
|||||||
@ -113,7 +113,7 @@ balanceReport opts q j = (items, total)
|
|||||||
| otherwise = id
|
| otherwise = id
|
||||||
where
|
where
|
||||||
maybeflip = if normalbalance_ opts == Just NormalNegative then id else flip
|
maybeflip = if normalbalance_ opts == Just NormalNegative then id else flip
|
||||||
maybesorttree | sort_amount_ opts = sortAccountTreeByAmount
|
maybesorttree | sort_amount_ opts = sortAccountTreeByAmount (fromMaybe NormalPositive $ normalbalance_ opts)
|
||||||
| otherwise = id
|
| otherwise = id
|
||||||
items = dbg1 "items" $ map (balanceReportItem opts q) accts'
|
items = dbg1 "items" $ map (balanceReportItem opts q) accts'
|
||||||
total | not (flat_ opts) = dbg1 "total" $ sum [amt | (_,_,indent,amt) <- items, indent == 0]
|
total | not (flat_ opts) = dbg1 "total" $ sum [amt | (_,_,indent,amt) <- items, indent == 0]
|
||||||
|
|||||||
@ -91,7 +91,7 @@ singleBalanceReport opts q j = (rows', total)
|
|||||||
-- showing the change of balance, accumulated balance, or historical balance
|
-- showing the change of balance, accumulated balance, or historical balance
|
||||||
-- in each of the specified periods.
|
-- in each of the specified periods.
|
||||||
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
||||||
multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow)
|
multiBalanceReport opts q j = MultiBalanceReport (displayspans, sorteditems, totalsrow)
|
||||||
where
|
where
|
||||||
symq = dbg1 "symq" $ filterQuery queryIsSym $ dbg1 "requested q" q
|
symq = dbg1 "symq" $ filterQuery queryIsSym $ dbg1 "requested q" q
|
||||||
depthq = dbg1 "depthq" $ filterQuery queryIsDepth q
|
depthq = dbg1 "depthq" $ filterQuery queryIsDepth q
|
||||||
@ -170,9 +170,6 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow
|
|||||||
|
|
||||||
items :: [MultiBalanceReportRow] =
|
items :: [MultiBalanceReportRow] =
|
||||||
dbg1 "items" $
|
dbg1 "items" $
|
||||||
(if sort_amount_ opts && accountlistmode_ opts /= ALTree
|
|
||||||
then sortBy (maybeflip $ comparing sortfield)
|
|
||||||
else id) $
|
|
||||||
[(a, accountLeafName a, accountNameLevel a, displayedBals, rowtot, rowavg)
|
[(a, accountLeafName a, accountNameLevel a, displayedBals, rowtot, rowavg)
|
||||||
| (a,changes) <- acctBalChanges
|
| (a,changes) <- acctBalChanges
|
||||||
, let displayedBals = case balancetype_ opts of
|
, let displayedBals = case balancetype_ opts of
|
||||||
@ -183,19 +180,49 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow
|
|||||||
, let rowavg = averageMixedAmounts displayedBals
|
, let rowavg = averageMixedAmounts displayedBals
|
||||||
, empty_ opts || depth == 0 || any (not . isZeroMixedAmount) displayedBals
|
, empty_ opts || depth == 0 || any (not . isZeroMixedAmount) displayedBals
|
||||||
]
|
]
|
||||||
|
|
||||||
|
sorteditems :: [MultiBalanceReportRow] =
|
||||||
|
dbg1 "sorteditems" $
|
||||||
|
maybesort items
|
||||||
|
where
|
||||||
|
maybesort
|
||||||
|
| not $ sort_amount_ opts = id
|
||||||
|
| accountlistmode_ opts == ALTree = sortTreeMultiBalanceReportRowsByAmount
|
||||||
|
| otherwise = sortFlatMultiBalanceReportRowsByAmount
|
||||||
|
where
|
||||||
|
-- Sort the report rows, representing a flat account list, by row total.
|
||||||
|
sortFlatMultiBalanceReportRowsByAmount = sortBy (maybeflip $ comparing fifth6)
|
||||||
where
|
where
|
||||||
-- reverse the sort if doing a balance report on normally-negative accounts,
|
|
||||||
-- so eg a large negative income balance appears at top in income statement
|
|
||||||
maybeflip = if normalbalance_ opts == Just NormalNegative then id else flip
|
maybeflip = if normalbalance_ opts == Just NormalNegative then id else flip
|
||||||
-- sort by average when that is displayed, instead of total.
|
|
||||||
-- Usually equivalent, but perhaps not in future (eg with --percent)
|
-- Sort the report rows, representing a tree of accounts, by row total at each level.
|
||||||
sortfield = if average_ opts then sixth6 else fifth6
|
-- 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 NormalPositive $ normalbalance_ opts) accounttreewithbals
|
||||||
|
sortedaccounts = drop 1 $ flattenAccounts sortedaccounttree
|
||||||
|
sortedrows = [
|
||||||
|
-- this error should not happen, but it's ugly TODO
|
||||||
|
fromMaybe (error "sortTreeMultiBalanceReportRowsByAmount 2") $ lookup (aname a) anamesandrows
|
||||||
|
| a <- sortedaccounts
|
||||||
|
]
|
||||||
|
|
||||||
totals :: [MixedAmount] =
|
totals :: [MixedAmount] =
|
||||||
-- dbg1 "totals" $
|
-- dbg1 "totals" $
|
||||||
map sum balsbycol
|
map sum balsbycol
|
||||||
where
|
where
|
||||||
balsbycol = transpose [bs | (a,_,_,bs,_,_) <- items, not (tree_ opts) || a `elem` highestlevelaccts]
|
balsbycol = transpose [bs | (a,_,_,bs,_,_) <- sorteditems, not (tree_ opts) || a `elem` highestlevelaccts]
|
||||||
highestlevelaccts =
|
highestlevelaccts =
|
||||||
dbg1 "highestlevelaccts"
|
dbg1 "highestlevelaccts"
|
||||||
[a | a <- displayedAccts, not $ any (`elem` displayedAccts) $ init $ expandAccountName a]
|
[a | a <- displayedAccts, not $ any (`elem` displayedAccts) $ init $ expandAccountName a]
|
||||||
|
|||||||
@ -7,7 +7,6 @@ Options common to most hledger reports.
|
|||||||
|
|
||||||
module Hledger.Reports.ReportOptions (
|
module Hledger.Reports.ReportOptions (
|
||||||
ReportOpts(..),
|
ReportOpts(..),
|
||||||
NormalBalance(..),
|
|
||||||
BalanceType(..),
|
BalanceType(..),
|
||||||
AccountListMode(..),
|
AccountListMode(..),
|
||||||
FormatStr,
|
FormatStr,
|
||||||
@ -136,15 +135,6 @@ defreportopts = ReportOpts
|
|||||||
def
|
def
|
||||||
def
|
def
|
||||||
|
|
||||||
-- | Whether an account's balance is normally a positive number (in accounting terms,
|
|
||||||
-- normally a debit balance), as for asset and expense accounts, or a negative number
|
|
||||||
-- (in accounting terms, normally a credit balance), as for liability, equity and
|
|
||||||
-- income accounts. Cf https://en.wikipedia.org/wiki/Normal_balance .
|
|
||||||
data NormalBalance =
|
|
||||||
NormalPositive -- ^ normally debit - assets, expenses...
|
|
||||||
| NormalNegative -- ^ normally credit - liabilities, equity, income...
|
|
||||||
deriving (Show, Data, Eq)
|
|
||||||
|
|
||||||
rawOptsToReportOpts :: RawOpts -> IO ReportOpts
|
rawOptsToReportOpts :: RawOpts -> IO ReportOpts
|
||||||
rawOptsToReportOpts rawopts = checkReportOpts <$> do
|
rawOptsToReportOpts rawopts = checkReportOpts <$> do
|
||||||
let rawopts' = checkRawOpts rawopts
|
let rawopts' = checkRawOpts rawopts
|
||||||
|
|||||||
@ -282,7 +282,7 @@ balancemode = (defCommandMode $ ["balance"] ++ aliases) { -- also accept but don
|
|||||||
,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "don't squash boring parent accounts (in tree mode)"
|
,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "don't squash boring parent accounts (in tree mode)"
|
||||||
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
|
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
|
||||||
,flagNone ["pretty-tables"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables"
|
,flagNone ["pretty-tables"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables"
|
||||||
,flagNone ["sort-amount","S"] (\opts -> setboolopt "sort-amount" opts) "sort by amount/total/average (in flat mode)"
|
,flagNone ["sort-amount","S"] (\opts -> setboolopt "sort-amount" opts) "sort by amount instead of account name"
|
||||||
]
|
]
|
||||||
++ outputflags
|
++ outputflags
|
||||||
,groupHidden = []
|
,groupHidden = []
|
||||||
|
|||||||
@ -68,7 +68,7 @@ compoundBalanceCommandMode CompoundBalanceCommandSpec{..} = (defCommandMode $ cb
|
|||||||
,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "don't squash boring parent accounts (in tree mode)"
|
,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "don't squash boring parent accounts (in tree mode)"
|
||||||
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
|
,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)"
|
||||||
,flagNone ["pretty-tables"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables"
|
,flagNone ["pretty-tables"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables"
|
||||||
,flagNone ["sort-amount","S"] (\opts -> setboolopt "sort-amount" opts) "sort by amount/total/average (in flat mode)"
|
,flagNone ["sort-amount","S"] (\opts -> setboolopt "sort-amount" opts) "sort by amount instead of account name"
|
||||||
,outputFormatFlag
|
,outputFormatFlag
|
||||||
,outputFileFlag
|
,outputFileFlag
|
||||||
]
|
]
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user