bal*: support --value-at in multicolumn balance reports
This commit is contained in:
parent
65934958f9
commit
00975fb226
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-}
|
{-# LANGUAGE FlexibleInstances, RecordWildCards, ScopedTypeVariables, OverloadedStrings #-}
|
||||||
{-|
|
{-|
|
||||||
|
|
||||||
Multi-column balance reports, used by the balance command.
|
Multi-column balance reports, used by the balance command.
|
||||||
@ -20,7 +20,6 @@ module Hledger.Reports.MultiBalanceReports (
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Applicative ((<|>))
|
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Ord
|
import Data.Ord
|
||||||
@ -276,39 +275,36 @@ multiBalanceReportSpan (MultiBalanceReport (colspans, _, _)) = DateSpan (spanSta
|
|||||||
-- | Convert all the posting amounts in a MultiBalanceReport to their
|
-- | Convert all the posting amounts in a MultiBalanceReport to their
|
||||||
-- default valuation commodities. This means using the Journal's most
|
-- default valuation commodities. This means using the Journal's most
|
||||||
-- recent applicable market prices before the valuation date.
|
-- recent applicable market prices before the valuation date.
|
||||||
-- The valuation date is the specified report end date if any,
|
-- The valuation date is set with --value-date and can be:
|
||||||
-- otherwise the current date, otherwise the journal's end date.
|
-- the posting date,
|
||||||
|
-- the last day in the report subperiod,
|
||||||
|
-- today's date (gives an error if today_ is not set in ReportOpts),
|
||||||
|
-- or a custom date.
|
||||||
mbrValue :: ReportOpts -> Journal -> MultiBalanceReport -> MultiBalanceReport
|
mbrValue :: ReportOpts -> Journal -> MultiBalanceReport -> MultiBalanceReport
|
||||||
mbrValue ropts j r =
|
mbrValue ReportOpts{..} Journal{..} (MultiBalanceReport (spans, rows, (coltotals, rowtotaltotal, rowavgtotal))) =
|
||||||
let mvaluationdate = periodEnd (period_ ropts) <|> today_ ropts <|> journalEndDate False j
|
MultiBalanceReport (
|
||||||
in case mvaluationdate of
|
spans
|
||||||
Nothing -> r
|
,[(acct, acct', depth, map (uncurry val) $ zip ends rowamts, val end rowtotal, val end rowavg)
|
||||||
Just d -> r'
|
| (acct, acct', depth, rowamts, rowtotal, rowavg) <- rows]
|
||||||
|
,(map (uncurry val) $ zip ends coltotals
|
||||||
|
,val end rowtotaltotal
|
||||||
|
,val end rowavgtotal)
|
||||||
|
)
|
||||||
|
where
|
||||||
|
ends = map (fromMaybe (error' "mbrValue: expected all report periods to have an end date") . spanEnd) spans -- XXX shouldn't happen
|
||||||
|
end = lastDef (error' "mbrValue: expected at least one report subperiod") ends -- XXX shouldn't happen
|
||||||
|
val periodend amt = mixedAmountValue prices d amt
|
||||||
where
|
where
|
||||||
-- prices are in parse order - sort into date then parse order,
|
-- prices are in parse order - sort into date then parse order,
|
||||||
-- & reversed for quick lookup of the latest price.
|
-- & reversed for quick lookup of the latest price.
|
||||||
prices = reverse $ sortOn mpdate $ jmarketprices j
|
prices = reverse $ sortOn mpdate jmarketprices
|
||||||
|
d = case value_at_ of
|
||||||
MultiBalanceReport (spans, rows, (coltotals, rowtotaltotal, rowavgtotal)) = r
|
AtTransaction -> error' "sorry, --value-at=transaction is not yet supported with multicolumn balance reports" -- XXX
|
||||||
r' = MultiBalanceReport
|
AtPeriod -> periodend
|
||||||
(spans,
|
AtNow -> case today_ of
|
||||||
[(acct, acct', depth, map convert rowamts, convert rowtotal, convert rowavg) | (acct, acct', depth, rowamts, rowtotal, rowavg) <- rows],
|
Just d -> d
|
||||||
(map convert coltotals, convert rowtotaltotal, convert rowavgtotal))
|
Nothing -> error' "ReportOpts today_ is unset so could not satisfy --value-at=now"
|
||||||
convert = mixedAmountValue prices d
|
AtDate d -> d
|
||||||
|
|
||||||
-- -- convert to value ?
|
|
||||||
-- -- first get period end date(s) XXX duplicated from multiBalanceReport
|
|
||||||
-- -- The date span specified by -b/-e/-p options and query args if any.
|
|
||||||
-- requestedspan = dbg1 "requestedspan" $ queryDateSpan (date2_ ropts) userq -- XXX userq ok ?
|
|
||||||
-- -- If the requested span is open-ended, close it using the journal's end dates.
|
|
||||||
-- -- This can still be the null (open) span if the journal is empty.
|
|
||||||
-- requestedspan' = dbg1 "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 = dbg1 "intervalspans" $ splitSpan (interval_ ropts) requestedspan'
|
|
||||||
|
|
||||||
|
|
||||||
-- | Generates a simple non-columnar BalanceReport, but using multiBalanceReport,
|
-- | Generates a simple non-columnar BalanceReport, but using multiBalanceReport,
|
||||||
-- in order to support --historical. Does not support tree-mode boring parent eliding.
|
-- in order to support --historical. Does not support tree-mode boring parent eliding.
|
||||||
|
|||||||
@ -511,10 +511,14 @@ The precise effect of the keywords is command-specific, but here is their genera
|
|||||||
: Use the prices as of today's date when the report is generated. This is the default.
|
: Use the prices as of today's date when the report is generated. This is the default.
|
||||||
|
|
||||||
- `--value-at=YYYY-MM-DD`
|
- `--value-at=YYYY-MM-DD`
|
||||||
: Use the prices as of the given date (must be 8 digits with `-` or `/` or `.` separators).
|
: Use the prices as of the given date (8 digits with `-` or `/` or `.` separators).
|
||||||
: Eg `--value-at=2019-04-25`.
|
: Eg `--value-at=2019-04-25`.
|
||||||
|
|
||||||
Currently `--value-at` affects only the [print](/hledger.html#print) command.
|
Currently `--value-at` affects only some commands
|
||||||
|
([print](/hledger.html#print),
|
||||||
|
[multicolumn balance reports](/hledger.html#balance)),
|
||||||
|
and some of the keywords may not be supported by certain commands.
|
||||||
|
|
||||||
Here are some examples to show its effect:
|
Here are some examples to show its effect:
|
||||||
|
|
||||||
```journal
|
```journal
|
||||||
|
|||||||
@ -198,3 +198,48 @@ $ hledger -f- print --value-at=2000-01-15
|
|||||||
|
|
||||||
>=0
|
>=0
|
||||||
|
|
||||||
|
# 14. multicolumn balance report with default value
|
||||||
|
$ hledger -f- bal -M -V
|
||||||
|
Balance changes in 2000q1:
|
||||||
|
|
||||||
|
|| Jan Feb Mar
|
||||||
|
===++===============
|
||||||
|
a || 4 B 4 B 4 B
|
||||||
|
---++---------------
|
||||||
|
|| 4 B 4 B 4 B
|
||||||
|
|
||||||
|
# 15. multicolumn balance report valued at transaction is not supported
|
||||||
|
$ hledger -f- bal -M --value-at=transaction
|
||||||
|
>2 /--value-at=transaction is not yet supported with multicolumn balance reports/
|
||||||
|
>=1
|
||||||
|
|
||||||
|
# 16. multicolumn balance report valued at period end
|
||||||
|
$ hledger -f- bal -M --value-at=period
|
||||||
|
Balance changes in 2000q1:
|
||||||
|
|
||||||
|
|| Jan Feb Mar
|
||||||
|
===++===============
|
||||||
|
a || 2 B 3 B 4 B
|
||||||
|
---++---------------
|
||||||
|
|| 2 B 3 B 4 B
|
||||||
|
|
||||||
|
# 17. multicolumn balance report valued at today
|
||||||
|
$ hledger -f- bal -M --value-at=now
|
||||||
|
Balance changes in 2000q1:
|
||||||
|
|
||||||
|
|| Jan Feb Mar
|
||||||
|
===++===============
|
||||||
|
a || 4 B 4 B 4 B
|
||||||
|
---++---------------
|
||||||
|
|| 4 B 4 B 4 B
|
||||||
|
|
||||||
|
# 18. multicolumn balance report valued at other date
|
||||||
|
$ hledger -f- bal -M --value-at=2000-01-15
|
||||||
|
Balance changes in 2000q1:
|
||||||
|
|
||||||
|
|| Jan Feb Mar
|
||||||
|
===++===============
|
||||||
|
a || 1 B 1 B 1 B
|
||||||
|
---++---------------
|
||||||
|
|| 1 B 1 B 1 B
|
||||||
|
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user