valuation: -V/-X respects report end date, code/doc cleanups (#1083)
-V (and -X) now respects a report end date set with -e/-p/date: when choosing the valuation date, similar to hledger 1.14 and Ledger. This means that -V/-X aren't exactly like either --value=end or --value=now. The "Effect of --value on reports" doc has been extended accordingly, and much of it has been reworded and made more accurate.
This commit is contained in:
parent
e73b7c2635
commit
a7f172b085
@ -331,19 +331,20 @@ aliasReplace (BasicAlias old new) a
|
|||||||
| otherwise = a
|
| otherwise = a
|
||||||
aliasReplace (RegexAlias re repl) a = T.pack $ regexReplaceCIMemo re repl $ T.unpack a -- XXX
|
aliasReplace (RegexAlias re repl) a = T.pack $ regexReplaceCIMemo re repl $ T.unpack a -- XXX
|
||||||
|
|
||||||
-- Apply a specified valuation to this posting's amount, using the provided
|
-- | Apply a specified valuation to this posting's amount, using the
|
||||||
-- price oracle, commodity styles, period-end/current dates, and whether
|
-- provided price oracle, commodity styles, reference dates, and
|
||||||
-- this is for a multiperiod report or not.
|
-- whether this is for a multiperiod report or not. See
|
||||||
postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Bool -> Posting -> ValuationType -> Posting
|
-- amountApplyValuation.
|
||||||
postingApplyValuation priceoracle styles periodend today ismultiperiod p v =
|
postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Posting -> ValuationType -> Posting
|
||||||
|
postingApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod p v =
|
||||||
case v of
|
case v of
|
||||||
AtCost Nothing -> postingToCost styles p
|
AtCost Nothing -> postingToCost styles p
|
||||||
AtCost mc -> postingValueAtDate priceoracle styles mc periodend $ postingToCost styles p
|
AtCost mc -> postingValueAtDate priceoracle styles mc periodlast $ postingToCost styles p
|
||||||
AtEnd mc -> postingValueAtDate priceoracle styles mc periodend p
|
AtEnd mc -> postingValueAtDate priceoracle styles mc periodlast p
|
||||||
AtNow mc -> postingValueAtDate priceoracle styles mc today p
|
AtNow mc -> postingValueAtDate priceoracle styles mc today p
|
||||||
AtDefault mc | ismultiperiod -> postingValueAtDate priceoracle styles mc periodend p
|
AtDefault mc | ismultiperiod -> postingValueAtDate priceoracle styles mc periodlast p
|
||||||
AtDefault mc -> postingValueAtDate priceoracle styles mc today p
|
AtDefault mc -> postingValueAtDate priceoracle styles mc (fromMaybe today mreportlast) p
|
||||||
AtDate d mc -> postingValueAtDate priceoracle styles mc d p
|
AtDate d mc -> postingValueAtDate priceoracle styles mc d p
|
||||||
|
|
||||||
-- | Convert this posting's amount to cost, and apply the appropriate amount styles.
|
-- | Convert this posting's amount to cost, and apply the appropriate amount styles.
|
||||||
postingToCost :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
|
postingToCost :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
|
||||||
|
|||||||
@ -97,26 +97,52 @@ data ValuationType =
|
|||||||
------------------------------------------------------------------------------
|
------------------------------------------------------------------------------
|
||||||
-- Valuation
|
-- Valuation
|
||||||
|
|
||||||
-- | Apply a specified valuation to this mixed amount, using the provided
|
-- | Apply a specified valuation to this mixed amount, using the
|
||||||
-- price oracle, commodity styles, period-end/current dates,
|
-- provided price oracle, commodity styles, reference dates, and
|
||||||
-- and whether this is for a multiperiod report or not.
|
-- whether this is for a multiperiod report or not.
|
||||||
mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Bool -> ValuationType -> MixedAmount -> MixedAmount
|
-- See amountApplyValuation.
|
||||||
mixedAmountApplyValuation priceoracle styles periodend today ismultiperiod v (Mixed as) =
|
mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> MixedAmount -> MixedAmount
|
||||||
Mixed $ map (amountApplyValuation priceoracle styles periodend today ismultiperiod v) as
|
mixedAmountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v (Mixed as) =
|
||||||
|
Mixed $ map (amountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v) as
|
||||||
|
|
||||||
-- | Apply a specified valuation to this amount, using the provided
|
-- | Apply a specified valuation to this amount, using the provided
|
||||||
-- price oracle, commodity styles, period-end/current dates,
|
-- price oracle, reference dates, and whether this is for a
|
||||||
-- and whether this is for a multiperiod report or not.
|
-- multiperiod report or not. Also fix up its display style using the
|
||||||
amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Bool -> ValuationType -> Amount -> Amount
|
-- provided commodity styles.
|
||||||
amountApplyValuation priceoracle styles periodend today ismultiperiod v a =
|
--
|
||||||
|
-- When the valuation requires converting to another commodity, a
|
||||||
|
-- valuation (conversion) date is chosen based on the valuation type,
|
||||||
|
-- the provided reference dates, and whether this is for a
|
||||||
|
-- single-period or multi-period report. It will be one of:
|
||||||
|
--
|
||||||
|
-- - a fixed date specified by the ValuationType itself
|
||||||
|
-- (--value=DATE).
|
||||||
|
--
|
||||||
|
-- - the provided "period end" date - this is typically the last day
|
||||||
|
-- of a subperiod (--value=end with a multi-period report), or of
|
||||||
|
-- the specified report period or the journal (--value=end with a
|
||||||
|
-- single-period report).
|
||||||
|
--
|
||||||
|
-- - the provided "report end" date - the last day of the specified
|
||||||
|
-- report period, if any (-V/-X with a report end date).
|
||||||
|
--
|
||||||
|
-- - the provided "today" date - (--value=now, or -V/X with no report
|
||||||
|
-- end date).
|
||||||
|
--
|
||||||
|
-- This is all a bit complicated. See the reference doc at
|
||||||
|
-- https://hledger.org/hledger.html#effect-of-value-on-reports
|
||||||
|
-- (hledger_options.m4.md "Effect of --value on reports"), and #1083.
|
||||||
|
--
|
||||||
|
amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> Amount -> Amount
|
||||||
|
amountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v a =
|
||||||
case v of
|
case v of
|
||||||
AtCost Nothing -> amountToCost styles a
|
AtCost Nothing -> amountToCost styles a
|
||||||
AtCost mc -> amountValueAtDate priceoracle styles mc periodend $ amountToCost styles a
|
AtCost mc -> amountValueAtDate priceoracle styles mc periodlast $ amountToCost styles a
|
||||||
AtEnd mc -> amountValueAtDate priceoracle styles mc periodend a
|
AtEnd mc -> amountValueAtDate priceoracle styles mc periodlast a
|
||||||
AtNow mc -> amountValueAtDate priceoracle styles mc today a
|
AtNow mc -> amountValueAtDate priceoracle styles mc today a
|
||||||
AtDefault mc | ismultiperiod -> amountValueAtDate priceoracle styles mc periodend a
|
AtDefault mc | ismultiperiod -> amountValueAtDate priceoracle styles mc periodlast a
|
||||||
AtDefault mc -> amountValueAtDate priceoracle styles mc today a
|
AtDefault mc -> amountValueAtDate priceoracle styles mc (fromMaybe today mreportlast) a
|
||||||
AtDate d mc -> amountValueAtDate priceoracle styles mc d a
|
AtDate d mc -> amountValueAtDate priceoracle styles mc d a
|
||||||
|
|
||||||
-- | Find the market value of each component amount in the given
|
-- | Find the market value of each component amount in the given
|
||||||
-- commodity, or its default valuation commodity, at the given
|
-- commodity, or its default valuation commodity, at the given
|
||||||
|
|||||||
@ -71,25 +71,24 @@ balanceReport ropts@ReportOpts{..} q j@Journal{..} =
|
|||||||
-- 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
|
||||||
|
|
||||||
today = fromMaybe (error' "balanceReport: ReportOpts today_ is unset so could not satisfy --value=now") today_
|
|
||||||
multiperiod = interval_ /= NoInterval
|
|
||||||
styles = journalCommodityStyles 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.
|
-- 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 other kinds of valuation, convert the summed amounts to value.
|
-- For other kinds of valuation, convert the summed amounts to value,
|
||||||
priceoracle = journalPriceOracle j
|
-- per hledger_options.m4.md "Effect of --value on reports".
|
||||||
valuedaccttree = mapAccounts valueaccount accttree
|
valuedaccttree = mapAccounts avalue accttree
|
||||||
where
|
where
|
||||||
valueaccount a@Account{..} = a{aebalance=val aebalance, aibalance=val aibalance}
|
avalue a@Account{..} = a{aebalance=bvalue aebalance, aibalance=bvalue aibalance}
|
||||||
where
|
where
|
||||||
val = maybe id (mixedAmountApplyValuation priceoracle styles periodlastday today multiperiod) value_
|
bvalue = maybe id (mixedAmountApplyValuation (journalPriceOracle j) (journalCommodityStyles j) periodlast mreportlast today multiperiod) value_
|
||||||
where
|
where
|
||||||
periodlastday =
|
periodlast =
|
||||||
fromMaybe (error' "balanceReport: expected a non-empty journal") $ -- XXX shouldn't happen
|
fromMaybe (error' "balanceReport: expected a non-empty journal") $ -- XXX shouldn't happen
|
||||||
reportPeriodOrJournalLastDay ropts j
|
reportPeriodOrJournalLastDay ropts j
|
||||||
|
mreportlast = reportPeriodLastDay ropts
|
||||||
|
today = fromMaybe (error' "balanceReport: could not pick a valuation date, ReportOpts today_ is unset") today_
|
||||||
|
multiperiod = interval_ /= NoInterval
|
||||||
|
|
||||||
-- Modify this tree for display - depth limit, boring parents, zeroes - and convert to a list.
|
-- Modify this tree for display - depth limit, boring parents, zeroes - and convert to a list.
|
||||||
displayaccts :: [Account]
|
displayaccts :: [Account]
|
||||||
|
|||||||
@ -14,11 +14,9 @@ module Hledger.Reports.EntriesReport (
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Ord
|
import Data.Ord
|
||||||
import Data.Time.Calendar (Day, addDays)
|
|
||||||
|
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Query
|
import Hledger.Query
|
||||||
@ -35,28 +33,19 @@ type EntriesReportItem = Transaction
|
|||||||
-- | Select transactions for an entries report.
|
-- | Select transactions for an entries report.
|
||||||
entriesReport :: ReportOpts -> Query -> Journal -> EntriesReport
|
entriesReport :: ReportOpts -> Query -> Journal -> EntriesReport
|
||||||
entriesReport ropts@ReportOpts{..} q j@Journal{..} =
|
entriesReport ropts@ReportOpts{..} q j@Journal{..} =
|
||||||
sortBy (comparing datefn) $ filter (q `matchesTransaction`) $ map tvalue jtxns
|
sortBy (comparing getdate) $ filter (q `matchesTransaction`) $ map tvalue jtxns
|
||||||
where
|
where
|
||||||
datefn = transactionDateFn ropts
|
getdate = transactionDateFn ropts
|
||||||
styles = journalCommodityStyles j
|
-- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports".
|
||||||
tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings}
|
tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings}
|
||||||
priceoracle = journalPriceOracle j
|
|
||||||
pvalue p = maybe p (postingApplyValuation priceoracle styles end today False p) value_
|
|
||||||
where
|
where
|
||||||
today = fromMaybe (error' "erValue: ReportOpts today_ is unset so could not satisfy --value=now") today_
|
pvalue p = maybe p
|
||||||
end = fromMaybe (postingDate p) mperiodorjournallastday
|
(postingApplyValuation (journalPriceOracle j) (journalCommodityStyles j) periodlast mreportlast today False p)
|
||||||
|
value_
|
||||||
where
|
where
|
||||||
mperiodorjournallastday = mperiodlastday <|> journalEndDate False j
|
periodlast = fromMaybe today $ reportPeriodOrJournalLastDay ropts j
|
||||||
where
|
mreportlast = reportPeriodLastDay ropts
|
||||||
-- The last day of the report period.
|
today = fromMaybe (error' "erValue: could not pick a valuation date, ReportOpts today_ is unset") today_ -- should not happen
|
||||||
-- Will be Nothing if no report period is specified, or also
|
|
||||||
-- if ReportOpts does not have today_ set, since we need that
|
|
||||||
-- to get the report period robustly.
|
|
||||||
mperiodlastday :: Maybe Day = do
|
|
||||||
t <- today_
|
|
||||||
let q = queryFromOpts t ropts
|
|
||||||
qend <- queryEndDate False q
|
|
||||||
return $ addDays (-1) qend
|
|
||||||
|
|
||||||
tests_EntriesReport = tests "EntriesReport" [
|
tests_EntriesReport = tests "EntriesReport" [
|
||||||
tests "entriesReport" [
|
tests "entriesReport" [
|
||||||
|
|||||||
@ -245,9 +245,6 @@ multiBalanceReportWith ropts@ReportOpts{..} q j@Journal{..} priceoracle =
|
|||||||
-- 6. Build the report rows.
|
-- 6. Build the report rows.
|
||||||
|
|
||||||
-- One row per account, with account name info, row amounts, row total and row average.
|
-- One row per account, with account name info, row amounts, row total and row average.
|
||||||
-- Row amounts are converted to value if that has been requested.
|
|
||||||
-- Row total/average are always simply the sum/average of the row amounts.
|
|
||||||
multiperiod = interval_ /= NoInterval
|
|
||||||
rows :: [MultiBalanceReportRow] =
|
rows :: [MultiBalanceReportRow] =
|
||||||
dbg1 "rows" $
|
dbg1 "rows" $
|
||||||
[(a, accountLeafName a, accountNameLevel a, valuedrowbals, rowtot, rowavg)
|
[(a, accountLeafName a, accountNameLevel a, valuedrowbals, rowtot, rowavg)
|
||||||
@ -259,38 +256,25 @@ multiBalanceReportWith ropts@ReportOpts{..} q j@Journal{..} priceoracle =
|
|||||||
PeriodChange -> changes
|
PeriodChange -> changes
|
||||||
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
CumulativeChange -> drop 1 $ scanl (+) 0 changes
|
||||||
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes
|
||||||
-- The row amounts valued according to --value if needed.
|
-- We may be converting amounts to value, per hledger_options.m4.md "Effect of --value on reports".
|
||||||
, let val end = maybe id (mixedAmountApplyValuation priceoracle styles end today multiperiod) value_
|
, let valuedrowbals = dbg1 "valuedrowbals" $ [avalue periodlastday amt | (amt,periodlastday) <- zip rowbals lastdays]
|
||||||
, let valuedrowbals = dbg1 "valuedrowbals" $ [val periodlastday amt | (amt,periodlastday) <- zip rowbals lastdays]
|
-- The total and average for the row.
|
||||||
-- The total and average for the row, and their values.
|
-- These are always simply the sum/average of the displayed row amounts.
|
||||||
-- Total for a cumulative/historical report is always zero.
|
-- Total for a cumulative/historical report is always zero.
|
||||||
, let rowtot = if balancetype_==PeriodChange then sum valuedrowbals else 0
|
, let rowtot = if balancetype_==PeriodChange then sum valuedrowbals else 0
|
||||||
, let rowavg = averageMixedAmounts valuedrowbals
|
, let rowavg = averageMixedAmounts valuedrowbals
|
||||||
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedrowbals
|
, empty_ || depth == 0 || any (not . isZeroMixedAmount) valuedrowbals
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
-- Some things needed if doing valuation.
|
avalue periodlast =
|
||||||
-- Here's the current intended effect of --value on each part of the report:
|
maybe id (mixedAmountApplyValuation priceoracle styles periodlast mreportlast today multiperiod) value_
|
||||||
-- -H/--historical starting balances:
|
where
|
||||||
-- cost: summed cost of previous postings
|
-- Some things needed if doing valuation.
|
||||||
-- end: historical starting balances valued at day before report start
|
styles = journalCommodityStyles j
|
||||||
-- date: historical starting balances valued at date
|
mreportlast = reportPeriodLastDay ropts
|
||||||
-- table cells:
|
today = fromMaybe (error' "multiBalanceReport: could not pick a valuation date, ReportOpts today_ is unset") today_ -- XXX shouldn't happen
|
||||||
-- cost: summed costs of postings
|
multiperiod = interval_ /= NoInterval
|
||||||
-- end: summed postings, valued at subperiod end
|
-- The last day of each column's subperiod.
|
||||||
-- date: summed postings, valued at date
|
|
||||||
-- column totals:
|
|
||||||
-- cost: summed column amounts
|
|
||||||
-- end: summed column amounts
|
|
||||||
-- date: summed column amounts
|
|
||||||
-- row totals & averages, grand total & average:
|
|
||||||
-- cost: summed/averaged row amounts
|
|
||||||
-- end: summed/averaged row amounts
|
|
||||||
-- date: summed/averaged row amounts
|
|
||||||
today = fromMaybe (error' "multiBalanceReport: ReportOpts today_ is unset so could not satisfy --value=now") today_ -- XXX shouldn't error if not needed, eg valuation type is AtDate
|
|
||||||
-- Market prices, commodity display styles.
|
|
||||||
styles = journalCommodityStyles j
|
|
||||||
-- The last day of each column subperiod.
|
|
||||||
lastdays =
|
lastdays =
|
||||||
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
|
||||||
|
|||||||
@ -70,67 +70,60 @@ postingsReport :: ReportOpts -> Query -> Journal -> PostingsReport
|
|||||||
postingsReport ropts@ReportOpts{..} q j@Journal{..} =
|
postingsReport ropts@ReportOpts{..} q j@Journal{..} =
|
||||||
(totallabel, items)
|
(totallabel, items)
|
||||||
where
|
where
|
||||||
reportspan = adjustReportDates ropts q j
|
reportspan = adjustReportDates ropts q j
|
||||||
whichdate = whichDateFromOpts ropts
|
whichdate = whichDateFromOpts ropts
|
||||||
depth = queryDepth q
|
depth = queryDepth q
|
||||||
styles = journalCommodityStyles j
|
styles = journalCommodityStyles j
|
||||||
|
priceoracle = journalPriceOracle j
|
||||||
|
multiperiod = interval_ /= NoInterval
|
||||||
|
today = fromMaybe (error' "postingsReport: could not pick a valuation date, ReportOpts today_ is unset") today_
|
||||||
|
|
||||||
-- postings to be included in the report, and similarly-matched postings before the report start date
|
-- postings to be included in the report, and similarly-matched postings before the report start date
|
||||||
(precedingps, reportps) = matchedPostingsBeforeAndDuring ropts q j reportspan
|
(precedingps, reportps) = matchedPostingsBeforeAndDuring ropts q j reportspan
|
||||||
|
|
||||||
-- We may be converting amounts to value.
|
|
||||||
-- Currently this is done as follows (keep synced with hledger_options.m4.md):
|
|
||||||
-- register -M --value
|
|
||||||
-- cost: value each posting at cost, then summarise ; value -H starting balance at cost
|
|
||||||
-- end: value each summary posting at period end ; value -H starting balance at day before report start
|
|
||||||
-- date: value each summary posting at date ; value -H starting balance at date
|
|
||||||
-- register --value
|
|
||||||
-- cost: value each posting at cost ; value -H starting balance at cost
|
|
||||||
-- end: value each posting at report end ; value -H starting balance at day before report start
|
|
||||||
-- date: value each posting at date ; value -H starting balance at date
|
|
||||||
--
|
|
||||||
-- In all cases, the running total/average is calculated from the above numbers.
|
|
||||||
-- "Day before report start" is a bit arbitrary.
|
|
||||||
today =
|
|
||||||
fromMaybe (error' "postingsReport: ReportOpts today_ is unset so could not satisfy --value=now")
|
|
||||||
today_
|
|
||||||
reportperiodlastday =
|
|
||||||
fromMaybe (error' "postingsReport: expected a non-empty journal") $ -- XXX shouldn't happen
|
|
||||||
reportPeriodOrJournalLastDay ropts j
|
|
||||||
multiperiod = interval_ /= NoInterval
|
|
||||||
showempty = empty_ || average_
|
|
||||||
priceoracle = journalPriceOracle j
|
|
||||||
pvalue p end = maybe p (postingApplyValuation priceoracle styles end today multiperiod p) value_
|
|
||||||
|
|
||||||
-- Postings, or summary postings with their subperiod's end date, to be displayed.
|
-- Postings, or summary postings with their subperiod's end date, to be displayed.
|
||||||
displayps :: [(Posting, Maybe Day)]
|
displayps :: [(Posting, Maybe Day)]
|
||||||
| multiperiod =
|
| multiperiod =
|
||||||
let summaryps = summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps
|
let summaryps = summarisePostingsByInterval interval_ whichdate depth showempty reportspan reportps
|
||||||
in [(pvalue p lastday, Just periodend) | (p, periodend) <- summaryps, let lastday = addDays (-1) periodend]
|
in [(pvalue p lastday, Just periodend) | (p, periodend) <- summaryps, let lastday = addDays (-1) periodend]
|
||||||
| otherwise =
|
| otherwise =
|
||||||
[(pvalue p reportperiodlastday, Nothing) | p <- reportps]
|
[(pvalue p reportorjournallast, Nothing) | p <- reportps]
|
||||||
|
|
||||||
-- posting report items ready for display
|
|
||||||
items = dbg1 "postingsReport items" $ postingsReportItems displayps (nullposting,Nothing) whichdate depth startbalvalued runningcalc startnum
|
|
||||||
where
|
where
|
||||||
historical = balancetype_ == HistoricalBalance
|
showempty = empty_ || average_
|
||||||
precedingsum = sumPostings precedingps
|
-- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports".
|
||||||
precedingavg | null precedingps = 0
|
pvalue p periodlast = maybe p (postingApplyValuation priceoracle styles periodlast mreportlast today multiperiod p) value_
|
||||||
| otherwise = divideMixedAmount (fromIntegral $ length precedingps) precedingsum
|
|
||||||
startbal | average_ = if historical then precedingavg else 0
|
|
||||||
| otherwise = if historical then precedingsum else 0
|
|
||||||
-- For --value=end/now/DATE, convert the initial running total/average to value.
|
|
||||||
startbalvalued = val startbal
|
|
||||||
where
|
where
|
||||||
val = maybe id (mixedAmountApplyValuation priceoracle styles daybeforereportstart today multiperiod) value_
|
mreportlast = reportPeriodLastDay ropts
|
||||||
where
|
reportorjournallast =
|
||||||
daybeforereportstart = maybe
|
fromMaybe (error' "postingsReport: expected a non-empty journal") $ -- XXX shouldn't happen
|
||||||
(error' "postingsReport: expected a non-empty journal") -- XXX shouldn't happen
|
reportPeriodOrJournalLastDay ropts j
|
||||||
(addDays (-1))
|
|
||||||
$ reportPeriodOrJournalStart ropts j
|
-- Posting report items ready for display.
|
||||||
|
items =
|
||||||
|
dbg1 "postingsReport items" $
|
||||||
|
postingsReportItems displayps (nullposting,Nothing) whichdate depth startbal runningcalc startnum
|
||||||
|
where
|
||||||
|
-- In historical mode we'll need a starting balance, which we
|
||||||
|
-- may be converting to value per hledger_options.m4.md "Effect
|
||||||
|
-- of --value on reports".
|
||||||
|
-- XXX balance report doesn't value starting balance.. should this ?
|
||||||
|
historical = balancetype_ == HistoricalBalance
|
||||||
|
startbal | average_ = if historical then bvalue precedingavg else 0
|
||||||
|
| otherwise = if historical then bvalue precedingsum else 0
|
||||||
|
where
|
||||||
|
precedingsum = sumPostings precedingps
|
||||||
|
precedingavg | null precedingps = 0
|
||||||
|
| otherwise = divideMixedAmount (fromIntegral $ length precedingps) precedingsum
|
||||||
|
bvalue = maybe id (mixedAmountApplyValuation priceoracle styles daybeforereportstart Nothing today multiperiod) value_
|
||||||
|
-- XXX constrain valuation type to AtDate daybeforereportstart here ?
|
||||||
|
where
|
||||||
|
daybeforereportstart =
|
||||||
|
maybe (error' "postingsReport: expected a non-empty journal") -- XXX shouldn't happen
|
||||||
|
(addDays (-1))
|
||||||
|
$ reportPeriodOrJournalStart ropts j
|
||||||
|
|
||||||
startnum = if historical then length precedingps + 1 else 1
|
|
||||||
runningcalc = registerRunningCalculationFn ropts
|
runningcalc = registerRunningCalculationFn ropts
|
||||||
|
startnum = if historical then length precedingps + 1 else 1
|
||||||
|
|
||||||
-- | Based on the given report options, return a function that does the appropriate
|
-- | Based on the given report options, return a function that does the appropriate
|
||||||
-- running calculation for the register report, ie a running average or running total.
|
-- running calculation for the register report, ie a running average or running total.
|
||||||
|
|||||||
@ -687,28 +687,28 @@ See also the definitions and notes below.
|
|||||||
If you find problems, please report them, ideally with a reproducible example.
|
If you find problems, please report them, ideally with a reproducible example.
|
||||||
Related: [#329](https://github.com/simonmichael/hledger/issues/329).
|
Related: [#329](https://github.com/simonmichael/hledger/issues/329).
|
||||||
|
|
||||||
| Report type | `-B`, `--value=cost` | `-V`, `-X` | `--value=end` | `--value=DATE`, `--value=now` |
|
| Report type | `-B`, `--value=cost` | `-V`, `-X` | `--value=end` | `--value=DATE`, `--value=now` |
|
||||||
|:------------------------------------------------|:-----------------------------------|:-----------------------------------------|:---------------------------------------------------|:----------------------------------------|
|
|:------------------------------------------------|:----------------------------------------------|:-------------------------------------------------|:---------------------------------------------------|:----------------------------------------|
|
||||||
| **print** | | | | |
|
| **print** | | | | |
|
||||||
| posting amounts | cost | value today[1] | value at report or journal end or posting date | value at DATE/today |
|
| posting amounts | cost | value at report end or today | value at report or journal end | value at DATE/today |
|
||||||
| balance assertions / assignments | unchanged | unchanged | unchanged | unchanged |
|
| balance assertions / assignments | unchanged | unchanged | unchanged | unchanged |
|
||||||
| <br> | | | | |
|
| <br> | | | | |
|
||||||
| **register** | | | | |
|
| **register** | | | | |
|
||||||
| starting balance (with -H) | cost | value today[1] | value at day before report or journal start | value at DATE/today |
|
| starting balance (with -H) | cost | value at day before report or journal start | value at day before report or journal start | value at DATE/today |
|
||||||
| posting amounts (no report interval) | cost | value today[1] | value at report or journal end | value at DATE/today |
|
| posting amounts (no report interval) | cost | value at report end or today | value at report or journal end | value at DATE/today |
|
||||||
| summary posting amounts (with report interval) | summarised cost | value at period ends | value at period ends | value at DATE/today |
|
| summary posting amounts (with report interval) | summarised cost | value at period ends | value at period ends | value at DATE/today |
|
||||||
| running total/average | sum/average of displayed values | sum/average of displayed values | sum/average of displayed values | sum/average of displayed values |
|
| running total/average | sum/average of displayed values | sum/average of displayed values | sum/average of displayed values | sum/average of displayed values |
|
||||||
| <br> | | | | |
|
| <br> | | | | |
|
||||||
| **balance (bs, bse, cf, is..)** | | | | |
|
| **balance (bs, bse, cf, is..)** | | | | |
|
||||||
| balances (no report interval) | sums of costs | value today[1] of sums of postings | value at report or journal end of sums of postings | value at DATE/today of sums of postings |
|
| balances (no report interval) | sums of costs | value at report end or today of sums of postings | value at report or journal end of sums of postings | value at DATE/today of sums of postings |
|
||||||
| starting balances (with report interval and -H) | sums of costs of previous postings | sums of previous postings | sums of previous postings | sums of previous postings |
|
| balances (with report interval) | sums of costs | value at period ends of sums of postings | value at period ends of sums of postings | value at DATE/today of sums of postings |
|
||||||
| balances (with report interval) | sums of costs | value at period ends of sums of postings | value at period ends of sums of postings | value at DATE/today of sums of postings |
|
| starting balances (with report interval and -H) | sums of costs of postings before report start | sums of postings before report start | sums of postings before report start | sums of postings before report start |
|
||||||
| budget amounts with --budget | like balances | like balances | like balances | like balances |
|
| budget amounts with --budget | like balances | like balances | like balances | like balances |
|
||||||
| grand total (no report interval) | sum of displayed values | sum of displayed values | sum of displayed values | sum of displayed values |
|
| grand total (no report interval) | sum of displayed values | sum of displayed values | sum of displayed values | sum of displayed values |
|
||||||
| row totals/averages (with report interval) | sums/averages of displayed values | sums/averages of displayed values | sums/averages of displayed values | sums/averages of displayed values |
|
| row totals/averages (with report interval) | sums/averages of displayed values | sums/averages of displayed values | sums/averages of displayed values | sums/averages of displayed values |
|
||||||
| column totals | sums of displayed values | sums of displayed values | sums of displayed values | sums of displayed values |
|
| column totals | sums of displayed values | sums of displayed values | sums of displayed values | sums of displayed values |
|
||||||
| grand total/average | sum/average of column totals | sum/average of column totals | sum/average of column totals | sum/average of column totals |
|
| grand total/average | sum/average of column totals | sum/average of column totals | sum/average of column totals | sum/average of column totals |
|
||||||
| <br> | | | | |
|
| <br> | | | | |
|
||||||
|
|
||||||
**Additional notes**
|
**Additional notes**
|
||||||
|
|
||||||
@ -733,11 +733,6 @@ Related: [#329](https://github.com/simonmichael/hledger/issues/329).
|
|||||||
*report interval*
|
*report interval*
|
||||||
: a flag (-D/-W/-M/-Q/-Y) or period expression that activates the report's multi-period mode (whether showing one or many subperiods).
|
: a flag (-D/-W/-M/-Q/-Y) or period expression that activates the report's multi-period mode (whether showing one or many subperiods).
|
||||||
|
|
||||||
[1] As of hledger 1.15, print -V and register -V, with no report interval,
|
|
||||||
use today as the valuation date, ignoring any end date specified with
|
|
||||||
-e/-p/date:, unlike hledger-1.14 and Ledger. Workaround: use
|
|
||||||
--value=end instead.
|
|
||||||
([#1083](https://github.com/simonmichael/hledger/issues/1083)).
|
|
||||||
|
|
||||||
### Combining -B, -V, -X, --value
|
### Combining -B, -V, -X, --value
|
||||||
|
|
||||||
|
|||||||
@ -45,7 +45,8 @@ $ hledger -f- bal -N -V a
|
|||||||
€130.00 a
|
€130.00 a
|
||||||
|
|
||||||
|
|
||||||
# 4. Market prices in the future (later than today's date) are ignored by default. #453, #683
|
# 4. Market prices in the future are ignored when the valuation date
|
||||||
|
# is today, which is the default with -V. #453, #683
|
||||||
<
|
<
|
||||||
P 2000/1/1 $ €1.20
|
P 2000/1/1 $ €1.20
|
||||||
P 3000/1/1 $ €1.30
|
P 3000/1/1 $ €1.30
|
||||||
@ -57,8 +58,9 @@ $ hledger -f- bal -N -V
|
|||||||
€120.00 a
|
€120.00 a
|
||||||
|
|
||||||
|
|
||||||
# 5. Market prices in the future are still ignored by default even
|
# 5. Market prices in the future are not ignored when they are before
|
||||||
# with an explicit future report end date, unlike hledger 1.14-.
|
# the valuation date set with an explicit report end date, as in
|
||||||
|
# hledger 1.14 and older, and Ledger. See also valuation2.test, #1083
|
||||||
<
|
<
|
||||||
P 3000/1/1 $ €1.10
|
P 3000/1/1 $ €1.10
|
||||||
|
|
||||||
@ -66,7 +68,7 @@ P 3000/1/1 $ €1.10
|
|||||||
(a) $100
|
(a) $100
|
||||||
|
|
||||||
$ hledger -f- bal -N -V -e 3000/2
|
$ hledger -f- bal -N -V -e 3000/2
|
||||||
$100 a
|
€110.00 a
|
||||||
|
|
||||||
|
|
||||||
# 6. Market prices interact with D directives and with amount style canonicalisation. #131
|
# 6. Market prices interact with D directives and with amount style canonicalisation. #131
|
||||||
|
|||||||
@ -183,3 +183,27 @@ $ hledger -f- print -B -XZ
|
|||||||
|
|
||||||
>=0
|
>=0
|
||||||
|
|
||||||
|
# A few more tests for -V (and -X, which should work similarly). #1083.
|
||||||
|
<
|
||||||
|
P 2000/01/01 A 2 B
|
||||||
|
P 2002/01/01 A 3 B
|
||||||
|
|
||||||
|
2000/01/01
|
||||||
|
(a) 1 A
|
||||||
|
|
||||||
|
# 17. -V uses today as the default valuation date, unlike --value=end.
|
||||||
|
$ hledger -f- reg -V
|
||||||
|
2000/01/01 (a) 3 B 3 B
|
||||||
|
|
||||||
|
# 18. -V uses the report end date, if specified, as valuation date.
|
||||||
|
$ hledger -f- reg -V -e 2001
|
||||||
|
2000/01/01 (a) 2 B 2 B
|
||||||
|
|
||||||
|
# 19. In balance reports too.
|
||||||
|
$ hledger -f- bal -N -V
|
||||||
|
3 B a
|
||||||
|
|
||||||
|
# 20.
|
||||||
|
$ hledger -f- bal -N -V -e 2001
|
||||||
|
2 B a
|
||||||
|
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user