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:
parent
940b2c6ab9
commit
0a019e2167
@ -34,7 +34,7 @@ main = do
|
|||||||
d <- getCurrentDay
|
d <- getCurrentDay
|
||||||
let
|
let
|
||||||
q = rsQuery rspec
|
q = rsQuery rspec
|
||||||
ts = filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts (rsOpts rspec) j
|
ts = filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j
|
||||||
ts' = map transactionSwapDates ts
|
ts' = map transactionSwapDates ts
|
||||||
mapM_ (T.putStrLn . showTransaction) ts'
|
mapM_ (T.putStrLn . showTransaction) ts'
|
||||||
|
|
||||||
|
|||||||
@ -95,9 +95,7 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
|
|||||||
ptraceAtWith 5 (("ts5:\n"++).pshowTransactions)
|
ptraceAtWith 5 (("ts5:\n"++).pshowTransactions)
|
||||||
. sortBy (comparing (transactionRegisterDate reportq' thisacctq))
|
. sortBy (comparing (transactionRegisterDate reportq' thisacctq))
|
||||||
. jtxns
|
. jtxns
|
||||||
-- maybe convert these transactions to cost or value
|
|
||||||
. ptraceAtWith 5 (("ts4:\n"++).pshowTransactions.jtxns)
|
. ptraceAtWith 5 (("ts4:\n"++).pshowTransactions.jtxns)
|
||||||
. journalSelectingAmountFromOpts ropts
|
|
||||||
-- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
|
-- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
|
||||||
. traceAt 3 ("thisacctq: "++show thisacctq)
|
. traceAt 3 ("thisacctq: "++show thisacctq)
|
||||||
. ptraceAtWith 5 (("ts3:\n"++).pshowTransactions.jtxns)
|
. 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'
|
-- apply any cur:SYM filters in reportq'
|
||||||
. ptraceAtWith 5 (("ts2:\n"++).pshowTransactions.jtxns)
|
. ptraceAtWith 5 (("ts2:\n"++).pshowTransactions.jtxns)
|
||||||
. (if queryIsNull symq then id else filterJournalAmounts symq)
|
. (if queryIsNull symq then id else filterJournalAmounts symq)
|
||||||
|
-- maybe convert these transactions to cost or value
|
||||||
$ journalApplyValuationFromOpts rspec j
|
$ journalApplyValuationFromOpts rspec j
|
||||||
|
|
||||||
startbal
|
startbal
|
||||||
|
|||||||
@ -28,7 +28,6 @@ module Hledger.Reports.ReportOptions (
|
|||||||
reportOptsToggleStatus,
|
reportOptsToggleStatus,
|
||||||
simplifyStatuses,
|
simplifyStatuses,
|
||||||
whichDateFromOpts,
|
whichDateFromOpts,
|
||||||
journalSelectingAmountFromOpts,
|
|
||||||
journalApplyValuationFromOpts,
|
journalApplyValuationFromOpts,
|
||||||
journalApplyValuationFromOptsWith,
|
journalApplyValuationFromOptsWith,
|
||||||
mixedAmountApplyValuationAfterSumFromOptsWith,
|
mixedAmountApplyValuationAfterSumFromOptsWith,
|
||||||
@ -493,21 +492,12 @@ flat_ = not . tree_
|
|||||||
-- depthFromOpts :: ReportOpts -> Int
|
-- depthFromOpts :: ReportOpts -> Int
|
||||||
-- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts)
|
-- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts)
|
||||||
|
|
||||||
-- | Convert this journal's postings' amounts to cost using their transaction prices,
|
-- | Convert this journal's postings' amounts to cost and/or to value, if specified
|
||||||
-- if specified by options (-B/--cost). Strip prices if not needed.
|
-- by options (-B/--cost/-V/-X/--value etc.). Strip prices if not needed. This
|
||||||
journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal
|
-- should be the main stop for performing costing and valuation. The exception is
|
||||||
journalSelectingAmountFromOpts ropts = maybeStripPrices . case cost_ ropts of
|
-- whenever you need to perform valuation _after_ summing up amounts, as in a
|
||||||
Cost -> journalToCost
|
-- historical balance report with --value=end. valuationAfterSum will check for this
|
||||||
NoCost -> id
|
-- condition.
|
||||||
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.
|
|
||||||
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
|
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
|
||||||
journalApplyValuationFromOpts rspec j =
|
journalApplyValuationFromOpts rspec j =
|
||||||
journalApplyValuationFromOptsWith rspec j priceoracle
|
journalApplyValuationFromOptsWith rspec j priceoracle
|
||||||
@ -532,12 +522,14 @@ journalApplyValuationFromOptsWith rspec@ReportSpec{rsOpts=ropts} j priceoracle =
|
|||||||
styles = journalCommodityStyles j
|
styles = journalCommodityStyles j
|
||||||
err = error "journalApplyValuationFromOpts: expected all spans to have an end date"
|
err = error "journalApplyValuationFromOpts: expected all spans to have an end date"
|
||||||
|
|
||||||
-- | Calculate the Account valuation functions required for valuing after summing amounts.
|
-- | Select the Account valuation functions required for performing valuation after summing
|
||||||
-- Used in MultiBalanceReport to value historical reports and the like.
|
-- amounts. Used in MultiBalanceReport to value historical and similar reports.
|
||||||
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> (DateSpan -> MixedAmount -> MixedAmount)
|
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle
|
||||||
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle = case valuationAfterSum ropts of
|
-> (DateSpan -> MixedAmount -> MixedAmount)
|
||||||
Just mc -> \span -> valuation mc span . maybeStripPrices . costing
|
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
||||||
Nothing -> const id
|
case valuationAfterSum ropts of
|
||||||
|
Just mc -> \span -> valuation mc span . maybeStripPrices . costing
|
||||||
|
Nothing -> const id
|
||||||
where
|
where
|
||||||
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
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"
|
where err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
|
||||||
@ -547,17 +539,15 @@ mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle = case valuati
|
|||||||
NoCost -> id
|
NoCost -> id
|
||||||
styles = journalCommodityStyles j
|
styles = journalCommodityStyles j
|
||||||
|
|
||||||
-- | If we are performing valuation after summing amounts, return Just the
|
-- | If the ReportOpts specify that we are performing valuation after summing amounts,
|
||||||
-- commodity symbols we're converting to, otherwise return Nothing.
|
-- return Just the commodity symbol we're converting to, otherwise return Nothing.
|
||||||
-- Used for example with historical reports with --value=end.
|
-- Used for example with historical reports with --value=end.
|
||||||
valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
|
valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
|
||||||
valuationAfterSum ropts = case value_ ropts of
|
valuationAfterSum ropts = case value_ ropts of
|
||||||
Just (AtEnd mc) -> case (reporttype_ ropts, balancetype_ ropts) of
|
Just (AtEnd mc) | valueAfterSum -> Just mc
|
||||||
(ValueChangeReport, _) -> Just mc
|
_ -> Nothing
|
||||||
(_, HistoricalBalance) -> Just mc
|
where valueAfterSum = reporttype_ ropts == ValueChangeReport
|
||||||
(_, CumulativeChange) -> Just mc
|
|| balancetype_ ropts /= PeriodChange
|
||||||
_ -> Nothing
|
|
||||||
_ -> Nothing
|
|
||||||
|
|
||||||
|
|
||||||
-- | Convert report options to a query, ignoring any non-flag command line arguments.
|
-- | Convert report options to a query, ignoring any non-flag command line arguments.
|
||||||
|
|||||||
@ -62,13 +62,13 @@ triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
|
|||||||
-- "postingsReport" except with transaction-based report items which
|
-- "postingsReport" except with transaction-based report items which
|
||||||
-- are ordered most recent first. XXX Or an EntriesReport - use that instead ?
|
-- are ordered most recent first. XXX Or an EntriesReport - use that instead ?
|
||||||
-- This is used by hledger-web's journal view.
|
-- This is used by hledger-web's journal view.
|
||||||
transactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport
|
transactionsReport :: ReportSpec -> Journal -> Query -> TransactionsReport
|
||||||
transactionsReport opts j q = items
|
transactionsReport rspec j q = items
|
||||||
where
|
where
|
||||||
-- XXX items' first element should be the full transaction with all postings
|
-- XXX items' first element should be the full transaction with all postings
|
||||||
items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts
|
items = reverse $ accountTransactionsReportItems q None nullmixedamt id ts
|
||||||
ts = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts opts j
|
ts = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j
|
||||||
date = transactionDateFn opts
|
date = transactionDateFn $ rsOpts rspec
|
||||||
|
|
||||||
-- | Split a transactions report whose items may involve several commodities,
|
-- | Split a transactions report whose items may involve several commodities,
|
||||||
-- into one or more single-commodity transactions reports.
|
-- into one or more single-commodity transactions reports.
|
||||||
|
|||||||
@ -27,7 +27,7 @@ getJournalR = do
|
|||||||
Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)"
|
Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)"
|
||||||
title' = title <> if m /= Any then ", filtered" else ""
|
title' = title <> if m /= Any then ", filtered" else ""
|
||||||
acctlink a = (RegisterR, [("q", replaceInacct q $ accountQuery a)])
|
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
|
transactionFrag = transactionFragment j
|
||||||
|
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
|
|||||||
@ -22,7 +22,7 @@ journalCheckOrdereddates CliOpts{reportspec_=rspec} j = do
|
|||||||
filets =
|
filets =
|
||||||
groupBy (\t1 t2 -> transactionFile t1 == transactionFile t2) $
|
groupBy (\t1 t2 -> transactionFile t1 == transactionFile t2) $
|
||||||
filter (rsQuery rspec `matchesTransaction`) $
|
filter (rsQuery rspec `matchesTransaction`) $
|
||||||
jtxns $ journalSelectingAmountFromOpts ropts j
|
jtxns $ journalApplyValuationFromOpts rspec j
|
||||||
checkunique = False -- boolopt "unique" rawopts XXX was supported by checkdates command
|
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
|
compare a b = if checkunique then getdate a < getdate b else getdate a <= getdate b
|
||||||
where getdate = transactionDateFn ropts
|
where getdate = transactionDateFn ropts
|
||||||
|
|||||||
@ -29,7 +29,7 @@ checkdates :: CliOpts -> Journal -> IO ()
|
|||||||
checkdates CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
checkdates CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
||||||
let ropts = (rsOpts rspec){accountlistmode_=ALFlat}
|
let ropts = (rsOpts rspec){accountlistmode_=ALFlat}
|
||||||
let ts = filter (rsQuery rspec `matchesTransaction`) $
|
let ts = filter (rsQuery rspec `matchesTransaction`) $
|
||||||
jtxns $ journalSelectingAmountFromOpts ropts j
|
jtxns $ journalApplyValuationFromOpts rspec{rsOpts=ropts} j
|
||||||
-- pprint rawopts
|
-- pprint rawopts
|
||||||
let unique = boolopt "--unique" rawopts -- TEMP: it's this for hledger check dates
|
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)
|
|| boolopt "unique" rawopts -- and this for hledger check-dates (for some reason)
|
||||||
|
|||||||
@ -39,7 +39,7 @@ tags CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
|||||||
argsquery <- either usageError (return . fst) $ parseQueryList d querystring
|
argsquery <- either usageError (return . fst) $ parseQueryList d querystring
|
||||||
let
|
let
|
||||||
q = simplifyQuery $ And [queryFromFlags $ rsOpts rspec, argsquery]
|
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 =
|
tagsorvalues =
|
||||||
(if parsed then id else nubSort)
|
(if parsed then id else nubSort)
|
||||||
[ r
|
[ r
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user