fix: areg: Make sure the true original transaction is made available in

AccountTransactionsReport.

Only a limited number of journal transformations are allowed in
accountTransactionReports due to the need to include the original
transaction. Document these.

Make sure to remove currency and amount queries from the reportq, so
they do not cause problems after valuation.

Avoid confusion by calculating transaction date at one point, and
passing that down with the transaction.
This commit is contained in:
Stephen Morgan 2021-08-02 13:59:20 +10:00 committed by Simon Michael
parent b7e40a9e63
commit ae3c7e8756
2 changed files with 66 additions and 64 deletions

View File

@ -23,10 +23,10 @@ module Hledger.Reports.AccountTransactionsReport (
)
where
import Data.List (mapAccumR, nub, partition, sortOn)
import Data.List (mapAccumR, nub, partition, sortBy)
import Data.List.Extra (nubSort)
import Data.Maybe (catMaybes)
import Data.Ord (Down(..))
import Data.Ord (Down(..), comparing)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar (Day, addDays)
@ -95,11 +95,11 @@ triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
accountTransactionsReport rspec@ReportSpec{_rsReportOpts=ropts} j thisacctq = items
where
-- a depth limit should not affect the account transactions report
-- seems unnecessary for some reason XXX
reportq = simplifyQuery $ And [depthlessq, periodq, excludeforecastq (forecast_ ropts)]
-- A depth limit should not affect the account transactions report; it should show all transactions in/below this account.
-- Queries on currency or amount are also ignored at this stage; they are handled earlier, before valuation.
reportq = simplifyQuery $ And [aregisterq, periodq, excludeforecastq (forecast_ ropts)]
where
depthlessq = filterQuery (not . queryIsDepth) $ _rsQuery rspec
aregisterq = filterQuery (not . queryIsCurOrAmt) . filterQuery (not . queryIsDepth) $ _rsQuery rspec
periodq = Date . periodAsDateSpan $ period_ ropts
-- Except in forecast mode, exclude future/forecast transactions.
excludeforecastq (Just _) = Any
@ -107,46 +107,41 @@ accountTransactionsReport rspec@ReportSpec{_rsReportOpts=ropts} j thisacctq = it
And [ Not . Date $ DateSpan (Just . addDays 1 $ _rsDay rspec) Nothing
, Not generatedTransactionTag
]
symq = filterQuery queryIsSym reportq
realq = filterQuery queryIsReal reportq
statusq = filterQuery queryIsStatus reportq
amtq = filterQuery queryIsCurOrAmt $ _rsQuery rspec
queryIsCurOrAmt q = queryIsSym q || queryIsAmt q
journalValuation = \j' -> journalApplyValuationFromOptsWith rspec j' priceoracle
where priceoracle = journalPriceOracle (infer_value_ $ _rsReportOpts rspec) j
-- sort by the transaction's register date, for accurate starting balance
transactions =
ptraceAtWith 5 (("ts4:\n"++).pshowTransactions)
. sortOn (Down . transactionRegisterDate reportq thisacctq)
. jtxns
. ptraceAtWith 5 (("ts3:\n"++).pshowTransactions.jtxns)
-- Note that within this functions, we are only allowed limited
-- transformation of the transaction postings: this is due to the need to
-- pass the original transactions into accountTransactionsReportItem.
-- Generally, we either include a transaction in full, or not at all.
-- Do some limited filtering and valuing of the journal's transactions:
-- - filter them by the account query if any,
-- - discard amounts not matched by the currency and amount query if any,
-- - then apply valuation if any.
acctJournal =
ptraceAtWith 5 (("ts3:\n"++).pshowTransactions.jtxns)
-- maybe convert these transactions to cost or value
. journalValuation
-- If we haven't yet filtered by reportq, do so now.
$ (if txn_dates_ ropts then id else filterJournalTransactions reportq) journalAcctTxns
-- these are not yet filtered by tdate, we want to search them all for priorps
journalAcctTxns =
-- accountTransactionsReportItem will keep transactions of any date which
-- have any posting inside the report period.
-- Should we also require that transaction date is inside the report period ?
-- Should we be filtering by reportq here to apply other query terms (?)
-- Make it an option for now.
(if txn_dates_ ropts then filterJournalTransactions reportq else id)
. journalApplyValuationFromOpts rspec
. ptraceAtWith 5 (("ts2:\n"++).pshowTransactions.jtxns)
-- apply any cur:SYM filters in reportq
. (if queryIsNull symq then id else filterJournalAmounts symq)
-- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
. (if queryIsNull amtq then id else filterJournalAmounts amtq)
-- only consider transactions which match thisacctq (possibly excluding postings
-- which are not real or have the wrong status)
. traceAt 3 ("thisacctq: "++show thisacctq)
. ptraceAtWith 5 (("ts1:\n"++).pshowTransactions.jtxns)
. filterJournalTransactions thisacctq
$ filterJournalPostings (And [realq, statusq]) j
$ ptraceAtWith 5 (("ts1:\n"++).pshowTransactions.jtxns)
j{jtxns = filter (matchesTransaction thisacctq . relevantPostings) $ jtxns j}
where
relevantPostings
| queryIsNull realq && queryIsNull statusq = id
| otherwise = filterTransactionPostings . simplifyQuery $ And [realq, statusq]
realq = filterQuery queryIsReal reportq
statusq = filterQuery queryIsStatus reportq
startbal
| balanceaccum_ ropts == Historical = sumPostings priorps
| otherwise = nullmixedamt
where
priorps = dbg5 "priorps" . journalPostings . journalValuation $
filterJournalPostings priorq journalAcctTxns
priorps = dbg5 "priorps" . journalPostings $ filterJournalPostings priorq acctJournal
priorq = dbg5 "priorq" $ And [thisacctq, tostartdateq, datelessreportq]
tostartdateq =
case mstartdate of
@ -155,30 +150,39 @@ accountTransactionsReport rspec@ReportSpec{_rsReportOpts=ropts} j thisacctq = it
mstartdate = queryStartDate (date2_ ropts) reportq
datelessreportq = filterQuery (not . queryIsDateOrDate2) reportq
items = accountTransactionsReportItems reportq thisacctq startbal maNegate transactions
items =
accountTransactionsReportItems reportq thisacctq startbal maNegate
-- sort by the transaction's register date, for accurate starting balance
. ptraceAtWith 5 (("ts4:\n"++).pshowTransactions.map snd)
. sortBy (comparing $ Down . fst)
. map (\t -> (transactionRegisterDate reportq thisacctq t, t))
$ jtxns acctJournal
pshowTransactions :: [Transaction] -> String
pshowTransactions = pshow . map (\t -> unwords [show $ tdate t, T.unpack $ tdescription t])
-- | Generate transactions report items from a list of transactions,
-- using the provided user-specified report query, a query specifying
-- which account to use as the focus, a starting balance, a sign-setting
-- function and a balance-summing function.
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> [Transaction] -> [AccountTransactionsReportItem]
-- which account to use as the focus, a starting balance, and a sign-setting
-- function.
-- Each transaction is accompanied by the date that should be shown for it
-- in the report, which is not necessarily the transaction date; it is
-- the earliest of the posting dates which match both thisacctq and reportq,
-- otherwise the transaction's date if there are no matching postings.
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount)
-> [(Day, Transaction)] -> [AccountTransactionsReportItem]
accountTransactionsReportItems reportq thisacctq bal signfn =
catMaybes . snd .
mapAccumR (accountTransactionsReportItem reportq thisacctq signfn) bal
catMaybes . snd . mapAccumR (accountTransactionsReportItem reportq thisacctq signfn) bal
accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount -> Transaction -> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem reportq thisacctq signfn bal torig = balItem
accountTransactionsReportItem :: Query -> Query -> (MixedAmount -> MixedAmount) -> MixedAmount
-> (Day, Transaction) -> (MixedAmount, Maybe AccountTransactionsReportItem)
accountTransactionsReportItem reportq thisacctq signfn bal (d, torig)
-- 201407: I've lost my grip on this, let's just hope for the best
-- 201606: we now calculate change and balance from filtered postings, check this still works well for all callers XXX
| null reportps = (bal, Nothing) -- no matched postings in this transaction, skip it
| otherwise = (b, Just (torig, tacct{tdate=d}, numotheraccts > 1, otheracctstr, a, b))
where
tacct@Transaction{tpostings=reportps} = torig{tdate=transactionRegisterDate reportq thisacctq torig}
balItem = case reportps of
[] -> (bal, Nothing) -- no matched postings in this transaction, skip it
_ -> (b, Just (torig, tacct, numotheraccts > 1, otheracctstr, a, b))
where
tacct@Transaction{tpostings=reportps} = filterTransactionPostings reportq torig
(thisacctps, otheracctps) = partition (matchesPosting thisacctq) reportps
numotheraccts = length $ nub $ map paccount otheracctps
otheracctstr | thisacctq == None = summarisePostingAccounts reportps -- no current account ? summarise all matched postings

View File

@ -324,10 +324,8 @@ $ hledger -f- register -V -B cur:A "amt:<5"
2021-01-01 (a) 1000 B 1000 B
>=
# 24. aregister report cur: and amt: query matches currency before
# valuation/cost (note that aregister currently only tests queries other than
# "cur:" and the account query when given the --txn-dates option. Who knows why.
$ hledger -f- aregister a -V -B cur:A "amt:<5" --txn-dates
# 24. aregister report cur: and amt: query matches currency before valuation/cost
$ hledger -f- aregister a -V -B cur:A "amt:<5"
Transactions in a and subaccounts:
2021-01-01 a 1000 B 1000 B
>=