lib: Do not include price directives in journalDateSpan. Only include

price directives after the last transaction/posting date if using
--value=end.

Also enlarges the reportspan to encompass full intervals for budget
goals.
This commit is contained in:
Stephen Morgan 2021-03-02 21:32:52 +11:00 committed by Simon Michael
parent ff5e810c78
commit edaaef897b
6 changed files with 144 additions and 138 deletions

View File

@ -58,6 +58,7 @@ module Hledger.Data.Journal (
journalPayeesDeclaredOrUsed, journalPayeesDeclaredOrUsed,
journalCommoditiesDeclared, journalCommoditiesDeclared,
journalDateSpan, journalDateSpan,
journalDateSpanBothDates,
journalStartDate, journalStartDate,
journalEndDate, journalEndDate,
journalDescriptions, journalDescriptions,
@ -106,14 +107,14 @@ import qualified Data.HashTable.ST.Cuckoo as H
import Data.List (find, foldl', sortOn) import Data.List (find, foldl', sortOn)
import Data.List.Extra (nubSort) import Data.List.Extra (nubSort)
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import Data.Maybe (catMaybes, fromJust, fromMaybe, isJust, mapMaybe) import Data.Maybe (catMaybes, fromJust, fromMaybe, isJust, mapMaybe, maybeToList)
#if !(MIN_VERSION_base(4,11,0)) #if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup (Semigroup(..)) import Data.Semigroup (Semigroup(..))
#endif #endif
import qualified Data.Set as S import qualified Data.Set as S
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Safe (headMay, headDef) import Safe (headMay, headDef, maximumMay, minimumMay)
import Data.Time.Calendar (Day, addDays, fromGregorian) import Data.Time.Calendar (Day, addDays, fromGregorian)
import Data.Tree (Tree, flatten) import Data.Tree (Tree, flatten)
import System.Time (ClockTime(TOD)) import System.Time (ClockTime(TOD))
@ -1286,23 +1287,34 @@ journalStyleInfluencingAmounts j =
-- | The fully specified date span enclosing the dates (primary or secondary) -- | The fully specified date span enclosing the dates (primary or secondary)
-- of all this journal's transactions and postings, or DateSpan Nothing Nothing -- of all this journal's transactions and postings, or DateSpan Nothing Nothing
-- if there are none. -- if there are none.
--
-- This will include the dates of any price directives that come after the last
-- posting/transaction, but not those that come before the first.
journalDateSpan :: Bool -> Journal -> DateSpan journalDateSpan :: Bool -> Journal -> DateSpan
journalDateSpan secondary j journalDateSpan False = journalDateSpanHelper $ Just PrimaryDate
| null ts = DateSpan Nothing Nothing journalDateSpan True = journalDateSpanHelper $ Just SecondaryDate
| otherwise = DateSpan (Just earliest) (Just $ addDays 1 latest)
where -- | The fully specified date span enclosing the dates (primary and secondary)
earliest = minimumStrict dates -- of all this journal's transactions and postings, or DateSpan Nothing Nothing
latest = case ddates of -- if there are none.
[] -> maximumStrict dates journalDateSpanBothDates :: Journal -> DateSpan
_ -> max (maximumStrict ddates) (maximumStrict dates) -- Include commodity price directives in journal end journalDateSpanBothDates = journalDateSpanHelper Nothing
dates = pdates ++ tdates
tdates = map (if secondary then transactionDate2 else tdate) ts -- | A helper for journalDateSpan which takes Maybe WhichDate directly. Nothing
pdates = concatMap (mapMaybe (if secondary then (Just . postingDate2) else pdate) . tpostings) ts -- uses both primary and secondary dates.
ddates = map pddate $ jpricedirectives j journalDateSpanHelper :: Maybe WhichDate -> Journal -> DateSpan
ts = jtxns j journalDateSpanHelper whichdate j =
DateSpan (minimumMay dates) (addDays 1 <$> maximumMay dates)
where
dates = pdates ++ tdates
tdates = concatMap gettdate ts
pdates = concatMap getpdate $ concatMap tpostings ts
ts = jtxns j
gettdate t = case whichdate of
Just PrimaryDate -> [tdate t]
Just SecondaryDate -> [fromMaybe (tdate t) $ tdate2 t]
Nothing -> tdate t : maybeToList (tdate2 t)
getpdate p = case whichdate of
Just PrimaryDate -> maybeToList $ pdate p
Just SecondaryDate -> maybeToList $ pdate2 p <|> pdate p
Nothing -> catMaybes [pdate p, pdate2 p]
-- | The earliest of this journal's transaction and posting dates, or -- | The earliest of this journal's transaction and posting dates, or
-- Nothing if there are none. -- Nothing if there are none.

View File

@ -23,7 +23,6 @@ module Hledger.Reports.MultiBalanceReport (
sortRowsLike, sortRowsLike,
-- * Helper functions -- * Helper functions
calculateReportSpan,
makeReportQuery, makeReportQuery,
getPostingsByColumn, getPostingsByColumn,
getPostings, getPostings,
@ -50,7 +49,7 @@ import Data.Semigroup ((<>))
#endif #endif
import Data.Semigroup (sconcat) import Data.Semigroup (sconcat)
import Data.Time.Calendar (Day, addDays, fromGregorian) import Data.Time.Calendar (Day, addDays, fromGregorian)
import Safe (headMay, lastDef, lastMay, minimumMay) import Safe (lastDef, minimumMay)
import Hledger.Data import Hledger.Data
import Hledger.Query import Hledger.Query
@ -112,7 +111,7 @@ multiBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> MultiBalanceRe
multiBalanceReportWith rspec' j priceoracle = report multiBalanceReportWith rspec' j priceoracle = report
where where
-- Queries, report/column dates. -- Queries, report/column dates.
reportspan = dbg3 "reportspan" $ calculateReportSpan rspec' j reportspan = dbg3 "reportspan" $ reportSpan j rspec'
rspec = dbg3 "reportopts" $ makeReportQuery rspec' reportspan rspec = dbg3 "reportopts" $ makeReportQuery rspec' reportspan
-- Group postings into their columns. -- Group postings into their columns.
@ -140,7 +139,7 @@ compoundBalanceReportWith :: ReportSpec -> Journal -> PriceOracle
compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr
where where
-- Queries, report/column dates. -- Queries, report/column dates.
reportspan = dbg3 "reportspan" $ calculateReportSpan rspec' j reportspan = dbg3 "reportspan" $ reportSpan j rspec'
rspec = dbg3 "reportopts" $ makeReportQuery rspec' reportspan rspec = dbg3 "reportopts" $ makeReportQuery rspec' reportspan
-- Group postings into their columns. -- Group postings into their columns.
@ -215,26 +214,6 @@ startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle repo
DateSpan Nothing Nothing -> emptydatespan DateSpan Nothing Nothing -> emptydatespan
a -> a a -> a
-- | Calculate the span of the report to be generated.
calculateReportSpan :: ReportSpec -> Journal -> DateSpan
calculateReportSpan ReportSpec{rsQuery=query,rsOpts=ropts} j = reportspan
where
-- The date span specified by -b/-e/-p options and query args if any.
requestedspan = dbg3 "requestedspan" $ queryDateSpan (date2_ ropts) query
-- If the requested span is open-ended, close it using the journal's start and end dates.
-- This can still be the null (open) span if the journal is empty.
requestedspan' = dbg3 "requestedspan'" $
requestedspan `spanDefaultsFrom` journalDateSpan (date2_ ropts) j
-- The list of interval spans enclosing the requested span.
-- This list can be empty if the journal was empty,
-- or if hledger-ui has added its special date:-tomorrow to the query
-- and all txns are in the future.
intervalspans = dbg3 "intervalspans" $ splitSpan (interval_ ropts) requestedspan'
-- The requested span enlarged to enclose a whole number of intervals.
-- This can be the null span if there were no intervals.
reportspan = DateSpan (spanStart =<< headMay intervalspans)
(spanEnd =<< lastMay intervalspans)
-- | Remove any date queries and insert queries from the report span. -- | Remove any date queries and insert queries from the report span.
-- The user's query expanded to the report span -- The user's query 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

View File

@ -65,7 +65,7 @@ type SummaryPosting = (Posting, Day)
postingsReport :: ReportSpec -> Journal -> PostingsReport postingsReport :: ReportSpec -> Journal -> PostingsReport
postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items
where where
reportspan = adjustReportDates rspec j reportspan = reportSpanBothDates j rspec
whichdate = whichDateFromOpts ropts whichdate = whichDateFromOpts ropts
mdepth = queryDepth $ rsQuery rspec mdepth = queryDepth $ rsQuery rspec
styles = journalCommodityStyles j styles = journalCommodityStyles j
@ -124,26 +124,6 @@ registerRunningCalculationFn ropts
| average_ ropts = \i avg amt -> avg + divideMixedAmount (fromIntegral i) (amt - avg) | average_ ropts = \i avg amt -> avg + divideMixedAmount (fromIntegral i) (amt - avg)
| otherwise = \_ bal amt -> bal + amt | otherwise = \_ bal amt -> bal + amt
-- | Adjust report start/end dates to more useful ones based on
-- journal data and report intervals. Ie:
-- 1. If the start date is unspecified, use the earliest date in the journal (if any)
-- 2. If the end date is unspecified, use the latest date in the journal (if any)
-- 3. If a report interval is specified, enlarge the dates to enclose whole intervals
adjustReportDates :: ReportSpec -> Journal -> DateSpan
adjustReportDates rspec@ReportSpec{rsOpts=ropts} j = reportspan
where
-- see also multiBalanceReport
requestedspan = dbg3 "requestedspan" $ queryDateSpan' $ rsQuery rspec -- span specified by -b/-e/-p options and query args
journalspan = dbg3 "journalspan" $ dates `spanUnion` date2s -- earliest and latest dates (or date2s) in the journal
where
dates = journalDateSpan False j
date2s = journalDateSpan True j
requestedspanclosed = dbg3 "requestedspanclosed" $ requestedspan `spanDefaultsFrom` journalspan -- if open-ended, close it using the journal's dates (if any)
intervalspans = dbg3 "intervalspans" $ splitSpan (interval_ ropts) requestedspanclosed -- get the whole intervals enclosing that
mreportstart = dbg3 "reportstart" $ maybe Nothing spanStart $ headMay intervalspans -- start of the first interval, or open ended
mreportend = dbg3 "reportend" $ maybe Nothing spanEnd $ lastMay intervalspans -- end of the last interval, or open ended
reportspan = dbg3 "reportspan" $ DateSpan mreportstart mreportend -- the requested span enlarged to whole intervals if possible
-- | Find postings matching a given query, within a given date span, -- | Find postings matching a given query, within a given date span,
-- and also any similarly-matched postings before that date span. -- and also any similarly-matched postings before that date span.
-- Date restrictions and depth restrictions in the query are ignored. -- Date restrictions and depth restrictions in the query are ignored.

View File

@ -34,6 +34,7 @@ module Hledger.Reports.ReportOptions (
transactionDateFn, transactionDateFn,
postingDateFn, postingDateFn,
reportSpan, reportSpan,
reportSpanBothDates,
reportStartDate, reportStartDate,
reportEndDate, reportEndDate,
reportPeriodStart, reportPeriodStart,
@ -49,7 +50,7 @@ import Data.Maybe (fromMaybe, isJust, mapMaybe)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Time.Calendar (Day, addDays) import Data.Time.Calendar (Day, addDays)
import Data.Default (Default(..)) import Data.Default (Default(..))
import Safe (lastDef, lastMay) import Safe (headMay, lastDef, lastMay, maximumMay)
import System.Console.ANSI (hSupportsANSIColor) import System.Console.ANSI (hSupportsANSIColor)
import System.Environment (lookupEnv) import System.Environment (lookupEnv)
@ -513,13 +514,41 @@ queryFromFlags ReportOpts{..} = simplifyQuery $ And flagsq
-- options or queries, or otherwise the earliest and latest transaction or -- options or queries, or otherwise the earliest and latest transaction or
-- posting dates in the journal. If no dates are specified by options/queries -- posting dates in the journal. If no dates are specified by options/queries
-- and the journal is empty, returns the null date span. -- and the journal is empty, returns the null date span.
-- The boolean argument flags whether primary and secondary dates are considered
-- equivalently.
reportSpan :: Journal -> ReportSpec -> DateSpan reportSpan :: Journal -> ReportSpec -> DateSpan
reportSpan j ReportSpec{rsQuery=query} = dbg3 "reportspan" $ DateSpan mstartdate menddate reportSpan = reportSpanHelper False
-- | Like reportSpan, but uses both primary and secondary dates when calculating
-- the span.
reportSpanBothDates :: Journal -> ReportSpec -> DateSpan
reportSpanBothDates = reportSpanHelper True
-- | A helper for reportSpan, which takes a Bool indicating whether to use both
-- primary and secondary dates.
reportSpanHelper :: Bool -> Journal -> ReportSpec -> DateSpan
reportSpanHelper bothdates j ReportSpec{rsQuery=query, rsOpts=ropts} = reportspan
where where
DateSpan mjournalstartdate mjournalenddate = -- The date span specified by -b/-e/-p options and query args if any.
dbg3 "journalspan" $ journalDateSpan False j -- ignore secondary dates requestedspan = dbg3 "requestedspan" $ if bothdates then queryDateSpan' query else queryDateSpan (date2_ ropts) query
mstartdate = queryStartDate False query <|> mjournalstartdate -- If we are requesting period-end valuation, the journal date span should
menddate = queryEndDate False query <|> mjournalenddate -- include price directives after the last transaction
journalspan = dbg3 "journalspan" $ if bothdates then journalDateSpanBothDates j else journalDateSpan (date2_ ropts) j
pricespan = dbg3 "pricespan" . DateSpan Nothing $ case value_ ropts of
Just (AtEnd _) -> fmap (addDays 1) . maximumMay . map pddate $ jpricedirectives j
_ -> Nothing
-- If the requested span is open-ended, close it using the journal's start and end dates.
-- This can still be the null (open) span if the journal is empty.
requestedspan' = dbg3 "requestedspan'" $ requestedspan `spanDefaultsFrom` (journalspan `spanUnion` pricespan)
-- The list of interval spans enclosing the requested span.
-- This list can be empty if the journal was empty,
-- or if hledger-ui has added its special date:-tomorrow to the query
-- and all txns are in the future.
intervalspans = dbg3 "intervalspans" $ splitSpan (interval_ ropts) requestedspan'
-- The requested span enlarged to enclose a whole number of intervals.
-- This can be the null span if there were no intervals.
reportspan = dbg3 "reportspan" $ DateSpan (spanStart =<< headMay intervalspans)
(spanEnd =<< lastMay intervalspans)
reportStartDate :: Journal -> ReportSpec -> Maybe Day reportStartDate :: Journal -> ReportSpec -> Maybe Day
reportStartDate j = spanStart . reportSpan j reportStartDate j = spanStart . reportSpan j
@ -550,8 +579,13 @@ reportPeriodLastDay = fmap (addDays (-1)) . queryEndDate False . rsQuery
-- Get the last day of the overall report period, or if no report -- Get the last day of the overall report period, or if no report
-- period is specified, the last day of the journal (ie the latest -- period is specified, the last day of the journal (ie the latest
-- posting date). If there's no report period and nothing in the -- posting date). If we're doing period-end valuation, include price
-- directive dates. If there's no report period and nothing in the
-- journal, will be Nothing. -- journal, will be Nothing.
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalLastDay rspec j = reportPeriodOrJournalLastDay rspec j = reportPeriodLastDay rspec <|> journalOrPriceEnd
reportPeriodLastDay rspec <|> journalEndDate False j where
journalOrPriceEnd = case value_ $ rsOpts rspec of
Just (AtEnd _) -> max (journalEndDate False j) lastPriceDirective
_ -> journalEndDate False j
lastPriceDirective = fmap (addDays 1) . maximumMay . map pddate $ jpricedirectives j

View File

@ -158,11 +158,11 @@ Budget performance in 2018-01-01W01:
|| 2018-01-01W01 || 2018-01-01W01
===++================ ===++================
a || 2 [7% of 30] a || 2 [3% of 70]
b || 2 [2% of 100] b || 2 [2% of 100]
c || 2 [0% of 1000] c || 2 [0% of 1000]
---++---------------- ---++----------------
|| 6 [1% of 1130] || 6 [1% of 1170]
# 7. A bounded two day budget. The end date is exclusive as usual. # 7. A bounded two day budget. The end date is exclusive as usual.
< <
@ -557,11 +557,12 @@ $ hledger bal -f- --budget -TA not:income -O csv
"expenses:bills:f","$10","0","$10","0","$10","0" "expenses:bills:f","$10","0","$10","0","$10","0"
"Total:","$80","$370","$80","$370","$80","$370" "Total:","$80","$370","$80","$370","$80","$370"
# 28. You might expect this to show a budget goal in jan, feb, mar. # 28. You would expect this to show a budget goal in jan, feb, mar.
# But by the usual report date logic, which picks the oldest and newest # But by the usual report date logic, which picks the oldest and newest
# transaction date (1/15 and 3/15) as start and end date by default, # transaction date (1/15 and 3/15) as start and end date by default,
# and since "monthly" generates transactions on the 1st, # and since "monthly" generates transactions on the 1st,
# the january budget goal transaction is excluded. # the january budget goal transaction is excluded. Make sure we entend so
# they're included.
< <
~ monthly in 2020 ~ monthly in 2020
(expenses:food) $500 (expenses:food) $500
@ -577,12 +578,12 @@ $ hledger bal -f- --budget -TA not:income -O csv
$ hledger -f- bal --budget -M $ hledger -f- bal --budget -M
Budget performance in 2020Q1: Budget performance in 2020Q1:
|| Jan Feb Mar || Jan Feb Mar
===============++============================================= ===============++===========================================================
<unbudgeted> || $-400 0 $-600 <unbudgeted> || $-400 0 $-600
expenses:food || $400 0 [0% of $500] $600 [120% of $500] expenses:food || $400 [80% of $500] 0 [0% of $500] $600 [120% of $500]
---------------++--------------------------------------------- ---------------++-----------------------------------------------------------
|| 0 0 [0% of $500] 0 [ 0% of $500] || 0 [ 0% of $500] 0 [0% of $500] 0 [ 0% of $500]
# 29. Specifying the report period works around it. # 29. Specifying the report period works around it.
$ hledger -f- bal --budget -M date:2020q1 $ hledger -f- bal --budget -M date:2020q1

View File

@ -368,23 +368,23 @@ $ hledger -f- bal -N -V -b 2000
# 34. multicolumn balance report valued at cost # 34. multicolumn balance report valued at cost
$ hledger -f- bal -MTA --value=cost -b 2000 $ hledger -f- bal -MTA --value=cost -b 2000
Balance changes in 2000-01-01..2000-04-30, converted to cost: Balance changes in 2000Q1, converted to cost:
|| Jan Feb Mar Apr Total Average || Jan Feb Mar Total Average
===++====================================== ===++=================================
a || 6 B 7 B 8 B 0 21 B 5 B a || 6 B 7 B 8 B 21 B 7 B
---++-------------------------------------- ---++---------------------------------
|| 6 B 7 B 8 B 0 21 B 5 B || 6 B 7 B 8 B 21 B 7 B
# 35. multicolumn balance report valued at posting date # 35. multicolumn balance report valued at posting date
$ hledger -f- bal -M --value=then -b 2000 $ hledger -f- bal -M --value=then -b 2000
Balance changes in 2000-01-01..2000-04-30, valued at posting date: Balance changes in 2000Q1, valued at posting date:
|| Jan Feb Mar Apr || Jan Feb Mar
===++==================== ===++===============
a || 1 B 2 B 3 B 0 a || 1 B 2 B 3 B
---++-------------------- ---++---------------
|| 1 B 2 B 3 B 0 || 1 B 2 B 3 B
# 36. 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 $ hledger -f- bal -MTA --value=end -b 2000
@ -398,23 +398,23 @@ Balance changes in 2000-01-01..2000-04-30, valued at period ends:
# 37. 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 $ hledger -f- bal -MTA --value=2000-01-15 -b 2000
Balance changes in 2000-01-01..2000-04-30, valued at 2000-01-15: Balance changes in 2000Q1, valued at 2000-01-15:
|| Jan Feb Mar Apr Total Average || Jan Feb Mar Total Average
===++====================================== ===++=================================
a || 5 B 5 B 5 B 0 15 B 4 B a || 5 B 5 B 5 B 15 B 5 B
---++-------------------------------------- ---++---------------------------------
|| 5 B 5 B 5 B 0 15 B 4 B || 5 B 5 B 5 B 15 B 5 B
# 38. 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 $ hledger -f- bal -M --value=now -b 2000
Balance changes in 2000-01-01..2000-04-30, current value: Balance changes in 2000Q1, current value:
|| Jan Feb Mar Apr || Jan Feb Mar
===++==================== ===++===============
a || 4 B 4 B 4 B 0 a || 4 B 4 B 4 B
---++-------------------- ---++---------------
|| 4 B 4 B 4 B 0 || 4 B 4 B 4 B
# 39. 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 $ hledger -f- bal -M -V -b 2000
@ -432,14 +432,14 @@ Balance changes in 2000-01-01..2000-04-30, valued at period ends:
# The starting balance on 2000/01/01 is 14 B (cost of the first 8A). # 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. # February adds 1 A costing 7 B, making 21 B.
# March adds 1 A costing 8 B, making 29 B. # March adds 1 A costing 8 B, making 29 B.
$ hledger -f- bal -M -H -b 200002 --value=cost $ hledger -f- bal -M -H -b 200002 --cost
Ending balances (historical) in 2000-02-01..2000-04-30, converted to cost: Ending balances (historical) in 2000-02-01..2000-03-31, converted to cost:
|| 2000-02-29 2000-03-31 2000-04-30 || 2000-02-29 2000-03-31
===++==================================== ===++========================
a || 13 B 21 B 21 B a || 13 B 21 B
---++------------------------------------ ---++------------------------
|| 13 B 21 B 21 B || 13 B 21 B
# 41. multicolumn balance report with -H valued at period end. # 41. multicolumn balance report with -H valued at period end.
# The starting balance is 1 A. # The starting balance is 1 A.
@ -458,13 +458,13 @@ Ending balances (historical) in 2000-02-01..2000-04-30, valued at period ends:
# 42. 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). # The starting balance is 15 B (3 A valued at 2000/1/15).
$ hledger -f- bal -M -H -b 200002 --value=2000-01-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: Ending balances (historical) in 2000-02-01..2000-03-31, valued at 2000-01-15:
|| 2000-02-29 2000-03-31 2000-04-30 || 2000-02-29 2000-03-31
===++==================================== ===++========================
a || 10 B 15 B 15 B a || 10 B 15 B
---++------------------------------------ ---++------------------------
|| 10 B 15 B 15 B || 10 B 15 B
# 43. 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.
< <
@ -531,23 +531,23 @@ P 2000/04/01 A 4 B
# 46. budget report, unvalued (for reference). # 46. budget report, unvalued (for reference).
$ hledger -f- bal -M --budget $ hledger -f- bal -M --budget
Budget performance in 2000-01-01..2000-04-30: Budget performance in 2000Q1:
|| Jan Feb Mar Apr || Jan Feb Mar
===++===================================================================== ===++======================================================
a || 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A] 0 [0% of 2 A] a || 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A]
---++--------------------------------------------------------------------- ---++------------------------------------------------------
|| 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A] 0 [0% of 2 A] || 1 A [50% of 2 A] 1 A [50% of 2 A] 1 A [50% of 2 A]
# 47. budget report, valued at cost. # 47. budget report, valued at cost.
$ hledger -f- bal -MTA --budget --value=c $ hledger -f- bal -MTA --budget --value=c
Budget performance in 2000-01-01..2000-04-30, converted to cost: Budget performance in 2000Q1, converted to cost:
|| Jan Feb Mar Apr Total Average || Jan Feb Mar Total Average
===++=============================================================================================================== ===++================================================================================================
a || 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] a || 6 B [300% of 2 B] 7 B [350% of 2 B] 8 B [400% of 2 B] 21 B [350% of 6 B] 7 B [350% of 2 B]
---++--------------------------------------------------------------------------------------------------------------- ---++------------------------------------------------------------------------------------------------
|| 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] || 6 B [300% of 2 B] 7 B [350% of 2 B] 8 B [400% of 2 B] 21 B [350% of 6 B] 7 B [350% of 2 B]
# 48. budget report, showing changes in period-end values. # 48. budget report, showing changes in period-end values.
$ hledger -f- bal -MTA --budget --value=e $ hledger -f- bal -MTA --budget --value=e
@ -561,13 +561,13 @@ Budget performance in 2000-01-01..2000-04-30, valued at period ends:
# 49. budget report, valued at other date. # 49. budget report, valued at other date.
$ hledger -f- bal -MTA --budget --value=2000-01-15 $ hledger -f- bal -MTA --budget --value=2000-01-15
Budget performance in 2000-01-01..2000-04-30, valued at 2000-01-15: Budget performance in 2000Q1, valued at 2000-01-15:
|| Jan Feb Mar Apr Total Average || Jan Feb Mar Total Average
===++================================================================================================================ ===++================================================================================================
a || 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] a || 5 B [50% of 10 B] 5 B [50% of 10 B] 5 B [50% of 10 B] 15 B [50% of 30 B] 5 B [50% of 10 B]
---++---------------------------------------------------------------------------------------------------------------- ---++------------------------------------------------------------------------------------------------
|| 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] || 5 B [50% of 10 B] 5 B [50% of 10 B] 5 B [50% of 10 B] 15 B [50% of 30 B] 5 B [50% of 10 B]
# 50. --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.
< <