diff --git a/hledger-lib/Hledger/Reports/MultiBalanceReport.hs b/hledger-lib/Hledger/Reports/MultiBalanceReport.hs index 7bb2b0cd2..7a9d22aa5 100644 --- a/hledger-lib/Hledger/Reports/MultiBalanceReport.hs +++ b/hledger-lib/Hledger/Reports/MultiBalanceReport.hs @@ -50,7 +50,7 @@ import Data.Semigroup ((<>)) #endif import Data.Semigroup (sconcat) import Data.Time.Calendar (Day, addDays, fromGregorian) -import Safe (headMay, lastDef, lastMay) +import Safe (headMay, lastDef, lastMay, minimumMay) import Hledger.Data import Hledger.Query @@ -197,7 +197,9 @@ startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle repo rspec' = rspec{rsQuery=startbalq,rsOpts=ropts'} -- If we're re-valuing every period, we need to have the unvalued start -- balance, so we can do it ourselves later. - ropts' = if changingValuation ropts then ropts''{value_=Nothing} else ropts'' + ropts' = case value_ ropts of + Just (AtEnd _) -> ropts''{value_=Nothing} + _ -> ropts'' where ropts'' = ropts{period_=precedingperiod, no_elide_=accountlistmode_ ropts == ALTree} -- q projected back before the report start date. @@ -314,16 +316,18 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col -- starting-balance-based historical balances. rowbals name changes = dbg5 "rowbals" $ case balancetype_ ropts of PeriodChange -> changeamts - CumulativeChange -> cumulative + CumulativeChange -> cumulativeSum avalue nullacct changeamts HistoricalBalance -> historical where + -- changes to report on: usually just the changes itself, but use the + -- differences in the historical amount for ValueChangeReports. + changeamts = case reporttype_ ropts of + ChangeReport -> M.mapWithKey avalue changes + BudgetReport -> M.mapWithKey avalue changes + ValueChangeReport -> periodChanges valuedStart historical historical = cumulativeSum avalue startingBalance changes - cumulative = cumulativeSum avalue nullacct changes - changeamts = if changingValuation ropts - then periodChanges nullacct cumulative - else changes - startingBalance = HM.lookupDefault nullacct name startbals + valuedStart = avalue (DateSpan Nothing historicalDate) startingBalance -- Transpose to get each account's balance changes across all columns, then -- pad with zeros @@ -334,6 +338,7 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col (pvalue, avalue) = postingAndAccountValuations rspec j priceoracle addElided = if queryDepth (rsQuery rspec) == Just 0 then HM.insert "..." zeros else id + historicalDate = minimumMay $ mapMaybe spanStart colspans zeros = M.fromList [(span, nullacct) | span <- colspans] colspans = M.keys colps @@ -574,13 +579,13 @@ cumulativeSum value start = snd . M.mapAccumWithKey accumValued start -- MultiBalanceReport. postingAndAccountValuations :: ReportSpec -> Journal -> PriceOracle -> (DateSpan -> Posting -> Posting, DateSpan -> Account -> Account) -postingAndAccountValuations rspec@ReportSpec{rsOpts=ropts} j priceoracle - | changingValuation ropts = (const id, avalue' (cost_ ropts) (value_ ropts)) - | otherwise = (pvalue' (cost_ ropts) (value_ ropts), const id) +postingAndAccountValuations ReportSpec{rsToday=today, rsOpts=ropts} j priceoracle = case value_ ropts of + Just (AtEnd _) -> (const id, avalue' (cost_ ropts) (value_ ropts)) + _ -> (pvalue' (cost_ ropts) (value_ ropts), const id) where avalue' c v span a = a{aibalance = value (aibalance a), aebalance = value (aebalance a)} - where value = mixedAmountApplyCostValuation priceoracle styles (end span) (rsToday rspec) (error "multiBalanceReport: did not expect amount valuation to be called ") c v -- PARTIAL: should not happen - pvalue' c v span = postingApplyCostValuation priceoracle styles (end span) (rsToday rspec) c v + where value = mixedAmountApplyCostValuation priceoracle styles (end span) today (error "multiBalanceReport: did not expect amount valuation to be called ") c v -- PARTIAL: should not happen + pvalue' c v span = postingApplyCostValuation priceoracle styles (end span) today c v end = fromMaybe (error "multiBalanceReport: expected all spans to have an end date") -- XXX should not happen . fmap (addDays (-1)) . spanEnd styles = journalCommodityStyles j diff --git a/hledger-lib/Hledger/Reports/PostingsReport.hs b/hledger-lib/Hledger/Reports/PostingsReport.hs index 715f62f4a..9e4e07760 100644 --- a/hledger-lib/Hledger/Reports/PostingsReport.hs +++ b/hledger-lib/Hledger/Reports/PostingsReport.hs @@ -80,9 +80,9 @@ postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items -- Postings, or summary postings with their subperiod's end date, to be displayed. displayps :: [(Posting, Maybe Day)] - | multiperiod && changingValuation ropts = [(pvalue lastday p, Just periodend) | (p, periodend) <- summariseps reportps, let lastday = addDays (-1) periodend] - | multiperiod = [(p, Just periodend) | (p, periodend) <- summariseps valuedps] - | otherwise = [(p, Nothing) | p <- valuedps] + | multiperiod, Just (AtEnd _) <- value_ = [(pvalue lastday p, Just periodend) | (p, periodend) <- summariseps reportps, let lastday = addDays (-1) periodend] + | multiperiod = [(p, Just periodend) | (p, periodend) <- summariseps valuedps] + | otherwise = [(p, Nothing) | p <- valuedps] where summariseps = summarisePostingsByInterval interval_ whichdate mdepth showempty reportspan valuedps = map (pvalue reportorjournallast) reportps diff --git a/hledger-lib/Hledger/Reports/ReportOptions.hs b/hledger-lib/Hledger/Reports/ReportOptions.hs index 4855ca76d..4443b3fc9 100644 --- a/hledger-lib/Hledger/Reports/ReportOptions.hs +++ b/hledger-lib/Hledger/Reports/ReportOptions.hs @@ -11,6 +11,7 @@ Options common to most hledger reports. module Hledger.Reports.ReportOptions ( ReportOpts(..), ReportSpec(..), + ReportType(..), BalanceType(..), AccountListMode(..), ValuationType(..), @@ -23,7 +24,6 @@ module Hledger.Reports.ReportOptions ( rawOptsToReportSpec, flat_, tree_, - changingValuation, reportOptsToggleStatus, simplifyStatuses, whichDateFromOpts, @@ -61,8 +61,16 @@ import Hledger.Query import Hledger.Utils --- | Which "balance" is being shown in a balance report. -data BalanceType = PeriodChange -- ^ The change of balance in each period. +-- | What is calculated and shown in each cell in a balance report. +data ReportType = ChangeReport -- ^ The sum of posting amounts. + | BudgetReport -- ^ The sum of posting amounts and the goal. + | ValueChangeReport -- ^ The change of value of period-end historical values. + deriving (Eq, Show) + +instance Default ReportType where def = ChangeReport + +-- | Which "accumulation method" is being shown in a balance report. +data BalanceType = PeriodChange -- ^ The accumulate change over a single period. | CumulativeChange -- ^ The accumulated change across multiple periods. | HistoricalBalance -- ^ The historical ending balance, including the effect of -- all postings before the report period. Unless altered by, @@ -102,6 +110,7 @@ data ReportOpts = ReportOpts { -- for account transactions reports (aregister) ,txn_dates_ :: Bool -- for balance reports (bal, bs, cf, is) + ,reporttype_ :: ReportType ,balancetype_ :: BalanceType ,accountlistmode_ :: AccountListMode ,drop_ :: Int @@ -148,6 +157,7 @@ defreportopts = ReportOpts , average_ = False , related_ = False , txn_dates_ = False + , reporttype_ = def , balancetype_ = def , accountlistmode_ = ALFlat , drop_ = 0 @@ -196,6 +206,7 @@ rawOptsToReportOpts rawopts = do ,average_ = boolopt "average" rawopts ,related_ = boolopt "related" rawopts ,txn_dates_ = boolopt "txn-dates" rawopts + ,reporttype_ = reporttypeopt rawopts ,balancetype_ = balancetypeopt rawopts ,accountlistmode_ = accountlistmodeopt rawopts ,drop_ = posintopt "drop" rawopts @@ -212,7 +223,16 @@ rawOptsToReportOpts rawopts = do ,forecast_ = forecastPeriodFromRawOpts d rawopts ,transpose_ = boolopt "transpose" rawopts } - return reportopts + + adjustReportDefaults reportopts + +-- | Warn users about option combinations which produce uninteresting results. +adjustReportDefaults :: ReportOpts -> IO ReportOpts +adjustReportDefaults ropts = case reporttype_ ropts of + ValueChangeReport -> case fromMaybe (AtEnd Nothing) $ value_ ropts of + v@(AtEnd _) -> return ropts{value_=Just v} -- Set value_ to AtEnd by default, unless overridden + _ -> fail "--valuechange only produces sensible results with --value=end" + _ -> return ropts -- | The result of successfully parsing a ReportOpts on a particular -- Day. Any ambiguous dates are completed and Queries are parsed, @@ -275,6 +295,15 @@ accountlistmodeopt = "flat" -> Just ALFlat _ -> Nothing +reporttypeopt :: RawOpts -> ReportType +reporttypeopt = + fromMaybe ChangeReport . choiceopt parse where + parse = \case + "change" -> Just ChangeReport + "valuechange" -> Just ValueChangeReport + "budget" -> Just BudgetReport + _ -> Nothing + balancetypeopt :: RawOpts -> BalanceType balancetypeopt = fromMaybe PeriodChange . choiceopt parse where @@ -478,13 +507,6 @@ queryFromFlags ReportOpts{..} = simplifyQuery $ And flagsq consIf f b = if b then (f True:) else id consJust f = maybe id ((:) . f) --- | Whether the market price for postings might change when reported in --- different report periods. -changingValuation :: ReportOpts -> Bool -changingValuation ropts = case value_ ropts of - Just (AtEnd _) -> True - _ -> False - -- Report dates. -- | The effective report span is the start and end dates specified by diff --git a/hledger/Hledger/Cli/Commands/Balance.hs b/hledger/Hledger/Cli/Commands/Balance.hs index 83b856637..24d1555e3 100644 --- a/hledger/Hledger/Cli/Commands/Balance.hs +++ b/hledger/Hledger/Cli/Commands/Balance.hs @@ -280,7 +280,14 @@ import Hledger.Read.CsvReader (CSV, printCSV) -- | Command line options for this command. balancemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Balance.txt") - ([flagNone ["periodic"] (setboolopt "periodic") + ([flagNone ["change"] (setboolopt "change") + "show sum of posting amounts (default)" + ,flagNone ["valuechange"] (setboolopt "valuechange") + "show change of value of period-end historical balances" + ,flagNone ["budget"] (setboolopt "budget") + "show sum of posting amounts compared to budget goals defined by periodic transactions\n " + + ,flagNone ["periodic"] (setboolopt "periodic") "accumulate amounts from column start to column end (in multicolumn reports, default)" ,flagNone ["cumulative"] (setboolopt "cumulative") "accumulate amounts from report start (specified by e.g. -b/--begin) to column end" @@ -299,7 +306,6 @@ balancemode = hledgerCommandMode ,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total" ,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign" ,flagNone ["transpose"] (setboolopt "transpose") "transpose rows and columns" - ,flagNone ["budget"] (setboolopt "budget") "show performance compared to budget goals defined by periodic transactions" ,outputFormatFlag ["txt","html","csv","json"] ,outputFileFlag ] @@ -310,13 +316,8 @@ balancemode = hledgerCommandMode -- | The balance command, prints a balance report. balance :: CliOpts -> Journal -> IO () -balance opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do - let ropts@ReportOpts{..} = rsOpts rspec - budget = boolopt "budget" rawopts - multiperiod = interval_ /= NoInterval - fmt = outputFormatFromOpts opts - - if budget then do -- single or multi period budget report +balance opts@CliOpts{reportspec_=rspec} j = case reporttype_ of + BudgetReport -> do -- single or multi period budget report let reportspan = reportSpan j rspec budgetreport = budgetReport rspec assrt reportspan j where @@ -328,8 +329,7 @@ balance opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do _ -> error' $ unsupportedOutputFormatError fmt writeOutputLazyText opts $ render budgetreport - else - if multiperiod then do -- multi period balance report + _ | multiperiod -> do -- multi period balance report let report = multiBalanceReport rspec j render = case fmt of "txt" -> multiBalanceReportAsText ropts @@ -339,7 +339,7 @@ balance opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do _ -> const $ error' $ unsupportedOutputFormatError fmt -- PARTIAL: writeOutputLazyText opts $ render report - else do -- single period simple balance report + _ -> do -- single period simple balance report let report = balanceReport rspec j -- simple Ledger-style balance report render = case fmt of "txt" -> \ropts -> TB.toLazyText . balanceReportAsText ropts @@ -348,6 +348,10 @@ balance opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do "json" -> const $ (<>"\n") . toJsonText _ -> error' $ unsupportedOutputFormatError fmt -- PARTIAL: writeOutputLazyText opts $ render ropts report + where + ropts@ReportOpts{..} = rsOpts rspec + multiperiod = interval_ /= NoInterval + fmt = outputFormatFromOpts opts -- XXX this allows rough HTML rendering of a flat BalanceReport, but it can't handle tree mode etc. -- -- | Convert a BalanceReport to a MultiBalanceReport. @@ -594,11 +598,12 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $ where title = mtitle <> " in " <> showDateSpan (periodicReportSpan r) <> valuationdesc <> ":" - mtitle = case balancetype_ of - PeriodChange | changingValuation -> "Period-end value changes" - PeriodChange -> "Balance changes" - CumulativeChange -> "Ending balances (cumulative)" - HistoricalBalance -> "Ending balances (historical)" + mtitle = case (reporttype_, balancetype_) of + (ValueChangeReport, PeriodChange ) -> "Period-end value changes" + (ValueChangeReport, CumulativeChange ) -> "Cumulative period-end value changes" + (_, PeriodChange ) -> "Balance changes" + (_, CumulativeChange ) -> "Ending balances (cumulative)" + (_, HistoricalBalance) -> "Ending balances (historical)" valuationdesc = (case cost_ of Cost -> ", converted to cost" @@ -611,9 +616,10 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $ Just (AtDate d _mc) -> ", valued at " <> showDate d Nothing -> "") - changingValuation = case (balancetype_, value_) of - (PeriodChange, Just (AtEnd _)) -> interval_ /= NoInterval - _ -> False + changingValuation = case (reporttype_, balancetype_) of + (ValueChangeReport, PeriodChange) -> True + (ValueChangeReport, CumulativeChange) -> True + _ -> False -- | Build a 'Table' from a multi-column balance report. balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text MixedAmount diff --git a/hledger/Hledger/Cli/CompoundBalanceCommand.hs b/hledger/Hledger/Cli/CompoundBalanceCommand.hs index cfcf3b5a8..e18663aed 100644 --- a/hledger/Hledger/Cli/CompoundBalanceCommand.hs +++ b/hledger/Hledger/Cli/CompoundBalanceCommand.hs @@ -61,7 +61,14 @@ compoundBalanceCommandMode :: CompoundBalanceCommandSpec -> Mode RawOpts compoundBalanceCommandMode CompoundBalanceCommandSpec{..} = hledgerCommandMode cbcdoc - ([flagNone ["periodic"] (setboolopt "periodic") + ([flagNone ["change"] (setboolopt "change") + "show sum of posting amounts (default)" + ,flagNone ["valuechange"] (setboolopt "valuechange") + "show change of value of period-end historical balances" + ,flagNone ["budget"] (setboolopt "budget") + "show sum of posting amounts compared to budget goals defined by periodic transactions\n " + + ,flagNone ["periodic"] (setboolopt "periodic") ("accumulate amounts from column start to column end (in multicolumn reports)" ++ defType PeriodChange) ,flagNone ["cumulative"] (setboolopt "cumulative") @@ -132,6 +139,7 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r `spanDefaultsFrom` journalDateSpan date2_ j -- when user overrides, add an indication to the report title + -- Do we need to deal with overridden ReportType? mtitleclarification = flip fmap mBalanceTypeOverride $ \case PeriodChange | changingValuation -> "(Period-End Value Changes)" PeriodChange -> "(Balance Changes)" @@ -150,9 +158,10 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r Just (AtDate today _mc) -> ", valued at " <> showDate today Nothing -> "") - changingValuation = case (balancetype_, value_) of - (PeriodChange, Just (AtEnd _)) -> interval_ /= NoInterval - _ -> False + changingValuation = case (reporttype_, balancetype_) of + (ValueChangeReport, PeriodChange) -> True + (ValueChangeReport, CumulativeChange) -> True + _ -> False -- make a CompoundBalanceReport. cbr' = compoundBalanceReport rspec{rsOpts=ropts'} j cbcqueries diff --git a/hledger/test/journal/valuation.test b/hledger/test/journal/valuation.test index 4088fae89..2112b267d 100644 --- a/hledger/test/journal/valuation.test +++ b/hledger/test/journal/valuation.test @@ -303,16 +303,12 @@ $ hledger -f- reg --value=cost -M # back to the original test journal: < -P 1999/01/01 A 10 B 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 -1999/01/01 - (a) 2 A @ 4 B - 2000/01/01 (a) 1 A @ 6 B @@ -390,27 +386,17 @@ Balance changes in 2000-01-01..2000-04-30, valued at posting date: ---++-------------------- || 1 B 2 B 3 B 0 -# 36. multicolumn balance report showing changes in period-end values -$ hledger -f- bal -M --value=end -b 2000 -Period-end value changes in 2000-01-01..2000-04-30: - - || Jan Feb Mar Apr -===++===================== - a || 5 B -1 B 5 B 3 B ----++--------------------- - || 5 B -1 B 5 B 3 B - -# 37. multicolumn balance report showing changes in period-end values with -T or -A +# 36. multicolumn balance report showing changes in period-end values with -T or -A $ hledger -f- bal -MTA --value=end -b 2000 -Period-end value changes in 2000-01-01..2000-04-30: +Balance changes in 2000-01-01..2000-04-30, valued at period ends: - || Jan Feb Mar Apr Total Average -===++======================================= - a || 5 B -1 B 5 B 3 B 12 B 3 B ----++--------------------------------------- - || 5 B -1 B 5 B 3 B 12 B 3 B + || Jan Feb Mar Apr Total Average +===++====================================== + a || 5 B 2 B 3 B 0 10 B 2 B +---++-------------------------------------- + || 5 B 2 B 3 B 0 10 B 2 B -# 38. multicolumn balance report valued at other date +# 37. multicolumn balance report valued at other date $ hledger -f- bal -MTA --value=2000-01-15 -b 2000 Balance changes in 2000-01-01..2000-04-30, valued at 2000-01-15: @@ -420,7 +406,7 @@ Balance changes in 2000-01-01..2000-04-30, valued at 2000-01-15: ---++-------------------------------------- || 5 B 5 B 5 B 0 15 B 4 B -# 39. multicolumn balance report valued today (with today >= 2000-04-01) +# 38. multicolumn balance report valued today (with today >= 2000-04-01) $ hledger -f- bal -M --value=now -b 2000 Balance changes in 2000-01-01..2000-04-30, current value: @@ -430,19 +416,19 @@ Balance changes in 2000-01-01..2000-04-30, current value: ---++-------------------- || 4 B 4 B 4 B 0 -# 40. multicolumn balance report showing changes in period-end values (same as --value=end) +# 39. multicolumn balance report showing changes in period-end values (same as --value=end) $ hledger -f- bal -M -V -b 2000 -Period-end value changes in 2000-01-01..2000-04-30: +Balance changes in 2000-01-01..2000-04-30, valued at period ends: - || Jan Feb Mar Apr -===++===================== - a || 5 B -1 B 5 B 3 B ----++--------------------- - || 5 B -1 B 5 B 3 B + || Jan Feb Mar Apr +===++==================== + a || 5 B 2 B 3 B 0 +---++-------------------- + || 5 B 2 B 3 B 0 # balance, periodic, with -H (starting balance and accumulating across periods) -# 41. multicolumn balance report with -H, valued at cost. +# 40. multicolumn balance report with -H, valued at cost. # The starting balance on 2000/01/01 is 14 B (cost of the first 8A). # February adds 1 A costing 7 B, making 21 B. # March adds 1 A costing 8 B, making 29 B. @@ -451,36 +437,36 @@ Ending balances (historical) in 2000-02-01..2000-04-30, converted to cost: || 2000-02-29 2000-03-31 2000-04-30 ===++==================================== - a || 21 B 29 B 29 B + a || 13 B 21 B 21 B ---++------------------------------------ - || 21 B 29 B 29 B + || 13 B 21 B 21 B -# 42. multicolumn balance report with -H valued at period end. -# The starting balance is 3 A. -# February adds 1 A making 4 A, which is valued at 2000/02/29 as 8 B. -# March adds 1 A making 5 A, which is valued at 2000/03/31 as 15 B. -# April adds 0 A making 5 A, which is valued at 2000/04/31 as 20 B. +# 41. multicolumn balance report with -H valued at period end. +# The starting balance is 1 A. +# February adds 1 A making 2 A, which is valued at 2000/02/29 as 4 B. +# March adds 1 A making 3 A, which is valued at 2000/03/31 as 9 B. +# April adds 0 A making 3 A, which is valued at 2000/04/30 as 12 B. $ hledger -f- bal -MA -H -b 200002 --value=end Ending balances (historical) in 2000-02-01..2000-04-30, valued at period ends: || 2000-02-29 2000-03-31 2000-04-30 Average ===++============================================= - a || 8 B 15 B 20 B 14 B + a || 4 B 9 B 12 B 8 B ---++--------------------------------------------- - || 8 B 15 B 20 B 14 B + || 4 B 9 B 12 B 8 B -# 43. multicolumn balance report with -H valued at other date. +# 42. multicolumn balance report with -H valued at other date. # The starting balance is 15 B (3 A valued at 2000/1/15). $ hledger -f- bal -M -H -b 200002 --value=2000-01-15 Ending balances (historical) in 2000-02-01..2000-04-30, valued at 2000-01-15: || 2000-02-29 2000-03-31 2000-04-30 ===++==================================== - a || 20 B 25 B 25 B + a || 10 B 15 B 15 B ---++------------------------------------ - || 20 B 25 B 25 B + || 10 B 15 B 15 B -# 44. multicolumn balance report with -H, valuing each period's carried-over balances at cost. +# 43. multicolumn balance report with -H, valuing each period's carried-over balances at cost. < P 2000/01/01 A 1 B P 2000/01/15 A 5 B @@ -500,7 +486,7 @@ Ending balances (historical) in 2000Q1, converted to cost: ---++------------------------------------ || 6 B 6 B 6 B -# 45. multicolumn balance report with -H, valuing each period's carried-over balances at period end. +# 44. multicolumn balance report with -H, valuing each period's carried-over balances at period end. # Unrelated, also -H always disables -T. $ hledger -f- bal -META -H -p200001-200004 --value=e Ending balances (historical) in 2000Q1, valued at period ends: @@ -511,7 +497,7 @@ Ending balances (historical) in 2000Q1, valued at period ends: ---++--------------------------------------------- || 5 B 2 B 3 B 3 B -# 46. multicolumn balance report with -H, valuing each period's carried-over balances at other date. +# 45. multicolumn balance report with -H, valuing each period's carried-over balances at other date. $ hledger -f- bal -ME -H -p200001-200004 --value=2000-01-15 Ending balances (historical) in 2000Q1, valued at 2000-01-15: @@ -543,7 +529,7 @@ P 2000/04/01 A 4 B 2000/03/01 (a) 1 A @ 8 B -# 47. budget report, unvalued (for reference). +# 46. budget report, unvalued (for reference). $ hledger -f- bal -M --budget Budget performance in 2000-01-01..2000-04-30: @@ -553,7 +539,7 @@ Budget performance in 2000-01-01..2000-04-30: ---++--------------------------------------------------------------------- || 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A] 0 [0% of 2 A] -# 48. budget report, valued at cost. +# 47. budget report, valued at cost. $ hledger -f- bal -MTA --budget --value=c Budget performance in 2000-01-01..2000-04-30, converted to cost: @@ -563,17 +549,17 @@ Budget performance in 2000-01-01..2000-04-30, converted to cost: ---++--------------------------------------------------------------------------------------------------------------- || 6 B [300% of 2 B] 7 B [350% of 2 B] 8 B [400% of 2 B] 0 [0% of 2 B] 21 B [262% of 8 B] 5 B [262% of 2 B] -# 49. budget report, showing changes in period-end values. +# 48. budget report, showing changes in period-end values. $ hledger -f- bal -MTA --budget --value=e Budget performance in 2000-01-01..2000-04-30, valued at period ends: - || Jan Feb Mar Apr Total Average -===++=================================================================================================================== - a || 5 B [50% of 10 B] -1 B [50% of -2 B] 5 B [50% of 10 B] 3 B [21% of 14 B] 12 B [38% of 32 B] 3 B [38% of 8 B] ----++------------------------------------------------------------------------------------------------------------------- - || 5 B [50% of 10 B] -1 B [50% of -2 B] 5 B [50% of 10 B] 3 B [21% of 14 B] 12 B [38% of 32 B] 3 B [38% of 8 B] + || Jan Feb Mar Apr Total Average +===++============================================================================================================ + a || 5 B [50% of 10 B] 2 B [50% of 4 B] 3 B [50% of 6 B] 0 [0% of 8 B] 10 B [36% of 28 B] 2 B [36% of 7 B] +---++------------------------------------------------------------------------------------------------------------ + || 5 B [50% of 10 B] 2 B [50% of 4 B] 3 B [50% of 6 B] 0 [0% of 8 B] 10 B [36% of 28 B] 2 B [36% of 7 B] -# 50. budget report, valued at other date. +# 49. budget report, valued at other date. $ hledger -f- bal -MTA --budget --value=2000-01-15 Budget performance in 2000-01-01..2000-04-30, valued at 2000-01-15: @@ -583,7 +569,7 @@ Budget performance in 2000-01-01..2000-04-30, valued at 2000-01-15: ---++---------------------------------------------------------------------------------------------------------------- || 5 B [50% of 10 B] 5 B [50% of 10 B] 5 B [50% of 10 B] 0 [0% of 10 B] 15 B [38% of 40 B] 4 B [38% of 10 B] -# 51. --value=then with --historical. The starting total is valued individually for each posting at its posting time. +# 50. --value=then with --historical. The starting total is valued individually for each posting at its posting time. < P 2020-01-01 A 1 B P 2020-02-01 A 2 B @@ -607,7 +593,7 @@ $ hledger -f- reg --value=then -b 2020-03 -H 2020-04-01 (a) 4 B 10 B >=0 -# 52. --value=then with a report interval. Summary amounts are the sums of the +# 51. --value=then with a report interval. Summary amounts are the sums of the # values of each posting at their posting date. < P 2020-01-01 A 1 B @@ -632,7 +618,7 @@ $ hledger -f- reg --value=then -Q 2020Q2 a 4 B 10 B >=0 -# 53. print --value should affect all postings, including when there's an implicit transaction price +# 52. print --value should affect all postings, including when there's an implicit transaction price < P 2020-01-01 A 1 C P 2020-01-01 B 1 C diff --git a/hledger/test/journal/valuechange.test b/hledger/test/journal/valuechange.test new file mode 100644 index 000000000..2c76dd2e5 --- /dev/null +++ b/hledger/test/journal/valuechange.test @@ -0,0 +1,55 @@ +< +P 1999/01/01 A 10 B +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 + +1999/01/01 + (a) 2 A @ 4 B + +2000/01/01 + (a) 1 A @ 6 B + +2000/02/01 + (a) 1 A @ 7 B + +2000/03/01 + (a) 1 A @ 8 B + +# 1. multicolumn balance report showing changes in period-end values +# Initial balance 2 A, valued at 10 B each, total 20 B +# 1 A added in Jan, total 3 A, valued at 5 B, total 15 B, change -5 B +# 1 A added in Feb, total 4 A, valued at 2 B, total 8 B, change -7 B +# 1 A added in Mar, total 5 A, valued at 3 B, total 15 B, change 7 B +# 0 A added in Apr, total 5 A, valued at 4 B, total 20 B, change 5 B +$ hledger -f- bal -M --valuechange -b 2000 +Period-end value changes in 2000-01-01..2000-04-30: + + || Jan Feb Mar Apr +===++====================== + a || -5 B -7 B 7 B 5 B +---++---------------------- + || -5 B -7 B 7 B 5 B + +# 2. Cumulative multicolumn balance report showing changes in period-end values +$ hledger -f- bal -M --valuechange --cumulative -b 2000 +Cumulative period-end value changes in 2000-01-01..2000-04-30: + + || 2000-01-31 2000-02-29 2000-03-31 2000-04-30 +===++================================================ + a || -5 B -12 B -5 B 0 +---++------------------------------------------------ + || -5 B -12 B -5 B 0 + +# 3. Historical multicolumn balance report showing changes in period-end values is +# the same as a historical report +$ hledger -f- bal -M --valuechange --historical -b 2000 +Ending balances (historical) in 2000-01-01..2000-04-30, valued at period ends: + + || 2000-01-31 2000-02-29 2000-03-31 2000-04-30 +===++================================================ + a || 15 B 8 B 15 B 20 B +---++------------------------------------------------ + || 15 B 8 B 15 B 20 B