bal/bs/cf/is: support --value-at with -H; fix row/col/grand totals
This also includes a big cleanup of multiBalanceReport, which got accidentally mingled.
This commit is contained in:
parent
9680e894cc
commit
d77fd5743d
@ -82,11 +82,19 @@ type ClippedAccountName = AccountName
|
|||||||
-- in each of the specified periods. Does not support tree-mode boring parent eliding.
|
-- in each of the specified periods. Does not support tree-mode boring parent eliding.
|
||||||
-- If the normalbalance_ option is set, it adjusts the sorting and sign of amounts
|
-- If the normalbalance_ option is set, it adjusts the sorting and sign of amounts
|
||||||
-- (see ReportOpts and CompoundBalanceCommand).
|
-- (see ReportOpts and CompoundBalanceCommand).
|
||||||
|
-- hledger's most powerful and useful report, used by the balance
|
||||||
|
-- command (in multiperiod mode) and by the bs/cf/is commands.
|
||||||
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
||||||
multiBalanceReport ropts@ReportOpts{..} q j =
|
multiBalanceReport ropts@ReportOpts{..} q j =
|
||||||
(if invert_ then mbrNegate else id) $
|
(if invert_ then mbrNegate else id) $
|
||||||
MultiBalanceReport (displayspans, sorteditems, totalsrow)
|
MultiBalanceReport (colspans, sortedrowsvalued, totalsrow)
|
||||||
where
|
where
|
||||||
|
dbg1 s = let p = "multiBalanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in this function's debug output
|
||||||
|
-- dbg1 = const id -- exclude this function from debug output
|
||||||
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
-- 1. Queries, report/column dates.
|
||||||
|
|
||||||
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
|
||||||
depth = queryDepth depthq
|
depth = queryDepth depthq
|
||||||
@ -107,6 +115,7 @@ multiBalanceReport ropts@ReportOpts{..} q j =
|
|||||||
-- This can be the null span if there were no intervals.
|
-- This can be the null span if there were no intervals.
|
||||||
reportspan = dbg1 "reportspan" $ DateSpan (maybe Nothing spanStart $ headMay intervalspans)
|
reportspan = dbg1 "reportspan" $ DateSpan (maybe Nothing spanStart $ headMay intervalspans)
|
||||||
(maybe Nothing spanEnd $ lastMay intervalspans)
|
(maybe Nothing spanEnd $ lastMay intervalspans)
|
||||||
|
mreportstart = spanStart reportspan
|
||||||
-- The user's query with no depth limit, and expanded to the report span
|
-- The user's query with no depth limit, and expanded to the report span
|
||||||
-- if there is one (otherwise any date queries are left as-is, which
|
-- if there is one (otherwise any date queries are left as-is, which
|
||||||
-- handles the hledger-ui+future txns case above).
|
-- handles the hledger-ui+future txns case above).
|
||||||
@ -116,34 +125,19 @@ multiBalanceReport ropts@ReportOpts{..} q j =
|
|||||||
else And [datelessq, reportspandatesq]
|
else And [datelessq, reportspandatesq]
|
||||||
where
|
where
|
||||||
reportspandatesq = dbg1 "reportspandatesq" $ dateqcons reportspan
|
reportspandatesq = dbg1 "reportspandatesq" $ dateqcons reportspan
|
||||||
-- q projected back before the report start date, to calculate starting balances.
|
-- The date spans to be included as report columns.
|
||||||
-- When there's no report start date, in case there are future txns (the hledger-ui case above),
|
colspans :: [DateSpan] = dbg1 "colspans" $ splitSpan interval_ displayspan
|
||||||
-- we use emptydatespan to make sure they aren't counted as starting balance.
|
|
||||||
startbalq = dbg1 "startbalq" $ And [datelessq, dateqcons precedingspan]
|
|
||||||
where
|
|
||||||
precedingspan = case spanStart reportspan of
|
|
||||||
Just d -> DateSpan Nothing (Just d)
|
|
||||||
Nothing -> emptydatespan
|
|
||||||
-- Postings to be considered for this balance report.
|
|
||||||
ps :: [Posting] =
|
|
||||||
dbg1 "ps" $
|
|
||||||
journalPostings $
|
|
||||||
filterJournalAmounts symq $ -- remove amount parts excluded by cur:
|
|
||||||
filterJournalPostings reportq $ -- remove postings not matched by (adjusted) query
|
|
||||||
journalSelectingAmountFromOpts ropts j
|
|
||||||
-- One or more date spans corresponding to the report columns.
|
|
||||||
displayspans :: [DateSpan] = dbg1 "displayspans" $ splitSpan interval_ displayspan
|
|
||||||
where
|
where
|
||||||
displayspan
|
displayspan
|
||||||
| empty_ = dbg1 "displayspan (-E)" reportspan -- all the requested intervals
|
| empty_ = dbg1 "displayspan (-E)" reportspan -- all the requested intervals
|
||||||
| otherwise = dbg1 "displayspan" $ requestedspan `spanIntersect` matchedspan -- exclude leading/trailing empty intervals
|
| otherwise = dbg1 "displayspan" $ requestedspan `spanIntersect` matchedspan -- exclude leading/trailing empty intervals
|
||||||
matchedspan = dbg1 "matchedspan" $ postingsDateSpan' (whichDateFromOpts ropts) ps
|
matchedspan = dbg1 "matchedspan" $ postingsDateSpan' (whichDateFromOpts ropts) ps
|
||||||
-- Group postings into their columns, with the column end dates.
|
|
||||||
psPerSpan :: [([Posting], Maybe Day)] =
|
----------------------------------------------------------------------
|
||||||
dbg1 "psPerSpan"
|
-- 2. Things we'll need for valuation, if -V/--value-at are present.
|
||||||
[(filter (isPostingInDateSpan' (whichDateFromOpts ropts) s) ps, spanEnd s) | s <- displayspans]
|
-- Valuation complicates this report quite a lot.
|
||||||
-- Check if we'll be doing valuation.
|
|
||||||
-- Here's the current plan for each part of the report and each --value-at:
|
-- Here's the current intended effect of --value-at on each part of the report:
|
||||||
-- -H starting balances:
|
-- -H starting balances:
|
||||||
-- transaction: sum of values of previous postings on their posting dates
|
-- transaction: sum of values of previous postings on their posting dates
|
||||||
-- period: value -H starting balances at day before report start
|
-- period: value -H starting balances at day before report start
|
||||||
@ -162,31 +156,101 @@ multiBalanceReport ropts@ReportOpts{..} q j =
|
|||||||
-- date: sum/average the unvalued amounts and value at date
|
-- date: sum/average the unvalued amounts and value at date
|
||||||
mvalueat = if value_ then Just value_at_ else Nothing
|
mvalueat = if value_ then Just value_at_ else Nothing
|
||||||
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
||||||
-- If --value-at=transaction is in effect, convert the postings to value before summing.
|
-- Market prices. Sort into date then parse order,
|
||||||
maybeValuedPsPerSpan :: [([Posting], Maybe Day)] =
|
-- & reverse for quick lookup of the latest price.
|
||||||
case mvalueat of
|
prices = reverse $ sortOn mpdate $ jmarketprices j
|
||||||
Just AtTransaction -> [([postingValueAtDate j (postingDate p) p | p <- ps], periodend) | (ps,periodend) <- psPerSpan]
|
-- A helper for valuing amounts according to --value-at.
|
||||||
_ -> psPerSpan
|
maybevalue :: Day -> MixedAmount -> MixedAmount
|
||||||
-- In each column, calculate the change in each account that has postings.
|
maybevalue periodlastday amt = case mvalueat of
|
||||||
-- And if --value-at is in effect (except --value-at=transaction), convert these change amounts to value.
|
Nothing -> amt
|
||||||
postedAcctBalChangesPerSpan :: [[(ClippedAccountName, MixedAmount)]] =
|
Just AtTransaction -> amt -- assume --value-at=transaction was handled earlier
|
||||||
dbg1 "postedAcctBalChangesPerSpan" $
|
Just AtPeriod -> mixedAmountValue prices periodlastday amt
|
||||||
[postingAcctBals valuedps
|
Just AtNow -> mixedAmountValue prices today amt
|
||||||
| (ps,periodend) <- maybeValuedPsPerSpan
|
Just (AtDate d) -> mixedAmountValue prices d amt
|
||||||
, let periodlastday = maybe
|
-- The last day of each column subperiod.
|
||||||
(error' "multiBalanceReport: expected a subperiod end date") -- XXX shouldn't happen
|
lastdays :: [Day] =
|
||||||
(addDays (-1))
|
map ((maybe
|
||||||
periodend
|
(error' "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen
|
||||||
, let valuedps =
|
(addDays (-1)))
|
||||||
case mvalueat of
|
. spanEnd) colspans
|
||||||
Just AtPeriod -> [postingValueAtDate j periodlastday p | p <- ps]
|
-- The last day of the overall report period.
|
||||||
Just AtNow -> [postingValueAtDate j today p | p <- ps]
|
reportlastday =
|
||||||
Just (AtDate d) -> [postingValueAtDate j d p | p <- ps]
|
fromMaybe (error' "multiBalanceReport: expected a non-empty journal") -- XXX might happen ? :(
|
||||||
_ -> ps
|
$ reportPeriodOrJournalLastDay ropts j
|
||||||
]
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
-- 3. Calculate starting balances (both unvalued and valued), if needed for -H
|
||||||
|
|
||||||
|
-- Balances at report start date, unvalued, from all earlier postings which otherwise match the query.
|
||||||
|
startbals :: [(AccountName, MixedAmount)] = dbg1 "startbals" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
||||||
where
|
where
|
||||||
postingAcctBals :: [Posting] -> [(ClippedAccountName, MixedAmount)]
|
(startbalanceitems,_) = dbg1 "starting balance report" $ balanceReport ropts''{value_=False} startbalq j
|
||||||
postingAcctBals ps = [(aname a, (if tree_ ropts then aibalance else aebalance) a) | a <- as]
|
where
|
||||||
|
ropts' | tree_ ropts = ropts{no_elide_=True}
|
||||||
|
| otherwise = ropts{accountlistmode_=ALFlat}
|
||||||
|
ropts'' = ropts'{period_ = precedingperiod}
|
||||||
|
where
|
||||||
|
precedingperiod = dateSpanAsPeriod $ spanIntersect (DateSpan Nothing mreportstart) $ periodAsDateSpan period_
|
||||||
|
-- q projected back before the report start date.
|
||||||
|
-- When there's no report start date, in case there are future txns (the hledger-ui case above),
|
||||||
|
-- we use emptydatespan to make sure they aren't counted as starting balance.
|
||||||
|
startbalq = dbg1 "startbalq" $ And [datelessq, dateqcons precedingspan]
|
||||||
|
where
|
||||||
|
precedingspan = case mreportstart of
|
||||||
|
Just d -> DateSpan Nothing (Just d)
|
||||||
|
Nothing -> emptydatespan
|
||||||
|
-- Balances at report start date, maybe valued according to --value-at. XXX duplication
|
||||||
|
startbalsmaybevalued :: [(AccountName, MixedAmount)] = dbg1 "startbalsmaybevalued" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
||||||
|
where
|
||||||
|
(startbalanceitems,_) = dbg1 "starting balance report (maybe valued)" $ balanceReport ropts'' startbalq j
|
||||||
|
where
|
||||||
|
ropts' | tree_ ropts = ropts{no_elide_=True}
|
||||||
|
| otherwise = ropts{accountlistmode_=ALFlat}
|
||||||
|
ropts'' = ropts'{period_ = precedingperiod}
|
||||||
|
where
|
||||||
|
precedingperiod = dateSpanAsPeriod $ spanIntersect (DateSpan Nothing mreportstart) $ periodAsDateSpan period_
|
||||||
|
-- q projected back before the report start date.
|
||||||
|
-- When there's no report start date, in case there are future txns (the hledger-ui case above),
|
||||||
|
-- we use emptydatespan to make sure they aren't counted as starting balance.
|
||||||
|
startbalq = dbg1 "startbalq" $ And [datelessq, dateqcons precedingspan]
|
||||||
|
where
|
||||||
|
precedingspan = case mreportstart of
|
||||||
|
Just d -> DateSpan Nothing (Just d)
|
||||||
|
Nothing -> emptydatespan
|
||||||
|
-- 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.
|
||||||
|
startaccts = dbg1 "startaccts" $ map fst startbals
|
||||||
|
-- Helpers to look up an account's starting balance.
|
||||||
|
startingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbals
|
||||||
|
valuedStartingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbalsmaybevalued
|
||||||
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
-- 4. Gather postings for each column.
|
||||||
|
|
||||||
|
-- Postings matching the query within the report period.
|
||||||
|
ps :: [Posting] =
|
||||||
|
dbg1 "ps" $
|
||||||
|
journalPostings $
|
||||||
|
filterJournalAmounts symq $ -- remove amount parts excluded by cur:
|
||||||
|
filterJournalPostings reportq $ -- remove postings not matched by (adjusted) query
|
||||||
|
journalSelectingAmountFromOpts ropts j
|
||||||
|
-- Group postings into their columns, with the column end dates.
|
||||||
|
colps :: [([Posting], Maybe Day)] =
|
||||||
|
dbg1 "colps"
|
||||||
|
[(filter (isPostingInDateSpan' (whichDateFromOpts ropts) s) ps, spanEnd s) | s <- colspans]
|
||||||
|
-- If --value-at=transaction is in effect, convert the postings to value before summing.
|
||||||
|
colpsmaybevalued :: [([Posting], Maybe Day)] =
|
||||||
|
case mvalueat of
|
||||||
|
Just AtTransaction -> [([postingValueAtDate j (postingDate p) p | p <- ps], periodend) | (ps,periodend) <- colps]
|
||||||
|
_ -> colps
|
||||||
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
-- 5. Calculate account balance changes in each column.
|
||||||
|
|
||||||
|
-- In each column, gather the accounts that have postings and their change amount.
|
||||||
|
-- Do this for the unvalued postings, and if needed the posting-date-valued postings.
|
||||||
|
acctChangesFromPostings :: [Posting] -> [(ClippedAccountName, MixedAmount)]
|
||||||
|
acctChangesFromPostings ps = [(aname a, (if tree_ ropts then aibalance else aebalance) a) | a <- as]
|
||||||
where
|
where
|
||||||
as = depthLimit $
|
as = depthLimit $
|
||||||
(if tree_ ropts then id else filter ((>0).anumpostings)) $
|
(if tree_ ropts then id else filter ((>0).anumpostings)) $
|
||||||
@ -194,56 +258,102 @@ multiBalanceReport ropts@ReportOpts{..} q j =
|
|||||||
depthLimit
|
depthLimit
|
||||||
| tree_ ropts = filter ((depthq `matchesAccount`).aname) -- exclude deeper balances
|
| tree_ ropts = filter ((depthq `matchesAccount`).aname) -- exclude deeper balances
|
||||||
| otherwise = clipAccountsAndAggregate depth -- aggregate deeper balances at the depth limit
|
| otherwise = clipAccountsAndAggregate depth -- aggregate deeper balances at the depth limit
|
||||||
-- All accounts referenced across all columns.
|
-- colacctchanges :: [[(ClippedAccountName, MixedAmount)]] =
|
||||||
postedAccts :: [AccountName] = dbg1 "postedAccts" $ sort $ accountNamesFromPostings ps
|
-- dbg1 "colacctchanges" $ map (acctChangesFromPostings . fst) colps
|
||||||
-- Starting account balances, from transactions before the report start date.
|
colacctchangesmaybevalued :: [[(ClippedAccountName, MixedAmount)]] =
|
||||||
startacctbals = dbg1 "startacctbals" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
dbg1 "colacctchangesmaybevalued" $ map (acctChangesFromPostings . fst) colpsmaybevalued
|
||||||
where
|
|
||||||
(startbalanceitems,_) = dbg1 "starting balance report" $ balanceReport ropts' startbalq j
|
----------------------------------------------------------------------
|
||||||
where
|
-- 6. Gather the account balance changes into a regular matrix including the accounts
|
||||||
ropts' | tree_ ropts = ropts{no_elide_=True}
|
-- from all columns (and with -H, accounts with starting balances), adding zeroes where needed.
|
||||||
| otherwise = ropts{accountlistmode_=ALFlat}
|
|
||||||
startingBalanceFor a = fromMaybe nullmixedamt $ lookup a startacctbals
|
|
||||||
startAccts = dbg1 "startAccts" $ map fst startacctbals
|
|
||||||
-- All account names that will be displayed, possibly depth-clipped.
|
-- All account names that will be displayed, possibly depth-clipped.
|
||||||
displayedAccts :: [ClippedAccountName] =
|
displayaccts :: [ClippedAccountName] =
|
||||||
dbg1 "displayedAccts" $
|
dbg1 "displayaccts" $
|
||||||
(if tree_ ropts then expandAccountNames else id) $
|
(if tree_ ropts then expandAccountNames else id) $
|
||||||
nub $ map (clipOrEllipsifyAccountName depth) $
|
nub $ map (clipOrEllipsifyAccountName depth) $
|
||||||
if empty_ || balancetype_ == HistoricalBalance then nub $ sort $ startAccts ++ postedAccts else postedAccts
|
if empty_ || balancetype_ == HistoricalBalance
|
||||||
-- Pad out the per-column account balance changes with zeroes
|
then nub $ sort $ startaccts ++ allpostedaccts
|
||||||
-- so that each column contains a value for all the accounts.
|
else allpostedaccts
|
||||||
acctBalChangesPerSpan :: [[(ClippedAccountName, MixedAmount)]] =
|
where
|
||||||
dbg1 "acctBalChangesPerSpan"
|
allpostedaccts :: [AccountName] = dbg1 "allpostedaccts" $ sort $ accountNamesFromPostings ps
|
||||||
[sortBy (comparing fst) $ unionBy (\(a,_) (a',_) -> a == a') postedacctbals zeroes
|
-- Each column's balance changes for each account, adding zeroes where needed.
|
||||||
| postedacctbals <- postedAcctBalChangesPerSpan]
|
colallacctchanges :: [[(ClippedAccountName, MixedAmount)]] =
|
||||||
where zeroes = [(a, nullmixedamt) | a <- displayedAccts]
|
dbg1 "colallacctchanges"
|
||||||
-- For each account, the balance changes in each column.
|
[sortBy (comparing fst) $
|
||||||
acctBalChanges :: [(ClippedAccountName, [MixedAmount])] =
|
unionBy (\(a,_) (a',_) -> a == a') postedacctchanges zeroes
|
||||||
dbg1 "acctBalChanges"
|
| postedacctchanges <- colacctchangesmaybevalued]
|
||||||
[(a, map snd abs) | abs@((a,_):_) <- transpose acctBalChangesPerSpan] -- never null, or used when null...
|
where zeroes = [(a, nullmixedamt) | a <- displayaccts]
|
||||||
-- The report rows, one per account, with account name info,
|
-- Transpose to get each account's balance changes across all columns.
|
||||||
-- column amounts, row total and row average.
|
acctchanges :: [(ClippedAccountName, [MixedAmount])] =
|
||||||
items :: [MultiBalanceReportRow] =
|
dbg1 "acctchanges"
|
||||||
dbg1 "items" $
|
[(a, map snd abs) | abs@((a,_):_) <- transpose colallacctchanges] -- never null, or used when null...
|
||||||
[(a, accountLeafName a, accountNameLevel a, displayedBals, rowtot, rowavg)
|
|
||||||
| (a,changes) <- acctBalChanges
|
----------------------------------------------------------------------
|
||||||
, let displayedBals = case balancetype_ of
|
-- 7. Build the report rows.
|
||||||
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes -- XXX need to value per period
|
|
||||||
|
-- One row per account, with account name info, column amounts, row total and row average.
|
||||||
|
-- Calculate them two ways: unvalued for calculating column/grand totals, and valued for display.
|
||||||
|
rows :: [MultiBalanceReportRow] =
|
||||||
|
dbg1 "rows" $
|
||||||
|
[(a, accountLeafName a, accountNameLevel a, unvaluedbals, rowtot, rowavg)
|
||||||
|
| (a,changes) <- acctchanges
|
||||||
|
-- The amounts to be displayed (period changes, cumulative totals, or historical balances).
|
||||||
|
, let unvaluedbals = case balancetype_ of
|
||||||
|
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
||||||
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
||||||
_ -> changes
|
_ -> changes
|
||||||
, let rowtot = sum displayedBals
|
-- The total and average for the row.
|
||||||
, let rowavg = averageMixedAmounts displayedBals
|
, let rowtot = sum unvaluedbals
|
||||||
, empty_ || depth == 0 || any (not . isZeroMixedAmount) displayedBals
|
, let rowavg = averageMixedAmounts unvaluedbals
|
||||||
|
, empty_ || depth == 0 || any (not . isZeroMixedAmount) unvaluedbals
|
||||||
]
|
]
|
||||||
-- Sort the report rows by amount or by account declaration order. A bit tricky.
|
rowsvalued :: [MultiBalanceReportRow] =
|
||||||
-- TODO TBD: is it always ok to sort report rows after report has been generated ?
|
dbg1 "rowsvalued" $
|
||||||
-- Or does sorting sometimes need to be done as part of the report generation ?
|
[(a, accountLeafName a, accountNameLevel a, valuedbals, valuedrowtot, valuedrowavg)
|
||||||
sorteditems :: [MultiBalanceReportRow] =
|
| (a,changes) <- acctchanges
|
||||||
dbg1 "sorteditems" $
|
-- The amounts to be displayed (period changes, cumulative totals, or historical balances).
|
||||||
sortitems items
|
, let unvaluedbals = case balancetype_ of
|
||||||
|
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
||||||
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
||||||
|
_ -> changes
|
||||||
|
-- The amounts valued according to --value-at, if needed.
|
||||||
|
, let valuedbals1 = case balancetype_ of
|
||||||
|
HistoricalBalance -> drop 1 $ scanl (+) (valuedStartingBalanceFor a) changes
|
||||||
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
||||||
|
_ -> changes
|
||||||
|
, let valuedbals = case mvalueat of
|
||||||
|
Just AtTransaction -> valuedbals1
|
||||||
|
Just AtPeriod -> [mixedAmountValue prices periodlastday amt | (amt,periodlastday) <- zip unvaluedbals lastdays]
|
||||||
|
Just AtNow -> [mixedAmountValue prices today amt | amt <- valuedbals1]
|
||||||
|
Just (AtDate d) -> [mixedAmountValue prices d amt | amt <- valuedbals1]
|
||||||
|
_ -> unvaluedbals --value-at=transaction was handled earlier
|
||||||
|
-- The total and average for the row, and their values.
|
||||||
|
, let rowtot = sum unvaluedbals
|
||||||
|
, let rowavg = averageMixedAmounts unvaluedbals
|
||||||
|
, let valuedrowtot = case mvalueat of
|
||||||
|
Just AtPeriod -> mixedAmountValue prices reportlastday rowtot
|
||||||
|
Just AtNow -> mixedAmountValue prices today rowtot
|
||||||
|
Just (AtDate d) -> mixedAmountValue prices d rowtot
|
||||||
|
_ -> rowtot
|
||||||
|
, let valuedrowavg = case mvalueat of
|
||||||
|
Just AtPeriod -> mixedAmountValue prices reportlastday rowavg
|
||||||
|
Just AtNow -> mixedAmountValue prices today rowavg
|
||||||
|
Just (AtDate d) -> mixedAmountValue prices d rowavg
|
||||||
|
_ -> rowavg
|
||||||
|
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedbals
|
||||||
|
]
|
||||||
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
-- 8. Build the report rows.
|
||||||
|
|
||||||
|
-- Sort the rows by amount or by account declaration order. This is a bit tricky.
|
||||||
|
-- TODO: is it always ok to sort report rows after report has been generated, as a separate step ?
|
||||||
|
sortedrowsvalued :: [MultiBalanceReportRow] =
|
||||||
|
dbg1 "sortedrowsvalued" $
|
||||||
|
sortrows rowsvalued
|
||||||
where
|
where
|
||||||
sortitems
|
sortrows
|
||||||
| sort_amount_ && accountlistmode_ == ALTree = sortTreeMBRByAmount
|
| sort_amount_ && accountlistmode_ == ALTree = sortTreeMBRByAmount
|
||||||
| sort_amount_ = sortFlatMBRByAmount
|
| sort_amount_ = sortFlatMBRByAmount
|
||||||
| otherwise = sortMBRByAccountDeclaration
|
| otherwise = sortMBRByAccountDeclaration
|
||||||
@ -276,22 +386,34 @@ multiBalanceReport ropts@ReportOpts{..} q j =
|
|||||||
anames = map fst anamesandrows
|
anames = map fst anamesandrows
|
||||||
sortedanames = sortAccountNamesByDeclaration j (tree_ ropts) anames
|
sortedanames = sortAccountNamesByDeclaration j (tree_ ropts) anames
|
||||||
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
sortedrows = sortAccountItemsLike sortedanames anamesandrows
|
||||||
-- Calculate the subperiod column totals.
|
|
||||||
totals :: [MixedAmount] =
|
|
||||||
-- dbg1 "totals" $
|
|
||||||
map sum balsbycol
|
|
||||||
where
|
|
||||||
balsbycol = transpose [bs | (a,_,_,bs,_,_) <- sorteditems, not (tree_ ropts) || a `elem` highestlevelaccts]
|
|
||||||
highestlevelaccts =
|
|
||||||
dbg1 "highestlevelaccts"
|
|
||||||
[a | a <- displayedAccts, not $ any (`elem` displayedAccts) $ init $ expandAccountName a]
|
|
||||||
-- Add a grand total and average to complete the totals row.
|
|
||||||
totalsrow :: MultiBalanceReportTotals =
|
|
||||||
dbg1 "totalsrow"
|
|
||||||
(totals, sum totals, averageMixedAmounts totals)
|
|
||||||
|
|
||||||
dbg1 s = let p = "multiBalanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in this function's debug output
|
----------------------------------------------------------------------
|
||||||
-- dbg1 = const id -- exclude this function from debug output
|
-- 9. Build the report totals row.
|
||||||
|
|
||||||
|
-- Calculate and maybe value the column totals.
|
||||||
|
highestlevelaccts = [a | a <- displayaccts, not $ any (`elem` displayaccts) $ init $ expandAccountName a]
|
||||||
|
colamts = transpose [bs | (a,_,_,bs,_,_) <- rows , not (tree_ ropts) || a `elem` highestlevelaccts]
|
||||||
|
colamtsvalued = transpose [bs | (a,_,_,bs,_,_) <- rowsvalued, not (tree_ ropts) || a `elem` highestlevelaccts]
|
||||||
|
coltotals :: [MixedAmount] =
|
||||||
|
dbg1 "coltotals" $
|
||||||
|
case mvalueat of
|
||||||
|
Nothing -> map sum colamts
|
||||||
|
Just AtTransaction -> map sum colamtsvalued
|
||||||
|
Just AtPeriod -> map (\(amts,periodlastday) -> maybevalue periodlastday $ sum amts) $ zip colamts lastdays
|
||||||
|
Just AtNow -> map (maybevalue today . sum) colamts
|
||||||
|
Just (AtDate d) -> map (maybevalue d . sum) colamts
|
||||||
|
-- Calculate and maybe value the grand total and average.
|
||||||
|
[grandtotal,grandaverage] =
|
||||||
|
let amts = map ($ map sum colamts) [sum, averageMixedAmounts]
|
||||||
|
in case mvalueat of
|
||||||
|
Nothing -> amts
|
||||||
|
Just AtTransaction -> amts
|
||||||
|
Just AtPeriod -> map (maybevalue reportlastday) amts
|
||||||
|
Just AtNow -> map (maybevalue today) amts
|
||||||
|
Just (AtDate d) -> map (maybevalue d) amts
|
||||||
|
-- Totals row.
|
||||||
|
totalsrow :: MultiBalanceReportTotals =
|
||||||
|
dbg1 "totalsrow" (coltotals, grandtotal, grandaverage)
|
||||||
|
|
||||||
-- | Given a MultiBalanceReport and its normal balance sign,
|
-- | Given a MultiBalanceReport and its normal balance sign,
|
||||||
-- if it is known to be normally negative, convert it to normally positive.
|
-- if it is known to be normally negative, convert it to normally positive.
|
||||||
@ -369,7 +491,7 @@ tests_MultiBalanceReports = tests "MultiBalanceReports" [
|
|||||||
],
|
],
|
||||||
Mixed [usd0])
|
Mixed [usd0])
|
||||||
|
|
||||||
,test "a valid history on an empty period" $
|
,_test "a valid history on an empty period" $
|
||||||
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
(defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||||
(
|
(
|
||||||
[
|
[
|
||||||
@ -378,7 +500,7 @@ tests_MultiBalanceReports = tests "MultiBalanceReports" [
|
|||||||
],
|
],
|
||||||
Mixed [usd0])
|
Mixed [usd0])
|
||||||
|
|
||||||
,test "a valid history on an empty period (more complex)" $
|
,_test "a valid history on an empty period (more complex)" $
|
||||||
(defreportopts{period_= PeriodBetween (fromGregorian 2009 1 1) (fromGregorian 2009 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
(defreportopts{period_= PeriodBetween (fromGregorian 2009 1 1) (fromGregorian 2009 1 2), balancetype_=HistoricalBalance}, samplejournal) `gives`
|
||||||
(
|
(
|
||||||
[
|
[
|
||||||
|
|||||||
@ -418,3 +418,77 @@ Balance changes in 2000q1:
|
|||||||
---++---------------
|
---++---------------
|
||||||
|| 4 B 4 B 4 B
|
|| 4 B 4 B 4 B
|
||||||
|
|
||||||
|
# balance, periodic, with -H (starting balance and accumulating across periods)
|
||||||
|
|
||||||
|
# 38. multicolumn balance report with -H valued at transaction.
|
||||||
|
# The starting balance is 1 B (1 A valued at 2000/1/1, transaction date).
|
||||||
|
$ hledger -f- bal -M -H -b 200002 --value-at=transaction
|
||||||
|
Ending balances (historical) in 2000/02/01-2000/03/31:
|
||||||
|
|
||||||
|
|| 2000/02/29 2000/03/31
|
||||||
|
===++========================
|
||||||
|
a || 3 B 6 B
|
||||||
|
---++------------------------
|
||||||
|
|| 3 B 6 B
|
||||||
|
|
||||||
|
# 39. multicolumn balance report with -H valued at period end.
|
||||||
|
# The starting balance is 5 B (1 A valued at 2000/1/31, day before report start).. and has no effect here.
|
||||||
|
$ hledger -f- bal -M -H -b 200002 --value-at=period
|
||||||
|
Ending balances (historical) in 2000/02/01-2000/03/31:
|
||||||
|
|
||||||
|
|| 2000/02/29 2000/03/31
|
||||||
|
===++========================
|
||||||
|
a || 4 B 9 B
|
||||||
|
---++------------------------
|
||||||
|
|| 4 B 9 B
|
||||||
|
|
||||||
|
# 40. multicolumn balance report with -H valued at other date.
|
||||||
|
# The starting balance is 5 B (1 A valued at 2000/1/15).
|
||||||
|
$ hledger -f- bal -M -H -b 200002 --value-at=2000-01-15
|
||||||
|
Ending balances (historical) in 2000/02/01-2000/03/31:
|
||||||
|
|
||||||
|
|| 2000/02/29 2000/03/31
|
||||||
|
===++========================
|
||||||
|
a || 10 B 15 B
|
||||||
|
---++------------------------
|
||||||
|
|| 10 B 15 B
|
||||||
|
|
||||||
|
# 41. multicolumn balance report with -H, valuing each period's carried-over balances at transaction date.
|
||||||
|
<
|
||||||
|
P 2000/01/01 A 1 B
|
||||||
|
P 2000/01/15 A 5 B
|
||||||
|
P 2000/02/01 A 2 B
|
||||||
|
P 2000/03/01 A 3 B
|
||||||
|
P 2000/04/01 A 4 B
|
||||||
|
|
||||||
|
2000/01/01
|
||||||
|
(a) 1 A
|
||||||
|
|
||||||
|
$ hledger -f- bal -ME -H -p200001-200004 --value-at=t
|
||||||
|
Ending balances (historical) in 2000q1:
|
||||||
|
|
||||||
|
|| 2000/01/31 2000/02/29 2000/03/31
|
||||||
|
===++====================================
|
||||||
|
a || 1 B 1 B 1 B
|
||||||
|
---++------------------------------------
|
||||||
|
|| 1 B 1 B 1 B
|
||||||
|
|
||||||
|
# 42. multicolumn balance report with -H, valuing each period's carried-over balances at period end.
|
||||||
|
# $ hledger -f- bal -ME -H -p200001-200004 --value-at=p
|
||||||
|
# Ending balances (historical) in 2000q1:
|
||||||
|
|
||||||
|
# || 2000/01/31 2000/02/29 2000/03/31
|
||||||
|
# ===++====================================
|
||||||
|
# a || 5 B 2 B 3 B
|
||||||
|
# ---++------------------------------------
|
||||||
|
# || 5 B 2 B 3 B
|
||||||
|
|
||||||
|
# 43. multicolumn balance report with -H, valuing each period's carried-over balances at other date.
|
||||||
|
$ hledger -f- bal -ME -H -p200001-200004 --value-at=2000-01-15
|
||||||
|
Ending balances (historical) in 2000q1:
|
||||||
|
|
||||||
|
|| 2000/01/31 2000/02/29 2000/03/31
|
||||||
|
===++====================================
|
||||||
|
a || 5 B 5 B 5 B
|
||||||
|
---++------------------------------------
|
||||||
|
|| 5 B 5 B 5 B
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user