bal: support --value-at in single column balance reports

This commit is contained in:
Simon Michael 2019-04-26 11:45:51 -07:00
parent 00975fb226
commit 7306e61646

View File

@ -4,7 +4,7 @@ Balance report, used by the balance command.
-} -}
{-# LANGUAGE FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-} {-# LANGUAGE FlexibleInstances, RecordWildCards, ScopedTypeVariables, OverloadedStrings #-}
module Hledger.Reports.BalanceReport ( module Hledger.Reports.BalanceReport (
BalanceReport, BalanceReport,
@ -172,25 +172,41 @@ brNegate (is, tot) = (map brItemNegate is, -tot)
-- | Convert all the posting amounts in a BalanceReport to their -- | Convert all the posting amounts in a BalanceReport 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-at and can be:
-- otherwise the current date, otherwise the journal's end date. -- each posting's date,
-- the last day in the report period (or in the journal if no period,
-- or gives an error if journal is empty - shouldn't happen),
-- or today's date (gives an error if today_ is not set in ReportOpts),
-- or a specified date.
brValue :: ReportOpts -> Journal -> BalanceReport -> BalanceReport brValue :: ReportOpts -> Journal -> BalanceReport -> BalanceReport
brValue ropts j r = brValue ropts@ReportOpts{..} j (items, total) =
let mvaluationdate = periodEnd (period_ ropts) <|> today_ ropts <|> journalEndDate False j ([ (n, n', i, mixedAmountValue prices d a) | (n,n',i,a) <- items ]
in case mvaluationdate of ,mixedAmountValue prices d total
Nothing -> r )
Just d -> r' 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 j d = case value_at_ of
(items,total) = r AtTransaction -> error' "sorry, --value-at=transaction is not yet supported with balance reports" -- XXX
r' = AtPeriod -> fromMaybe (error' "brValue: expected a non-empty journal") mperiodorjournallastday -- XXX shouldn't happen
dbg8 "market prices" prices `seq` AtNow -> case today_ of
dbg8 "valuation date" d `seq` Just d -> d
dbg8 "brValue" Nothing -> error' "brValue: ReportOpts today_ is unset so could not satisfy --value-at=now"
([(n, n', i, mixedAmountValue prices d a) |(n,n',i,a) <- items], mixedAmountValue prices d total) AtDate d -> d
-- Get the last day of the report period.
-- 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
mperiodorjournallastday = mperiodlastday <|> journalEndDate False j
-- -- | Find the best commodity to convert to when asked to show the -- -- | Find the best commodity to convert to when asked to show the
-- -- market value of this commodity on the given date. That is, the one -- -- market value of this commodity on the given date. That is, the one
-- -- in which it has most recently been market-priced, ie the commodity -- -- in which it has most recently been market-priced, ie the commodity