Skip to content

Commit

Permalink
lib!: Rename the fields of ReportSpec.
Browse files Browse the repository at this point in the history
This is done to be more consistent with future field naming conventions,
and to make automatic generation of lenses simpler. See discussion in
\simonmichael#1545.

rsOpts -> _rsReportOpts
rsToday -> _rsDay
rsQuery -> _rsQuery
rsQueryOpts -> _rsQueryOpts
  • Loading branch information
Xitian9 committed Jul 23, 2021
1 parent 7ed2a0a commit 9ba84e2
Show file tree
Hide file tree
Showing 39 changed files with 163 additions and 163 deletions.
6 changes: 3 additions & 3 deletions hledger-lib/Hledger/Reports/AccountTransactionsReport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,17 +93,17 @@ triCommodityAmount c = filterMixedAmountByCommodity c . triAmount
triCommodityBalance c = filterMixedAmountByCommodity c . triBalance

accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j thisacctq = items
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 [rsQuery rspec, periodq, excludeforecastq (forecast_ ropts)]
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
And [ Not . Date $ DateSpan (Just . addDays 1 $ _rsDay rspec) Nothing
, Not generatedTransactionTag
]
symq = filterQuery queryIsSym reportq
Expand Down
20 changes: 10 additions & 10 deletions hledger-lib/Hledger/Reports/BalanceReport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -104,7 +104,7 @@ tests_BalanceReport = tests "BalanceReport" [

let
(rspec,journal) `gives` r = do
let opts' = rspec{rsQuery=And [queryFromFlags $ rsOpts rspec, rsQuery rspec]}
let opts' = rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
(eitems, etotal) = r
(aitems, atotal) = balanceReport opts' journal
showw (acct,acct',indent,amt) = (acct, acct', indent, showMixedAmountDebug amt)
Expand All @@ -130,7 +130,7 @@ tests_BalanceReport = tests "BalanceReport" [
mixedAmount (usd 0))

,test "with --tree" $
(defreportspec{rsOpts=defreportopts{accountlistmode_=ALTree}}, samplejournal) `gives`
(defreportspec{_rsReportOpts=defreportopts{accountlistmode_=ALTree}}, samplejournal) `gives`
([
("assets","assets",0, mamountp' "$0.00")
,("assets:bank","bank",1, mamountp' "$2.00")
Expand All @@ -147,43 +147,43 @@ tests_BalanceReport = tests "BalanceReport" [
mixedAmount (usd 0))

,test "with --depth=N" $
(defreportspec{rsOpts=defreportopts{depth_=Just 1}}, samplejournal) `gives`
(defreportspec{_rsReportOpts=defreportopts{depth_=Just 1}}, samplejournal) `gives`
([
("expenses", "expenses", 0, mamountp' "$2.00")
,("income", "income", 0, mamountp' "$-2.00")
],
mixedAmount (usd 0))

,test "with depth:N" $
(defreportspec{rsQuery=Depth 1}, samplejournal) `gives`
(defreportspec{_rsQuery=Depth 1}, samplejournal) `gives`
([
("expenses", "expenses", 0, mamountp' "$2.00")
,("income", "income", 0, mamountp' "$-2.00")
],
mixedAmount (usd 0))

,test "with date:" $
(defreportspec{rsQuery=Date $ DateSpan (Just $ fromGregorian 2009 01 01) (Just $ fromGregorian 2010 01 01)}, samplejournal2) `gives`
(defreportspec{_rsQuery=Date $ DateSpan (Just $ fromGregorian 2009 01 01) (Just $ fromGregorian 2010 01 01)}, samplejournal2) `gives`
([], nullmixedamt)

,test "with date2:" $
(defreportspec{rsQuery=Date2 $ DateSpan (Just $ fromGregorian 2009 01 01) (Just $ fromGregorian 2010 01 01)}, samplejournal2) `gives`
(defreportspec{_rsQuery=Date2 $ DateSpan (Just $ fromGregorian 2009 01 01) (Just $ fromGregorian 2010 01 01)}, samplejournal2) `gives`
([
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
,("income:salary","income:salary",0,mamountp' "$-1.00")
],
mixedAmount (usd 0))

,test "with desc:" $
(defreportspec{rsQuery=Desc $ toRegexCI' "income"}, samplejournal) `gives`
(defreportspec{_rsQuery=Desc $ toRegexCI' "income"}, samplejournal) `gives`
([
("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00")
,("income:salary","income:salary",0, mamountp' "$-1.00")
],
mixedAmount (usd 0))

,test "with not:desc:" $
(defreportspec{rsQuery=Not . Desc $ toRegexCI' "income"}, samplejournal) `gives`
(defreportspec{_rsQuery=Not . Desc $ toRegexCI' "income"}, samplejournal) `gives`
([
("assets:bank:saving","assets:bank:saving",0, mamountp' "$1.00")
,("assets:cash","assets:cash",0, mamountp' "$-2.00")
Expand All @@ -194,7 +194,7 @@ tests_BalanceReport = tests "BalanceReport" [
mixedAmount (usd 0))

,test "with period on a populated period" $
(defreportspec{rsOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2)}}, samplejournal) `gives`
(defreportspec{_rsReportOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2)}}, samplejournal) `gives`
(
[
("assets:bank:checking","assets:bank:checking",0, mamountp' "$1.00")
Expand All @@ -203,7 +203,7 @@ tests_BalanceReport = tests "BalanceReport" [
mixedAmount (usd 0))

,test "with period on an unpopulated period" $
(defreportspec{rsOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3)}}, samplejournal) `gives`
(defreportspec{_rsReportOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 2) (fromGregorian 2008 1 3)}}, samplejournal) `gives`
([], nullmixedamt)


Expand Down
6 changes: 3 additions & 3 deletions hledger-lib/Hledger/Reports/BudgetReport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ budgetReport rspec bopts reportspan j = dbg4 "sortedbudgetreport" budgetreport
where
-- Budget report demands ALTree mode to ensure subaccounts and subaccount budgets are properly handled
-- and that reports with and without --empty make sense when compared side by side
ropts = (rsOpts rspec){ accountlistmode_ = ALTree }
ropts = (_rsReportOpts rspec){ accountlistmode_ = ALTree }
showunbudgeted = empty_ ropts
budgetedaccts =
dbg3 "budgetedacctsinperiod" $
Expand All @@ -81,9 +81,9 @@ budgetReport rspec bopts reportspan j = dbg4 "sortedbudgetreport" budgetreport
actualj = journalWithBudgetAccountNames budgetedaccts showunbudgeted j
budgetj = journalAddBudgetGoalTransactions bopts ropts reportspan j
actualreport@(PeriodicReport actualspans _ _) =
dbg5 "actualreport" $ multiBalanceReport rspec{rsOpts=ropts{empty_=True}} actualj
dbg5 "actualreport" $ multiBalanceReport rspec{_rsReportOpts=ropts{empty_=True}} actualj
budgetgoalreport@(PeriodicReport _ budgetgoalitems budgetgoaltotals) =
dbg5 "budgetgoalreport" $ multiBalanceReport rspec{rsOpts=ropts{empty_=True}} budgetj
dbg5 "budgetgoalreport" $ multiBalanceReport rspec{_rsReportOpts=ropts{empty_=True}} budgetj
budgetgoalreport'
-- If no interval is specified:
-- budgetgoalreport's span might be shorter actualreport's due to periodic txns;
Expand Down
10 changes: 5 additions & 5 deletions hledger-lib/Hledger/Reports/EntriesReport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,14 +34,14 @@ type EntriesReportItem = Transaction

-- | Select transactions for an entries report.
entriesReport :: ReportSpec -> Journal -> EntriesReport
entriesReport rspec@ReportSpec{rsOpts=ropts} =
sortBy (comparing $ transactionDateFn ropts) . jtxns . filterJournalTransactions (rsQuery rspec)
. journalApplyValuationFromOpts rspec{rsOpts=ropts{show_costs_=True}}
entriesReport rspec@ReportSpec{_rsReportOpts=ropts} =
sortBy (comparing $ transactionDateFn ropts) . jtxns . filterJournalTransactions (_rsQuery rspec)
. journalApplyValuationFromOpts rspec{_rsReportOpts=ropts{show_costs_=True}}

tests_EntriesReport = tests "EntriesReport" [
tests "entriesReport" [
test "not acct" $ (length $ entriesReport defreportspec{rsQuery=Not . Acct $ toRegex' "bank"} samplejournal) @?= 1
,test "date" $ (length $ entriesReport defreportspec{rsQuery=Date $ DateSpan (Just $ fromGregorian 2008 06 01) (Just $ fromGregorian 2008 07 01)} samplejournal) @?= 3
test "not acct" $ (length $ entriesReport defreportspec{_rsQuery=Not . Acct $ toRegex' "bank"} samplejournal) @?= 1
,test "date" $ (length $ entriesReport defreportspec{_rsQuery=Date $ DateSpan (Just $ fromGregorian 2008 06 01) (Just $ fromGregorian 2008 07 01)} samplejournal) @?= 3
]
]

36 changes: 18 additions & 18 deletions hledger-lib/Hledger/Reports/MultiBalanceReport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ type ClippedAccountName = AccountName
-- by the bs/cf/is commands.
multiBalanceReport :: ReportSpec -> Journal -> MultiBalanceReport
multiBalanceReport rspec j = multiBalanceReportWith rspec j (journalPriceOracle infer j)
where infer = infer_value_ $ rsOpts rspec
where infer = infer_value_ $ _rsReportOpts rspec

-- | A helper for multiBalanceReport. This one takes an extra argument,
-- a PriceOracle to be used for looking up market prices. Commands which
Expand Down Expand Up @@ -126,7 +126,7 @@ multiBalanceReportWith rspec' j priceoracle = report
compoundBalanceReport :: ReportSpec -> Journal -> [CBCSubreportSpec a]
-> CompoundPeriodicReport a MixedAmount
compoundBalanceReport rspec j = compoundBalanceReportWith rspec j (journalPriceOracle infer j)
where infer = infer_value_ $ rsOpts rspec
where infer = infer_value_ $ _rsReportOpts rspec

-- | A helper for compoundBalanceReport, similar to multiBalanceReportWith.
compoundBalanceReportWith :: ReportSpec -> Journal -> PriceOracle
Expand All @@ -151,14 +151,14 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr
( cbcsubreporttitle
-- Postprocess the report, negating balances and taking percentages if needed
, cbcsubreporttransform $
generateMultiBalanceReport rspec{rsOpts=ropts} j priceoracle colps' startbals'
generateMultiBalanceReport rspec{_rsReportOpts=ropts} j priceoracle colps' startbals'
, cbcsubreportincreasestotal
)
where
-- Filter the column postings according to each subreport
colps' = filter (matchesPosting q) <$> colps
startbals' = HM.filterWithKey (\k _ -> matchesAccount q k) startbals
ropts = cbcsubreportoptions $ rsOpts rspec
ropts = cbcsubreportoptions $ _rsReportOpts rspec
q = cbcsubreportquery j

-- Sum the subreport totals by column. Handle these cases:
Expand All @@ -183,13 +183,13 @@ compoundBalanceReportWith rspec' j priceoracle subreportspecs = cbr
-- and startDate is not nothing, otherwise mempty? This currently gives a
-- failure with some totals which are supposed to be 0 being blank.
startingBalances :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> HashMap AccountName Account
startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle reportspan =
startingBalances rspec@ReportSpec{_rsQuery=query,_rsReportOpts=ropts} j priceoracle reportspan =
fmap (M.findWithDefault nullacct precedingspan) acctmap
where
acctmap = calculateReportMatrix rspec' j priceoracle mempty
. M.singleton precedingspan . map fst $ getPostings rspec' j priceoracle

rspec' = rspec{rsQuery=startbalq,rsOpts=ropts'}
rspec' = rspec{_rsQuery=startbalq,_rsReportOpts=ropts'}
-- If we're re-valuing every period, we need to have the unvalued start
-- balance, so we can do it ourselves later.
ropts' = case value_ ropts of
Expand Down Expand Up @@ -217,12 +217,12 @@ startingBalances rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle repo
makeReportQuery :: ReportSpec -> DateSpan -> ReportSpec
makeReportQuery rspec reportspan
| reportspan == nulldatespan = rspec
| otherwise = rspec{rsQuery=query}
| otherwise = rspec{_rsQuery=query}
where
query = simplifyQuery $ And [dateless $ rsQuery rspec, reportspandatesq]
query = simplifyQuery $ And [dateless $ _rsQuery rspec, reportspandatesq]
reportspandatesq = dbg3 "reportspandatesq" $ dateqcons reportspan
dateless = dbg3 "dateless" . filterQuery (not . queryIsDateOrDate2)
dateqcons = if date2_ (rsOpts rspec) then Date2 else Date
dateqcons = if date2_ (_rsReportOpts rspec) then Date2 else Date

-- | Group postings, grouped by their column
getPostingsByColumn :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> Map DateSpan [Posting]
Expand All @@ -232,7 +232,7 @@ getPostingsByColumn rspec j priceoracle reportspan = columns
ps :: [(Posting, Day)] = dbg5 "getPostingsByColumn" $ getPostings rspec j priceoracle

-- The date spans to be included as report columns.
colspans = dbg3 "colspans" $ splitSpan (interval_ $ rsOpts rspec) reportspan
colspans = dbg3 "colspans" $ splitSpan (interval_ $ _rsReportOpts rspec) reportspan
addPosting (p, d) = maybe id (M.adjust (p:)) $ latestSpanContaining colspans d
emptyMap = M.fromList . zip colspans $ repeat []

Expand All @@ -241,7 +241,7 @@ getPostingsByColumn rspec j priceoracle reportspan = columns

-- | Gather postings matching the query within the report period.
getPostings :: ReportSpec -> Journal -> PriceOracle -> [(Posting, Day)]
getPostings rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle =
getPostings rspec@ReportSpec{_rsQuery=query,_rsReportOpts=ropts} j priceoracle =
map (\p -> (p, date p)) .
journalPostings .
filterJournalAmounts symq . -- remove amount parts excluded by cur:
Expand All @@ -267,7 +267,7 @@ getPostings rspec@ReportSpec{rsQuery=query,rsOpts=ropts} j priceoracle =
-- each. Accounts and amounts will be depth-clipped appropriately if
-- a depth limit is in effect.
acctChangesFromPostings :: ReportSpec -> [Posting] -> HashMap ClippedAccountName Account
acctChangesFromPostings ReportSpec{rsQuery=query,rsOpts=ropts} ps =
acctChangesFromPostings ReportSpec{_rsQuery=query,_rsReportOpts=ropts} ps =
HM.fromList [(aname a, a) | a <- as]
where
as = filterAccounts . drop 1 $ accountsFromPostings ps
Expand All @@ -285,7 +285,7 @@ calculateReportMatrix :: ReportSpec -> Journal -> PriceOracle
-> HashMap ClippedAccountName Account
-> Map DateSpan [Posting]
-> HashMap ClippedAccountName (Map DateSpan Account)
calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals colps = -- PARTIAL:
calculateReportMatrix rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle startbals colps = -- PARTIAL:
-- Ensure all columns have entries, including those with starting balances
HM.mapWithKey rowbals allchanges
where
Expand Down Expand Up @@ -316,7 +316,7 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col

avalue = acctApplyBoth . mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle
acctApplyBoth f a = a{aibalance = f $ aibalance a, aebalance = f $ aebalance a}
addElided = if queryDepth (rsQuery rspec) == Just 0 then HM.insert "..." zeros else id
addElided = if queryDepth (_rsQuery rspec) == Just 0 then HM.insert "..." zeros else id
historicalDate = minimumMay $ mapMaybe spanStart colspans
zeros = M.fromList [(span, nullacct) | span <- colspans]
colspans = M.keys colps
Expand All @@ -328,7 +328,7 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col
generateMultiBalanceReport :: ReportSpec -> Journal -> PriceOracle
-> Map DateSpan [Posting] -> HashMap AccountName Account
-> MultiBalanceReport
generateMultiBalanceReport rspec@ReportSpec{rsOpts=ropts} j priceoracle colps startbals =
generateMultiBalanceReport rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle colps startbals =
report
where
-- Process changes into normal, cumulative, or historical amounts, plus value them
Expand Down Expand Up @@ -378,7 +378,7 @@ buildReportRows ropts displaynames =
-- their name and depth
displayedAccounts :: ReportSpec -> HashMap AccountName (Map DateSpan Account)
-> HashMap AccountName DisplayName
displayedAccounts ReportSpec{rsQuery=query,rsOpts=ropts} valuedaccts
displayedAccounts ReportSpec{_rsQuery=query,_rsReportOpts=ropts} valuedaccts
| depth == 0 = HM.singleton "..." $ DisplayName "..." "..." 1
| otherwise = HM.mapWithKey (\a _ -> displayedName a) displayedAccts
where
Expand Down Expand Up @@ -561,7 +561,7 @@ tests_MultiBalanceReport = tests "MultiBalanceReport" [
let
amt0 = Amount {acommodity="$", aquantity=0, aprice=Nothing, astyle=AmountStyle {ascommodityside = L, ascommodityspaced = False, asprecision = Precision 2, asdecimalpoint = Just '.', asdigitgroups = Nothing}}
(rspec,journal) `gives` r = do
let rspec' = rspec{rsQuery=And [queryFromFlags $ rsOpts rspec, rsQuery rspec]}
let rspec' = rspec{_rsQuery=And [queryFromFlags $ _rsReportOpts rspec, _rsQuery rspec]}
(eitems, etotal) = r
(PeriodicReport _ aitems atotal) = multiBalanceReport rspec' journal
showw (PeriodicReportRow a lAmt amt amt')
Expand All @@ -574,7 +574,7 @@ tests_MultiBalanceReport = tests "MultiBalanceReport" [
(defreportspec, nulljournal) `gives` ([], nullmixedamt)

,test "with -H on a populated period" $
(defreportspec{rsOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balanceaccum_=Historical}}, samplejournal) `gives`
(defreportspec{_rsReportOpts=defreportopts{period_= PeriodBetween (fromGregorian 2008 1 1) (fromGregorian 2008 1 2), balanceaccum_=Historical}}, samplejournal) `gives`
(
[ PeriodicReportRow (flatDisplayName "assets:bank:checking") [mamountp' "$1.00"] (mamountp' "$1.00") (mixedAmount amt0{aquantity=1})
, PeriodicReportRow (flatDisplayName "income:salary") [mamountp' "$-1.00"] (mamountp' "$-1.00") (mixedAmount amt0{aquantity=(-1)})
Expand Down
Loading

0 comments on commit 9ba84e2

Please sign in to comment.