bal etc.: replace --value=transaction with --value=cost (#329)
This commit is contained in:
parent
adbce22152
commit
9977739c76
@ -71,11 +71,7 @@ balanceReport ropts@ReportOpts{..} q j =
|
|||||||
-- dbg1 = const id -- exclude from debug output
|
-- dbg1 = const id -- exclude from debug output
|
||||||
dbg1 s = let p = "balanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in debug output
|
dbg1 s = let p = "balanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in debug output
|
||||||
|
|
||||||
-- We may be converting amounts to value, according to --value-at:
|
today = fromMaybe (error' "balanceReport: ReportOpts today_ is unset so could not satisfy --value=now") today_
|
||||||
-- transaction: value each posting at posting date before summing
|
|
||||||
-- period: value totals at period end
|
|
||||||
-- date: value totals at date
|
|
||||||
today = fromMaybe (error' "balanceReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
|
||||||
|
|
||||||
-- For --value-at=transaction, convert all postings to value before summing them.
|
-- For --value-at=transaction, convert all postings to value before summing them.
|
||||||
-- The report might not use them all but laziness probably helps here.
|
-- The report might not use them all but laziness probably helps here.
|
||||||
@ -83,9 +79,10 @@ balanceReport ropts@ReportOpts{..} q j =
|
|||||||
| otherwise = j
|
| otherwise = j
|
||||||
|
|
||||||
-- Get all the summed accounts & balances, according to the query, as an account tree.
|
-- Get all the summed accounts & balances, according to the query, as an account tree.
|
||||||
|
-- If doing cost valuation, amounts will be converted to cost first.
|
||||||
accttree = ledgerRootAccount $ ledgerFromJournal q $ journalSelectingAmountFromOpts ropts j'
|
accttree = ledgerRootAccount $ ledgerFromJournal q $ journalSelectingAmountFromOpts ropts j'
|
||||||
|
|
||||||
-- For --value-at=(all except transaction, done above), convert the summed amounts to value.
|
-- For other kinds of valuation, convert the summed amounts to value.
|
||||||
valuedaccttree = mapAccounts valueaccount accttree
|
valuedaccttree = mapAccounts valueaccount accttree
|
||||||
where
|
where
|
||||||
valueaccount a@Account{..} = a{aebalance=val aebalance, aibalance=val aibalance}
|
valueaccount a@Account{..} = a{aebalance=val aebalance, aibalance=val aibalance}
|
||||||
|
|||||||
@ -276,7 +276,7 @@ budgetReportAsText ropts@ReportOpts{..} budgetr@(PeriodicReport ( _, rows, _)) =
|
|||||||
title = printf "Budget performance in %s%s:"
|
title = printf "Budget performance in %s%s:"
|
||||||
(showDateSpan $ budgetReportSpan budgetr)
|
(showDateSpan $ budgetReportSpan budgetr)
|
||||||
(case value_ of
|
(case value_ of
|
||||||
Just (AtCost _mc) -> ", valued at transaction dates"
|
Just (AtCost _mc) -> ", valued at cost"
|
||||||
Just (AtEnd _mc) -> ", valued at period ends"
|
Just (AtEnd _mc) -> ", valued at period ends"
|
||||||
Just (AtNow _mc) -> ", current value"
|
Just (AtNow _mc) -> ", current value"
|
||||||
Just (AtDate d _mc) -> ", valued at "++showDate d
|
Just (AtDate d _mc) -> ", valued at "++showDate d
|
||||||
|
|||||||
@ -90,7 +90,7 @@ type ClippedAccountName = AccountName
|
|||||||
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
|
||||||
multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
||||||
(if invert_ then mbrNegate else id) $
|
(if invert_ then mbrNegate else id) $
|
||||||
MultiBalanceReport (colspans, sortedrowsvalued, totalsrow)
|
MultiBalanceReport (colspans, sortedrows, totalsrow)
|
||||||
where
|
where
|
||||||
dbg1 s = let p = "multiBalanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in this function's debug output
|
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
|
-- dbg1 = const id -- exclude this function from debug output
|
||||||
@ -137,75 +137,46 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
matchedspan = dbg1 "matchedspan" $ postingsDateSpan' (whichDateFromOpts ropts) ps
|
matchedspan = dbg1 "matchedspan" $ postingsDateSpan' (whichDateFromOpts ropts) ps
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 2. Things we'll need for valuation, if -V/--value-at are present.
|
-- 2. Things we'll need if doing valuation.
|
||||||
-- Valuation complicates this report quite a lot.
|
|
||||||
|
|
||||||
-- Here's the current intended effect of --value-at on each part of the report:
|
-- Here's the current intended effect of --value on each part of the report:
|
||||||
-- -H starting balances:
|
-- -H/--historical starting balances:
|
||||||
-- transaction: sum of values of previous postings on their posting dates
|
-- cost: summed cost of previous postings
|
||||||
-- period: value -H starting balances at day before report start
|
-- end: historical starting balances valued at day before report start
|
||||||
-- date: value -H starting balances at date
|
-- date: historical starting balances valued at date
|
||||||
-- table cells:
|
-- table cells:
|
||||||
-- transaction: value each posting before calculating table cell amounts
|
-- cost: summed costs of postings
|
||||||
-- period: value each table cell amount at subperiod end
|
-- end: summed postings, valued at subperiod end
|
||||||
-- date: value each table cell amount at date
|
-- date: summed postings, valued at date
|
||||||
-- column totals:
|
-- column totals:
|
||||||
-- transaction: sum/average the valued cell amounts
|
-- cost: summed column amounts
|
||||||
-- period: sum/average the unvalued amounts and value at subperiod end
|
-- end: summed column amounts
|
||||||
-- date: sum/average the unvalued amounts and value at date
|
-- date: summed column amounts
|
||||||
-- row totals & averages, grand total & average:
|
-- row totals & averages, grand total & average:
|
||||||
-- transaction: sum/average the valued amounts
|
-- cost: summed/averaged row amounts
|
||||||
-- period: sum/average the unvalued amounts and value at report period end
|
-- end: summed/averaged row amounts
|
||||||
-- date: sum/average the unvalued amounts and value at date
|
-- date: summed/averaged row amounts
|
||||||
-- mvalueat = valueTypeFromOpts ropts
|
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value=now") today_
|
||||||
today = fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value-at=now") today_
|
|
||||||
-- Market prices. Sort into date then parse order,
|
-- Market prices. Sort into date then parse order,
|
||||||
-- & reverse for quick lookup of the latest price.
|
-- & reverse for quick lookup of the latest price.
|
||||||
prices = reverse $ sortOn mpdate jmarketprices
|
prices = reverse $ sortOn mpdate jmarketprices
|
||||||
-- A helper for valuing amounts according to --value-at.
|
|
||||||
maybevalue :: Day -> MixedAmount -> MixedAmount
|
|
||||||
maybevalue periodlastday amt = case value_ of
|
|
||||||
Nothing -> amt
|
|
||||||
Just (AtCost _mc) -> amt -- assume --value-at=transaction was handled earlier
|
|
||||||
Just (AtEnd _mc) -> mixedAmountValue prices periodlastday amt
|
|
||||||
Just (AtNow _mc) -> mixedAmountValue prices today amt
|
|
||||||
Just (AtDate d _mc) -> mixedAmountValue prices d amt
|
|
||||||
-- The last day of each column subperiod.
|
-- The last day of each column subperiod.
|
||||||
lastdays :: [Day] =
|
lastdays :: [Day] =
|
||||||
map ((maybe
|
map ((maybe
|
||||||
(error' "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen
|
(error' "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen
|
||||||
(addDays (-1)))
|
(addDays (-1)))
|
||||||
. spanEnd) colspans
|
. spanEnd) colspans
|
||||||
-- The last day of the overall report period.
|
-- If doing cost valuation, convert amounts to cost.
|
||||||
reportlastday =
|
j' = journalSelectingAmountFromOpts ropts j
|
||||||
fromMaybe (error' "multiBalanceReport: expected a non-empty journal") -- XXX might happen ? :(
|
|
||||||
$ reportPeriodOrJournalLastDay ropts j
|
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 3. Calculate starting balances (both unvalued and valued), if needed for -H
|
-- 3. Calculate starting balances, if needed for -H
|
||||||
|
|
||||||
-- Balances at report start date, unvalued, from all earlier postings which otherwise match the query.
|
-- Balances at report start date, from all earlier postings which otherwise match the query.
|
||||||
|
-- These balances are unvalued except maybe converted to cost.
|
||||||
startbals :: [(AccountName, MixedAmount)] = dbg1 "startbals" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
startbals :: [(AccountName, MixedAmount)] = dbg1 "startbals" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems
|
||||||
where
|
where
|
||||||
(startbalanceitems,_) = dbg1 "starting balance report" $ balanceReport ropts''{value_=Nothing} startbalq j
|
(startbalanceitems,_) = dbg1 "starting balance report" $ balanceReport ropts''{value_=Nothing} 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
|
|
||||||
-- 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
|
where
|
||||||
ropts' | tree_ ropts = ropts{no_elide_=True}
|
ropts' | tree_ ropts = ropts{no_elide_=True}
|
||||||
| otherwise = ropts{accountlistmode_=ALFlat}
|
| otherwise = ropts{accountlistmode_=ALFlat}
|
||||||
@ -225,7 +196,6 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
startaccts = dbg1 "startaccts" $ map fst startbals
|
startaccts = dbg1 "startaccts" $ map fst startbals
|
||||||
-- Helpers to look up an account's starting balance.
|
-- Helpers to look up an account's starting balance.
|
||||||
startingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbals
|
startingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbals
|
||||||
valuedStartingBalanceFor a = fromMaybe nullmixedamt $ lookup a startbalsmaybevalued
|
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 4. Gather postings for each column.
|
-- 4. Gather postings for each column.
|
||||||
@ -234,24 +204,19 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
ps :: [Posting] =
|
ps :: [Posting] =
|
||||||
dbg1 "ps" $
|
dbg1 "ps" $
|
||||||
journalPostings $
|
journalPostings $
|
||||||
filterJournalAmounts symq $ -- remove amount parts excluded by cur:
|
filterJournalAmounts symq $ -- remove amount parts excluded by cur:
|
||||||
filterJournalPostings reportq $ -- remove postings not matched by (adjusted) query
|
filterJournalPostings reportq $ -- remove postings not matched by (adjusted) query
|
||||||
journalSelectingAmountFromOpts ropts j
|
j'
|
||||||
|
|
||||||
-- Group postings into their columns, with the column end dates.
|
-- Group postings into their columns, with the column end dates.
|
||||||
colps :: [([Posting], Maybe Day)] =
|
colps :: [([Posting], Maybe Day)] =
|
||||||
dbg1 "colps"
|
dbg1 "colps"
|
||||||
[(filter (isPostingInDateSpan' (whichDateFromOpts ropts) s) ps, spanEnd s) | s <- colspans]
|
[(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 value_ of
|
|
||||||
Just (AtCost _mc) -> [([postingValue jmarketprices (postingDate p) p | p <- ps], periodend) | (ps,periodend) <- colps]
|
|
||||||
_ -> colps
|
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 5. Calculate account balance changes in each column.
|
-- 5. Calculate account balance changes in each column.
|
||||||
|
|
||||||
-- In each column, gather the accounts that have postings and their change amount.
|
-- 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 :: [Posting] -> [(ClippedAccountName, MixedAmount)]
|
||||||
acctChangesFromPostings ps = [(aname a, (if tree_ ropts then aibalance else aebalance) a) | a <- as]
|
acctChangesFromPostings ps = [(aname a, (if tree_ ropts then aibalance else aebalance) a) | a <- as]
|
||||||
where
|
where
|
||||||
@ -261,10 +226,8 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
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
|
||||||
-- colacctchanges :: [[(ClippedAccountName, MixedAmount)]] =
|
colacctchanges :: [[(ClippedAccountName, MixedAmount)]] =
|
||||||
-- dbg1 "colacctchanges" $ map (acctChangesFromPostings . fst) colps
|
dbg1 "colacctchanges" $ map (acctChangesFromPostings . fst) colps
|
||||||
colacctchangesmaybevalued :: [[(ClippedAccountName, MixedAmount)]] =
|
|
||||||
dbg1 "colacctchangesmaybevalued" $ map (acctChangesFromPostings . fst) colpsmaybevalued
|
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 6. Gather the account balance changes into a regular matrix including the accounts
|
-- 6. Gather the account balance changes into a regular matrix including the accounts
|
||||||
@ -285,7 +248,7 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
dbg1 "colallacctchanges"
|
dbg1 "colallacctchanges"
|
||||||
[sortBy (comparing fst) $
|
[sortBy (comparing fst) $
|
||||||
unionBy (\(a,_) (a',_) -> a == a') postedacctchanges zeroes
|
unionBy (\(a,_) (a',_) -> a == a') postedacctchanges zeroes
|
||||||
| postedacctchanges <- colacctchangesmaybevalued]
|
| postedacctchanges <- colacctchanges]
|
||||||
where zeroes = [(a, nullmixedamt) | a <- displayaccts]
|
where zeroes = [(a, nullmixedamt) | a <- displayaccts]
|
||||||
-- Transpose to get each account's balance changes across all columns.
|
-- Transpose to get each account's balance changes across all columns.
|
||||||
acctchanges :: [(ClippedAccountName, [MixedAmount])] =
|
acctchanges :: [(ClippedAccountName, [MixedAmount])] =
|
||||||
@ -295,56 +258,33 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 7. Build the report rows.
|
-- 7. Build the report rows.
|
||||||
|
|
||||||
-- One row per account, with account name info, column amounts, row total and row average.
|
-- One row per account, with account name info, row amounts, row total and row average.
|
||||||
-- Calculate them two ways: unvalued for calculating column/grand totals, and valued for display.
|
-- Row amounts are converted to value if that has been requested.
|
||||||
|
-- Row total/average are always simply the sum/average of the row amounts.
|
||||||
rows :: [MultiBalanceReportRow] =
|
rows :: [MultiBalanceReportRow] =
|
||||||
dbg1 "rows" $
|
dbg1 "rows" $
|
||||||
[(a, accountLeafName a, accountNameLevel a, unvaluedbals, rowtot, rowavg)
|
[(a, accountLeafName a, accountNameLevel a, valuedrowbals, rowtot, rowavg)
|
||||||
| (a,changes) <- acctchanges
|
| (a,changes) <- dbg1 "acctchanges" acctchanges
|
||||||
-- The amounts to be displayed (period changes, cumulative totals, or historical balances).
|
-- The row amounts to be displayed: per-period changes,
|
||||||
, let unvaluedbals = case balancetype_ of
|
-- zero-based cumulative totals, or
|
||||||
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
-- starting-balance-based historical balances.
|
||||||
|
, let rowbals = dbg1 "rowbals" $ case balancetype_ of
|
||||||
|
PeriodChange -> changes
|
||||||
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
||||||
_ -> changes
|
|
||||||
-- The total and average for the row.
|
|
||||||
, let rowtot = if balancetype_==PeriodChange then sum unvaluedbals else 0
|
|
||||||
, let rowavg = averageMixedAmounts unvaluedbals
|
|
||||||
, empty_ || depth == 0 || any (not . isZeroMixedAmount) unvaluedbals
|
|
||||||
]
|
|
||||||
rowsvalued :: [MultiBalanceReportRow] =
|
|
||||||
dbg1 "rowsvalued" $
|
|
||||||
[(a, accountLeafName a, accountNameLevel a, valuedbals, valuedrowtot, valuedrowavg)
|
|
||||||
| (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
|
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
||||||
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
-- The row amounts valued according to --value if needed.
|
||||||
_ -> changes
|
, let valuedrowbals = dbg1 "valuedrowbals" $ case value_ of
|
||||||
-- The amounts valued according to --value-at, if needed.
|
Just (AtCost _mc) -> rowbals -- cost valuation was handled earlier
|
||||||
, let valuedbals1 = case balancetype_ of
|
Just (AtEnd _mc) -> [mixedAmountValue prices periodlastday amt | (amt,periodlastday) <- zip rowbals lastdays]
|
||||||
HistoricalBalance -> drop 1 $ scanl (+) (valuedStartingBalanceFor a) changes
|
Just (AtNow _mc) -> [mixedAmountValue prices today amt | amt <- rowbals]
|
||||||
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
Just (AtDate d _mc) -> [mixedAmountValue prices d amt | amt <- rowbals]
|
||||||
_ -> changes
|
Nothing -> rowbals
|
||||||
, let valuedbals = case value_ of
|
|
||||||
Just (AtCost _mc) -> valuedbals1
|
|
||||||
Just (AtEnd _mc) -> [mixedAmountValue prices periodlastday amt | (amt,periodlastday) <- zip unvaluedbals lastdays]
|
|
||||||
Just (AtNow _mc) -> [mixedAmountValue prices today amt | amt <- valuedbals1]
|
|
||||||
Just (AtDate d _mc) -> [mixedAmountValue prices d amt | amt <- valuedbals1]
|
|
||||||
_ -> unvaluedbals --value-at=transaction was handled earlier
|
|
||||||
-- The total and average for the row, and their values.
|
-- The total and average for the row, and their values.
|
||||||
, let rowtot = if balancetype_==PeriodChange then sum unvaluedbals else 0
|
-- Total for a cumulative/historical report is always zero.
|
||||||
, let rowavg = averageMixedAmounts unvaluedbals
|
, let rowtot = if balancetype_==PeriodChange then sum valuedrowbals else 0
|
||||||
, let valuedrowtot = case value_ of
|
, let rowavg = averageMixedAmounts valuedrowbals
|
||||||
Just (AtEnd _mc) -> mixedAmountValue prices reportlastday rowtot
|
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedrowbals
|
||||||
Just (AtNow _mc) -> mixedAmountValue prices today rowtot
|
|
||||||
Just (AtDate d _mc) -> mixedAmountValue prices d rowtot
|
|
||||||
_ -> rowtot
|
|
||||||
, let valuedrowavg = case value_ of
|
|
||||||
Just (AtEnd _mc) -> mixedAmountValue prices reportlastday rowavg
|
|
||||||
Just (AtNow _mc) -> mixedAmountValue prices today rowavg
|
|
||||||
Just (AtDate d _mc) -> mixedAmountValue prices d rowavg
|
|
||||||
_ -> rowavg
|
|
||||||
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedbals
|
|
||||||
]
|
]
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
@ -352,9 +292,9 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
|
|
||||||
-- Sort the rows by amount or by account declaration order. This is a bit tricky.
|
-- 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 ?
|
-- TODO: is it always ok to sort report rows after report has been generated, as a separate step ?
|
||||||
sortedrowsvalued :: [MultiBalanceReportRow] =
|
sortedrows :: [MultiBalanceReportRow] =
|
||||||
dbg1 "sortedrowsvalued" $
|
dbg1 "sortedrows" $
|
||||||
sortrows rowsvalued
|
sortrows rows
|
||||||
where
|
where
|
||||||
sortrows
|
sortrows
|
||||||
| sort_amount_ && accountlistmode_ == ALTree = sortTreeMBRByAmount
|
| sort_amount_ && accountlistmode_ == ALTree = sortTreeMBRByAmount
|
||||||
@ -393,30 +333,19 @@ multiBalanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- 9. Build the report totals row.
|
-- 9. Build the report totals row.
|
||||||
|
|
||||||
-- Calculate and maybe value the column totals.
|
-- Calculate the column totals. These are always the sum of column amounts.
|
||||||
highestlevelaccts = [a | a <- displayaccts, not $ any (`elem` displayaccts) $ init $ expandAccountName a]
|
highestlevelaccts = [a | a <- displayaccts, not $ any (`elem` displayaccts) $ init $ expandAccountName a]
|
||||||
colamts = transpose [bs | (a,_,_,bs,_,_) <- rows , not (tree_ ropts) || a `elem` highestlevelaccts]
|
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] =
|
coltotals :: [MixedAmount] =
|
||||||
dbg1 "coltotals" $
|
dbg1 "coltotals" $ map sum colamts
|
||||||
case value_ of
|
-- Calculate the grand total and average. These are always the sum/average
|
||||||
Nothing -> map sum colamts
|
-- of the column totals.
|
||||||
Just (AtCost _mc) -> map sum colamtsvalued
|
|
||||||
Just (AtEnd _mc) -> map (\(amts,periodlastday) -> maybevalue periodlastday $ sum amts) $ zip colamts lastdays
|
|
||||||
Just (AtNow _mc) -> map (maybevalue today . sum) colamts
|
|
||||||
Just (AtDate d _mc) -> map (maybevalue d . sum) colamts
|
|
||||||
-- Calculate and maybe value the grand total and average.
|
|
||||||
[grandtotal,grandaverage] =
|
[grandtotal,grandaverage] =
|
||||||
let amts = map ($ map sum colamts)
|
let amts = map ($ map sum colamts)
|
||||||
[if balancetype_==PeriodChange then sum else const 0
|
[if balancetype_==PeriodChange then sum else const 0
|
||||||
,averageMixedAmounts
|
,averageMixedAmounts
|
||||||
]
|
]
|
||||||
in case value_ of
|
in amts
|
||||||
Nothing -> amts
|
|
||||||
Just (AtCost _mc) -> amts
|
|
||||||
Just (AtEnd _mc) -> map (maybevalue reportlastday) amts
|
|
||||||
Just (AtNow _mc) -> map (maybevalue today) amts
|
|
||||||
Just (AtDate d _mc) -> map (maybevalue d) amts
|
|
||||||
-- Totals row.
|
-- Totals row.
|
||||||
totalsrow :: MultiBalanceReportTotals =
|
totalsrow :: MultiBalanceReportTotals =
|
||||||
dbg1 "totalsrow" (coltotals, grandtotal, grandaverage)
|
dbg1 "totalsrow" (coltotals, grandtotal, grandaverage)
|
||||||
|
|||||||
@ -583,7 +583,7 @@ multiBalanceReportAsText ropts@ReportOpts{..} r =
|
|||||||
HistoricalBalance -> "Ending balances (historical)")
|
HistoricalBalance -> "Ending balances (historical)")
|
||||||
(showDateSpan $ multiBalanceReportSpan r)
|
(showDateSpan $ multiBalanceReportSpan r)
|
||||||
(case value_ of
|
(case value_ of
|
||||||
Just (AtCost _mc) -> ", valued at transaction dates"
|
Just (AtCost _mc) -> ", valued at cost"
|
||||||
Just (AtEnd _mc) -> ", valued at period ends"
|
Just (AtEnd _mc) -> ", valued at period ends"
|
||||||
Just (AtNow _mc) -> ", current value"
|
Just (AtNow _mc) -> ", current value"
|
||||||
Just (AtDate d _mc) -> ", valued at "++showDate d
|
Just (AtDate d _mc) -> ", valued at "++showDate d
|
||||||
|
|||||||
@ -141,7 +141,7 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportopts_=r
|
|||||||
CumulativeChange -> "(Cumulative Ending Balances)"
|
CumulativeChange -> "(Cumulative Ending Balances)"
|
||||||
HistoricalBalance -> "(Historical Ending Balances)"
|
HistoricalBalance -> "(Historical Ending Balances)"
|
||||||
valuation = case value_ of
|
valuation = case value_ of
|
||||||
Just (AtCost _mc) -> ", valued at transaction dates"
|
Just (AtCost _mc) -> ", valued at cost"
|
||||||
Just (AtEnd _mc) -> ", valued at period ends"
|
Just (AtEnd _mc) -> ", valued at period ends"
|
||||||
Just (AtNow _mc) -> ", current value"
|
Just (AtNow _mc) -> ", current value"
|
||||||
Just (AtDate d _mc) -> ", valued at "++showDate d
|
Just (AtDate d _mc) -> ", valued at "++showDate d
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user