lib,cli,web,bin: Replace journalSelectingAmountFromOpts with journalApplyValuationFromOpts.

This also has the effect of allowing valuation in more reports, for
example the transactionReport.
This commit is contained in:
Stephen Morgan 2021-05-13 21:00:25 +10:00
parent 940b2c6ab9
commit 0a019e2167
8 changed files with 30 additions and 41 deletions

View File

@ -34,7 +34,7 @@ main = do
d <- getCurrentDay
let
q = rsQuery rspec
ts = filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts (rsOpts rspec) j
ts = filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j
ts' = map transactionSwapDates ts
mapM_ (T.putStrLn . showTransaction) ts'

View File

@ -95,9 +95,7 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
ptraceAtWith 5 (("ts5:\n"++).pshowTransactions)
. sortBy (comparing (transactionRegisterDate reportq' thisacctq))
. jtxns
-- maybe convert these transactions to cost or value
. ptraceAtWith 5 (("ts4:\n"++).pshowTransactions.jtxns)
. journalSelectingAmountFromOpts ropts
-- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
. traceAt 3 ("thisacctq: "++show thisacctq)
. ptraceAtWith 5 (("ts3:\n"++).pshowTransactions.jtxns)
@ -106,6 +104,7 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
-- apply any cur:SYM filters in reportq'
. ptraceAtWith 5 (("ts2:\n"++).pshowTransactions.jtxns)
. (if queryIsNull symq then id else filterJournalAmounts symq)
-- maybe convert these transactions to cost or value
$ journalApplyValuationFromOpts rspec j
startbal

View File

@ -28,7 +28,6 @@ module Hledger.Reports.ReportOptions (
reportOptsToggleStatus,
simplifyStatuses,
whichDateFromOpts,
journalSelectingAmountFromOpts,
journalApplyValuationFromOpts,
journalApplyValuationFromOptsWith,
mixedAmountApplyValuationAfterSumFromOptsWith,
@ -493,21 +492,12 @@ flat_ = not . tree_
-- depthFromOpts :: ReportOpts -> Int
-- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts)
-- | Convert this journal's postings' amounts to cost using their transaction prices,
-- if specified by options (-B/--cost). Strip prices if not needed.
journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal
journalSelectingAmountFromOpts ropts = maybeStripPrices . case cost_ ropts of
Cost -> journalToCost
NoCost -> id
where
maybeStripPrices = if show_costs_ ropts then id else journalMapPostingAmounts mixedAmountStripPrices
-- | Convert this journal's postings' amounts to cost using their transaction
-- prices and apply valuation, if specified by options (-B/--cost). Strip prices
-- if not needed. This should be the main stop for performing costing and valuation.
-- The exception is whenever you need to perform valuation _after_ summing up amounts,
-- as in a historical balance report with --value=end. valuationAfterSum will
-- check for this condition.
-- | Convert this journal's postings' amounts to cost and/or to value, if specified
-- by options (-B/--cost/-V/-X/--value etc.). Strip prices if not needed. This
-- should be the main stop for performing costing and valuation. The exception is
-- whenever you need to perform valuation _after_ summing up amounts, as in a
-- historical balance report with --value=end. valuationAfterSum will check for this
-- condition.
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
journalApplyValuationFromOpts rspec j =
journalApplyValuationFromOptsWith rspec j priceoracle
@ -532,12 +522,14 @@ journalApplyValuationFromOptsWith rspec@ReportSpec{rsOpts=ropts} j priceoracle =
styles = journalCommodityStyles j
err = error "journalApplyValuationFromOpts: expected all spans to have an end date"
-- | Calculate the Account valuation functions required for valuing after summing amounts.
-- Used in MultiBalanceReport to value historical reports and the like.
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> (DateSpan -> MixedAmount -> MixedAmount)
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle = case valuationAfterSum ropts of
Just mc -> \span -> valuation mc span . maybeStripPrices . costing
Nothing -> const id
-- | Select the Account valuation functions required for performing valuation after summing
-- amounts. Used in MultiBalanceReport to value historical and similar reports.
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle
-> (DateSpan -> MixedAmount -> MixedAmount)
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
case valuationAfterSum ropts of
Just mc -> \span -> valuation mc span . maybeStripPrices . costing
Nothing -> const id
where
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
where err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
@ -547,17 +539,15 @@ mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle = case valuati
NoCost -> id
styles = journalCommodityStyles j
-- | If we are performing valuation after summing amounts, return Just the
-- commodity symbols we're converting to, otherwise return Nothing.
-- | If the ReportOpts specify that we are performing valuation after summing amounts,
-- return Just the commodity symbol we're converting to, otherwise return Nothing.
-- Used for example with historical reports with --value=end.
valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
valuationAfterSum ropts = case value_ ropts of
Just (AtEnd mc) -> case (reporttype_ ropts, balancetype_ ropts) of
(ValueChangeReport, _) -> Just mc
(_, HistoricalBalance) -> Just mc
(_, CumulativeChange) -> Just mc
_ -> Nothing
_ -> Nothing
Just (AtEnd mc) | valueAfterSum -> Just mc
_ -> Nothing
where valueAfterSum = reporttype_ ropts == ValueChangeReport
|| balancetype_ ropts /= PeriodChange
-- | Convert report options to a query, ignoring any non-flag command line arguments.

View File

@ -62,13 +62,13 @@ triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
-- "postingsReport" except with transaction-based report items which
-- are ordered most recent first. XXX Or an EntriesReport - use that instead ?
-- This is used by hledger-web's journal view.
transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
transactionsReport opts j q = items
transactionsReport :: ReportSpec -> Journal -> Query -> TransactionsReport
transactionsReport rspec j q = items
where
-- XXX items' first element should be the full transaction with all postings
items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts
ts = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts opts j
date = transactionDateFn opts
ts = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j
date = transactionDateFn $ rsOpts rspec
-- | Split a transactions report whose items may involve several commodities,
-- into one or more single-commodity transactions reports.

View File

@ -27,7 +27,7 @@ getJournalR = do
Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)"
title' = title <> if m /= Any then ", filtered" else ""
acctlink a = (RegisterR, [("q", replaceInacct q $ accountQuery a)])
items = transactionsReport (rsOpts . reportspec_ $ cliopts_ opts) j m
items = transactionsReport (reportspec_ $ cliopts_ opts) j m
transactionFrag = transactionFragment j
defaultLayout $ do

View File

@ -22,7 +22,7 @@ journalCheckOrdereddates CliOpts{reportspec_=rspec} j = do
filets =
groupBy (\t1 t2 -> transactionFile t1 == transactionFile t2) $
filter (rsQuery rspec `matchesTransaction`) $
jtxns $ journalSelectingAmountFromOpts ropts j
jtxns $ journalApplyValuationFromOpts rspec j
checkunique = False -- boolopt "unique" rawopts XXX was supported by checkdates command
compare a b = if checkunique then getdate a < getdate b else getdate a <= getdate b
where getdate = transactionDateFn ropts

View File

@ -29,7 +29,7 @@ checkdates :: CliOpts -> Journal -> IO ()
checkdates CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
let ropts = (rsOpts rspec){accountlistmode_=ALFlat}
let ts = filter (rsQuery rspec `matchesTransaction`) $
jtxns $ journalSelectingAmountFromOpts ropts j
jtxns $ journalApplyValuationFromOpts rspec{rsOpts=ropts} j
-- pprint rawopts
let unique = boolopt "--unique" rawopts -- TEMP: it's this for hledger check dates
|| boolopt "unique" rawopts -- and this for hledger check-dates (for some reason)

View File

@ -39,7 +39,7 @@ tags CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
argsquery <- either usageError (return . fst) $ parseQueryList d querystring
let
q = simplifyQuery $ And [queryFromFlags $ rsOpts rspec, argsquery]
txns = filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts (rsOpts rspec) j
txns = filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j
tagsorvalues =
(if parsed then id else nubSort)
[ r