lib!: lib,cli,ui,web: For accountTransactionsReport, generate the overall

reportq from the ReportSpec, rather than being supplied as a separate
option.

This is the same approach used by the other reports, e.g. EntryReport,
PostingReport, MultiBalanceReport. This reduces code duplication, as
previously the reportq had to be separately tweaked in each of 5
different places.

If you call accountTransactionreport, there is no need to separately
derive the report query.
This commit is contained in:
Stephen Morgan 2021-06-23 12:48:02 +10:00 committed by Simon Michael
parent f673e7c2eb
commit 3969eb2679
5 changed files with 35 additions and 54 deletions

View File

@ -23,13 +23,12 @@ module Hledger.Reports.AccountTransactionsReport (
)
where
import Data.List (mapAccumL, nub, partition, sortBy)
import Data.List (mapAccumL, nub, partition, sortOn)
import Data.List.Extra (nubSort)
import Data.Ord (comparing)
import Data.Maybe (catMaybes)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar (Day)
import Data.Time.Calendar (Day, addDays)
import Hledger.Data
import Hledger.Query
@ -93,21 +92,29 @@ triBalance (_,_,_,_,_,a) = a
triCommodityAmount c = filterMixedAmountByCommodity c . triAmount
triCommodityBalance c = filterMixedAmountByCommodity c . triBalance
accountTransactionsReport :: ReportSpec -> Journal -> Query -> Query -> AccountTransactionsReport
accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = items
accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j thisacctq = items
where
-- a depth limit should not affect the account transactions report
-- seems unnecessary for some reason XXX
reportq' = reportq -- filterQuery (not . queryIsDepth)
symq = filterQuery queryIsSym reportq'
realq = filterQuery queryIsReal reportq'
statusq = filterQuery queryIsStatus reportq'
reportq = simplifyQuery $ And [rsQuery rspec, periodq, excludeforecastq (forecast_ ropts)]
where
periodq = Date . periodAsDateSpan $ period_ ropts
-- Except in forecast mode, exclude future/forecast transactions.
excludeforecastq (Just _) = Any
excludeforecastq Nothing = -- not:date:tomorrow- not:tag:generated-transaction
And [ Not . Date $ DateSpan (Just . addDays 1 $ rsToday rspec) Nothing
, Not generatedTransactionTag
]
symq = filterQuery queryIsSym reportq
realq = filterQuery queryIsReal reportq
statusq = filterQuery queryIsStatus reportq
-- sort by the transaction's register date, for accurate starting balance
-- these are not yet filtered by tdate, we want to search them all for priorps
transactions =
ptraceAtWith 5 (("ts5:\n"++).pshowTransactions)
. sortBy (comparing (transactionRegisterDate reportq' thisacctq))
. sortOn (transactionRegisterDate reportq thisacctq)
. jtxns
. ptraceAtWith 5 (("ts4:\n"++).pshowTransactions.jtxns)
-- keep just the transactions affecting this account (via possibly realness or status-filtered postings)
@ -115,7 +122,7 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
. ptraceAtWith 5 (("ts3:\n"++).pshowTransactions.jtxns)
. filterJournalTransactions thisacctq
. filterJournalPostings (And [realq, statusq])
-- apply any cur:SYM filters in reportq'
-- 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
@ -134,8 +141,8 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
case mstartdate of
Just _ -> Date (DateSpan Nothing mstartdate)
Nothing -> None -- no start date specified, there are no prior postings
mstartdate = queryStartDate (date2_ ropts) reportq'
datelessreportq = filterQuery (not . queryIsDateOrDate2) reportq'
mstartdate = queryStartDate (date2_ ropts) reportq
datelessreportq = filterQuery (not . queryIsDateOrDate2) reportq
-- 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 ?
@ -144,8 +151,8 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i
filtertxns = txn_dates_ ropts
items = reverse $
accountTransactionsReportItems reportq' thisacctq startbal maNegate $
(if filtertxns then filter (reportq' `matchesTransaction`) else id) $
accountTransactionsReportItems reportq thisacctq startbal maNegate $
(if filtertxns then filter (reportq `matchesTransaction`) else id) $
transactions
pshowTransactions :: [Transaction] -> String

View File

@ -74,20 +74,8 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec
}
rspec' =
either (error "rsInit: adjusting the query for register, should not have failed") id $ -- PARTIAL:
updateReportSpec ropts' rspec
-- Further restrict the query based on the current period and future/forecast mode.
q = simplifyQuery $ And [rsQuery rspec', periodq, excludeforecastq (forecast_ ropts)]
where
periodq = Date $ periodAsDateSpan $ period_ ropts
-- Except in forecast mode, exclude future/forecast transactions.
excludeforecastq (Just _) = Any
excludeforecastq Nothing = -- not:date:tomorrow- not:tag:generated-transaction
And [
Not (Date $ DateSpan (Just $ addDays 1 d) Nothing)
,Not generatedTransactionTag
]
items = accountTransactionsReport rspec' j q thisacctq
updateReportSpec ropts' rspec{rsToday=d}
items = accountTransactionsReport rspec' j thisacctq
items' = (if empty_ ropts then id else filter (not . mixedAmountLooksZero . fifth6)) $ -- without --empty, exclude no-change txns
reverse -- most recent last
items
@ -96,7 +84,7 @@ rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec
displayitems = map displayitem items'
where
displayitem (t, _, _issplit, otheracctsstr, change, bal) =
RegisterScreenItem{rsItemDate = showDate $ transactionRegisterDate q thisacctq t
RegisterScreenItem{rsItemDate = showDate $ transactionRegisterDate (rsQuery rspec') thisacctq t
,rsItemStatus = tstatus t
,rsItemDescription = tdescription t
,rsItemOtherAccounts = otheracctsstr

View File

@ -103,8 +103,7 @@ getAccounttransactionsR a = do
when (CapView `notElem` caps) (permissionDenied "Missing the 'view' capability")
let
rspec = defreportspec
q = Any --filterQuery (not . queryIsDepth) $ queryFromOpts d ropts'
thisacctq = Acct $ accountNameToAccountRegex a -- includes subs
selectRep $ do
provideJson $ accountTransactionsReport rspec j q thisacctq
provideJson $ accountTransactionsReport rspec{rsQuery=Any} j thisacctq

View File

@ -44,7 +44,7 @@ getRegisterR = do
zip xs $
zip (map (T.unpack . accountSummarisedName . paccount) xs) $
tail $ (", "<$xs) ++ [""]
items = accountTransactionsReport rspec j m acctQuery
items = accountTransactionsReport rspec{rsQuery=m} j acctQuery
balancelabel
| isJust (inAccount qopts), balanceaccum_ (rsOpts rspec) == Historical = "Historical Total"
| isJust (inAccount qopts) = "Period Total"

View File

@ -20,11 +20,10 @@ module Hledger.Cli.Commands.Aregister (
) where
import Data.List (find, intersperse)
import Data.Maybe (fromMaybe, isJust)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Data.Time (addDays)
import System.Console.CmdArgs.Explicit (flagNone, flagReq)
import Hledger.Read.CsvReader (CSV, CsvRecord, printCSV)
@ -67,12 +66,10 @@ aregistermode = hledgerCommandMode
-- | Print an account register report for a specified account.
aregister :: CliOpts -> Journal -> IO ()
aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
d <- getCurrentDay
-- the first argument specifies the account, any remaining arguments are a filter query
(apat,querystring) <- case listofstringopt "args" rawopts of
[] -> fail "aregister needs an account, please provide an account name or pattern"
(a:as) -> return (a, map T.pack as)
argsquery <- either fail (return . fst) $ parseQueryList d querystring
let
acct = fromMaybe (error' $ show apat++" did not match any account") -- PARTIAL:
. firstMatch $ journalAccountNamesDeclaredOrImplied j
@ -87,29 +84,19 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
depth_=Nothing
-- always show historical balance
, balanceaccum_= Historical
, querystring_ = querystring
}
-- and regenerate the ReportSpec, making sure to use the above
rspec' = rspec{ rsQuery=simplifyQuery $ And [queryFromFlags ropts', argsquery]
, rsOpts=ropts'
}
reportq = And [rsQuery rspec', excludeforecastq (isJust $ forecast_ ropts')]
where
-- As in RegisterScreen, why ? XXX
-- Except in forecast mode, exclude future/forecast transactions.
excludeforecastq True = Any
excludeforecastq False = -- not:date:tomorrow- not:tag:generated-transaction
And [
Not (Date $ DateSpan (Just $ addDays 1 d) Nothing)
,Not generatedTransactionTag
]
-- and regenerate the ReportSpec, making sure to use the above
rspec' <- either fail return $ updateReportSpec ropts' rspec
let
-- run the report
-- TODO: need to also pass the queries so we can choose which date to render - move them into the report ?
items = accountTransactionsReport rspec' j reportq thisacctq
items = accountTransactionsReport rspec' j thisacctq
items' = (if empty_ ropts' then id else filter (not . mixedAmountLooksZero . fifth6)) $
reverse items
-- select renderer
render | fmt=="txt" = accountTransactionsReportAsText opts reportq thisacctq
| fmt=="csv" = printCSV . accountTransactionsReportAsCsv reportq thisacctq
render | fmt=="txt" = accountTransactionsReportAsText opts (rsQuery rspec') thisacctq
| fmt=="csv" = printCSV . accountTransactionsReportAsCsv (rsQuery rspec') thisacctq
| fmt=="json" = toJsonText
| otherwise = error' $ unsupportedOutputFormatError fmt -- PARTIAL:
where