mirror of
https://github.com/simonmichael/hledger.git
synced 2024-12-26 20:02:27 +03:00
lib!: Rename the fields of ReportSpec.
This is done to be more consistent with future field naming conventions, and to make automatic generation of lenses simpler. See discussion in \#1545. rsOpts -> _rsReportOpts rsToday -> _rsDay rsQuery -> _rsQuery rsQueryOpts -> _rsQueryOpts
This commit is contained in:
parent
7ed2a0aa9b
commit
b0aa70b27a
@ -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
|
||||
|
@ -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)
|
||||
@ -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")
|
||||
@ -147,7 +147,7 @@ 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")
|
||||
@ -155,7 +155,7 @@ tests_BalanceReport = tests "BalanceReport" [
|
||||
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")
|
||||
@ -163,11 +163,11 @@ tests_BalanceReport = tests "BalanceReport" [
|
||||
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")
|
||||
@ -175,7 +175,7 @@ tests_BalanceReport = tests "BalanceReport" [
|
||||
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")
|
||||
@ -183,7 +183,7 @@ tests_BalanceReport = tests "BalanceReport" [
|
||||
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")
|
||||
@ -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")
|
||||
@ -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)
|
||||
|
||||
|
||||
|
@ -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" $
|
||||
@ -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;
|
||||
|
@ -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
|
||||
]
|
||||
]
|
||||
|
||||
|
@ -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
|
||||
@ -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
|
||||
@ -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:
|
||||
@ -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
|
||||
@ -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]
|
||||
@ -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 []
|
||||
|
||||
@ -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:
|
||||
@ -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
|
||||
@ -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
|
||||
@ -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
|
||||
@ -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
|
||||
@ -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
|
||||
@ -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')
|
||||
@ -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)})
|
||||
|
@ -63,11 +63,11 @@ type SummaryPosting = (Posting, Day)
|
||||
-- | Select postings from the journal and add running balance and other
|
||||
-- information to make a postings report. Used by eg hledger's register command.
|
||||
postingsReport :: ReportSpec -> Journal -> PostingsReport
|
||||
postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items
|
||||
postingsReport rspec@ReportSpec{_rsReportOpts=ropts@ReportOpts{..}} j = items
|
||||
where
|
||||
reportspan = reportSpanBothDates j rspec
|
||||
whichdate = whichDateFromOpts ropts
|
||||
mdepth = queryDepth $ rsQuery rspec
|
||||
mdepth = queryDepth $ _rsQuery rspec
|
||||
multiperiod = interval_ /= NoInterval
|
||||
|
||||
-- postings to be included in the report, and similarly-matched postings before the report start date
|
||||
@ -114,7 +114,7 @@ registerRunningCalculationFn ropts
|
||||
-- Date restrictions and depth restrictions in the query are ignored.
|
||||
-- A helper for the postings report.
|
||||
matchedPostingsBeforeAndDuring :: ReportSpec -> Journal -> DateSpan -> ([Posting],[Posting])
|
||||
matchedPostingsBeforeAndDuring rspec@ReportSpec{rsOpts=ropts,rsQuery=q} j reportspan =
|
||||
matchedPostingsBeforeAndDuring rspec@ReportSpec{_rsReportOpts=ropts,_rsQuery=q} j reportspan =
|
||||
dbg5 "beforeps, duringps" $ span (beforestartq `matchesPosting`) beforeandduringps
|
||||
where
|
||||
beforestartq = dbg3 "beforestartq" $ dateqtype $ DateSpan Nothing $ spanStart reportspan
|
||||
@ -223,7 +223,7 @@ negatePostingAmount = postingTransformAmount negate
|
||||
tests_PostingsReport = tests "PostingsReport" [
|
||||
|
||||
test "postingsReport" $ do
|
||||
let (query, journal) `gives` n = (length $ postingsReport defreportspec{rsQuery=query} journal) @?= n
|
||||
let (query, journal) `gives` n = (length $ postingsReport defreportspec{_rsQuery=query} journal) @?= n
|
||||
-- with the query specified explicitly
|
||||
(Any, nulljournal) `gives` 0
|
||||
(Any, samplejournal) `gives` 13
|
||||
@ -233,9 +233,9 @@ tests_PostingsReport = tests "PostingsReport" [
|
||||
(And [And [Depth 1, StatusQ Cleared], Acct (toRegex' "expenses")], samplejournal) `gives` 2
|
||||
-- with query and/or command-line options
|
||||
(length $ postingsReport defreportspec samplejournal) @?= 13
|
||||
(length $ postingsReport defreportspec{rsOpts=defreportopts{interval_=Months 1}} samplejournal) @?= 11
|
||||
(length $ postingsReport defreportspec{rsOpts=defreportopts{interval_=Months 1, empty_=True}} samplejournal) @?= 20
|
||||
(length $ postingsReport defreportspec{rsQuery=Acct $ toRegex' "assets:bank:checking"} samplejournal) @?= 5
|
||||
(length $ postingsReport defreportspec{_rsReportOpts=defreportopts{interval_=Months 1}} samplejournal) @?= 11
|
||||
(length $ postingsReport defreportspec{_rsReportOpts=defreportopts{interval_=Months 1, empty_=True}} samplejournal) @?= 20
|
||||
(length $ postingsReport defreportspec{_rsQuery=Acct $ toRegex' "assets:bank:checking"} samplejournal) @?= 5
|
||||
|
||||
-- (defreportopts, And [Acct "a a", Acct "'b"], samplejournal2) `gives` 0
|
||||
-- [(Just (fromGregorian 2008 01 01,"income"),assets:bank:checking $1,$1)
|
||||
|
@ -236,20 +236,20 @@ rawOptsToReportOpts rawopts = do
|
||||
-- `reportOptsToSpec` to regenerate the ReportSpec with the new
|
||||
-- Query.
|
||||
data ReportSpec = ReportSpec
|
||||
{ rsOpts :: ReportOpts -- ^ The underlying ReportOpts used to generate this ReportSpec
|
||||
, rsToday :: Day -- ^ The Day this ReportSpec is generated for
|
||||
, rsQuery :: Query -- ^ The generated Query for the given day
|
||||
, rsQueryOpts :: [QueryOpt] -- ^ A list of QueryOpts for the given day
|
||||
{ _rsReportOpts :: ReportOpts -- ^ The underlying ReportOpts used to generate this ReportSpec
|
||||
, _rsDay :: Day -- ^ The Day this ReportSpec is generated for
|
||||
, _rsQuery :: Query -- ^ The generated Query for the given day
|
||||
, _rsQueryOpts :: [QueryOpt] -- ^ A list of QueryOpts for the given day
|
||||
} deriving (Show)
|
||||
|
||||
instance Default ReportSpec where def = defreportspec
|
||||
|
||||
defreportspec :: ReportSpec
|
||||
defreportspec = ReportSpec
|
||||
{ rsOpts = def
|
||||
, rsToday = nulldate
|
||||
, rsQuery = Any
|
||||
, rsQueryOpts = []
|
||||
{ _rsReportOpts = def
|
||||
, _rsDay = nulldate
|
||||
, _rsQuery = Any
|
||||
, _rsQueryOpts = []
|
||||
}
|
||||
|
||||
-- | Generate a ReportSpec from a set of ReportOpts on a given day.
|
||||
@ -257,22 +257,22 @@ reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec
|
||||
reportOptsToSpec day ropts = do
|
||||
(argsquery, queryopts) <- parseQueryList day $ querystring_ ropts
|
||||
return ReportSpec
|
||||
{ rsOpts = ropts
|
||||
, rsToday = day
|
||||
, rsQuery = simplifyQuery $ And [queryFromFlags ropts, argsquery]
|
||||
, rsQueryOpts = queryopts
|
||||
{ _rsReportOpts = ropts
|
||||
, _rsDay = day
|
||||
, _rsQuery = simplifyQuery $ And [queryFromFlags ropts, argsquery]
|
||||
, _rsQueryOpts = queryopts
|
||||
}
|
||||
|
||||
-- | Update the ReportOpts and the fields derived from it in a ReportSpec,
|
||||
-- or return an error message if there is a problem such as missing or
|
||||
-- unparseable options data. This is the safe way to change a ReportSpec,
|
||||
-- ensuring that all fields (rsQuery, rsOpts, querystring_, etc.) are in sync.
|
||||
-- or return an error message if there is a problem such as missing or
|
||||
-- unparseable options data. This is the safe way to change a ReportSpec,
|
||||
-- ensuring that all fields (_rsQuery, _rsReportOpts, querystring_, etc.) are in sync.
|
||||
updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec
|
||||
updateReportSpec ropts rspec = reportOptsToSpec (rsToday rspec) ropts
|
||||
updateReportSpec ropts rspec = reportOptsToSpec (_rsDay rspec) ropts
|
||||
|
||||
-- | Like updateReportSpec, but takes a ReportOpts-modifying function.
|
||||
updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec
|
||||
updateReportSpecWith f rspec = reportOptsToSpec (rsToday rspec) . f $ rsOpts rspec
|
||||
updateReportSpecWith f rspec = reportOptsToSpec (_rsDay rspec) . f $ _rsReportOpts rspec
|
||||
|
||||
-- | Generate a ReportSpec from RawOpts and the current date.
|
||||
rawOptsToReportSpec :: RawOpts -> IO ReportSpec
|
||||
@ -503,14 +503,14 @@ flat_ = not . tree_
|
||||
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
|
||||
journalApplyValuationFromOpts rspec j =
|
||||
journalApplyValuationFromOptsWith rspec j priceoracle
|
||||
where priceoracle = journalPriceOracle (infer_value_ $ rsOpts rspec) j
|
||||
where priceoracle = journalPriceOracle (infer_value_ $ _rsReportOpts rspec) j
|
||||
|
||||
-- | Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.
|
||||
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
|
||||
journalApplyValuationFromOptsWith rspec@ReportSpec{rsOpts=ropts} j priceoracle =
|
||||
journalApplyValuationFromOptsWith rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle =
|
||||
journalMapPostings valuation $ costing j
|
||||
where
|
||||
valuation p = maybe id (postingApplyValuation priceoracle styles (periodEnd p) (rsToday rspec)) (value_ ropts) p
|
||||
valuation p = maybe id (postingApplyValuation priceoracle styles (periodEnd p) (_rsDay rspec)) (value_ ropts) p
|
||||
costing = case cost_ ropts of
|
||||
Cost -> journalToCost
|
||||
NoCost -> id
|
||||
@ -579,7 +579,7 @@ reportSpanBothDates = reportSpanHelper True
|
||||
-- | A helper for reportSpan, which takes a Bool indicating whether to use both
|
||||
-- primary and secondary dates.
|
||||
reportSpanHelper :: Bool -> Journal -> ReportSpec -> DateSpan
|
||||
reportSpanHelper bothdates j ReportSpec{rsQuery=query, rsOpts=ropts} = reportspan
|
||||
reportSpanHelper bothdates j ReportSpec{_rsQuery=query, _rsReportOpts=ropts} = reportspan
|
||||
where
|
||||
-- The date span specified by -b/-e/-p options and query args if any.
|
||||
requestedspan = dbg3 "requestedspan" $ if bothdates then queryDateSpan' query else queryDateSpan (date2_ ropts) query
|
||||
@ -613,7 +613,7 @@ reportEndDate j = spanEnd . reportSpan j
|
||||
-- Get the report's start date.
|
||||
-- If no report period is specified, will be Nothing.
|
||||
reportPeriodStart :: ReportSpec -> Maybe Day
|
||||
reportPeriodStart = queryStartDate False . rsQuery
|
||||
reportPeriodStart = queryStartDate False . _rsQuery
|
||||
|
||||
-- Get the report's start date, or if no report period is specified,
|
||||
-- the journal's start date (the earliest posting date). If there's no
|
||||
@ -627,7 +627,7 @@ reportPeriodOrJournalStart rspec j =
|
||||
-- more commonly used, exclusive, report end date).
|
||||
-- If no report period is specified, will be Nothing.
|
||||
reportPeriodLastDay :: ReportSpec -> Maybe Day
|
||||
reportPeriodLastDay = fmap (addDays (-1)) . queryEndDate False . rsQuery
|
||||
reportPeriodLastDay = fmap (addDays (-1)) . queryEndDate False . _rsQuery
|
||||
|
||||
-- Get the last day of the overall report period, or if no report
|
||||
-- period is specified, the last day of the journal (ie the latest
|
||||
@ -637,7 +637,7 @@ reportPeriodLastDay = fmap (addDays (-1)) . queryEndDate False . rsQuery
|
||||
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day
|
||||
reportPeriodOrJournalLastDay rspec j = reportPeriodLastDay rspec <|> journalOrPriceEnd
|
||||
where
|
||||
journalOrPriceEnd = case value_ $ rsOpts rspec of
|
||||
journalOrPriceEnd = case value_ $ _rsReportOpts rspec of
|
||||
Just (AtEnd _) -> max (journalLastDay False j) lastPriceDirective
|
||||
_ -> journalLastDay False j
|
||||
lastPriceDirective = fmap (addDays 1) . maximumMay . map pddate $ jpricedirectives j
|
||||
|
@ -49,7 +49,7 @@ accountsScreen = AccountsScreen{
|
||||
|
||||
asInit :: Day -> Bool -> UIState -> UIState
|
||||
asInit d reset ui@UIState{
|
||||
aopts=UIOpts{cliopts_=CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}},
|
||||
aopts=UIOpts{cliopts_=CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}},
|
||||
ajournal=j,
|
||||
aScreen=s@AccountsScreen{}
|
||||
} =
|
||||
@ -77,7 +77,7 @@ asInit d reset ui@UIState{
|
||||
as = map asItemAccountName displayitems
|
||||
|
||||
-- Further restrict the query based on the current period and future/forecast mode.
|
||||
rspec' = rspec{rsQuery=simplifyQuery $ And [rsQuery rspec, periodq, excludeforecastq (forecast_ ropts)]}
|
||||
rspec' = rspec{_rsQuery=simplifyQuery $ And [_rsQuery rspec, periodq, excludeforecastq (forecast_ ropts)]}
|
||||
where
|
||||
periodq = Date $ periodAsDateSpan $ period_ ropts
|
||||
-- Except in forecast mode, exclude future/forecast transactions.
|
||||
@ -152,7 +152,7 @@ asDraw UIState{aopts=_uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec}}
|
||||
render $ defaultLayout toplabel bottomlabel $ renderList (asDrawItem colwidths) True (_asList s)
|
||||
|
||||
where
|
||||
ropts = rsOpts rspec
|
||||
ropts = _rsReportOpts rspec
|
||||
ishistorical = balanceaccum_ ropts == Historical
|
||||
|
||||
toplabel =
|
||||
|
@ -182,13 +182,13 @@ uiReloadJournalIfChanged copts d j ui = do
|
||||
-- or in the provided UIState's startup options,
|
||||
-- it is preserved.
|
||||
enableForecastPreservingPeriod :: UIState -> CliOpts -> CliOpts
|
||||
enableForecastPreservingPeriod ui copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}} =
|
||||
copts{reportspec_=rspec{rsOpts=ropts{forecast_=mforecast}}}
|
||||
enableForecastPreservingPeriod ui copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}} =
|
||||
copts{reportspec_=rspec{_rsReportOpts=ropts{forecast_=mforecast}}}
|
||||
where
|
||||
mforecast = asum [mprovidedforecastperiod, mstartupforecastperiod, mdefaultforecastperiod]
|
||||
where
|
||||
mprovidedforecastperiod = forecast_ ropts
|
||||
mstartupforecastperiod = forecast_ $ rsOpts $ reportspec_ $ cliopts_ $ astartupopts ui
|
||||
mstartupforecastperiod = forecast_ $ _rsReportOpts $ reportspec_ $ cliopts_ $ astartupopts ui
|
||||
mdefaultforecastperiod = Just nulldatespan
|
||||
|
||||
-- Re-check any balance assertions in the current journal, and if any
|
||||
|
@ -43,11 +43,11 @@ writeChan = BC.writeBChan
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
opts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rspec@ReportSpec{rsOpts=ropts},rawopts_=rawopts}} <- getHledgerUIOpts
|
||||
opts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rspec@ReportSpec{_rsReportOpts=ropts},rawopts_=rawopts}} <- getHledgerUIOpts
|
||||
-- when (debug_ $ cliopts_ opts) $ printf "%s\n" prognameandversion >> printf "opts: %s\n" (show opts)
|
||||
|
||||
-- always generate forecasted periodic transactions; their visibility will be toggled by the UI.
|
||||
let copts' = copts{reportspec_=rspec{rsOpts=ropts{forecast_=Just $ fromMaybe nulldatespan (forecast_ ropts)}}}
|
||||
let copts' = copts{reportspec_=rspec{_rsReportOpts=ropts{forecast_=Just $ fromMaybe nulldatespan (forecast_ ropts)}}}
|
||||
|
||||
case True of
|
||||
_ | "help" `inRawOpts` rawopts -> putStr (showModeUsage uimode)
|
||||
@ -58,7 +58,7 @@ main = do
|
||||
_ -> withJournalDo copts' (runBrickUi opts)
|
||||
|
||||
runBrickUi :: UIOpts -> Journal -> IO ()
|
||||
runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rspec@ReportSpec{rsOpts=ropts}}} j = do
|
||||
runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}} j = do
|
||||
d <- getCurrentDay
|
||||
|
||||
let
|
||||
@ -103,9 +103,9 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rsp
|
||||
uopts' = uopts{
|
||||
cliopts_=copts{
|
||||
reportspec_=rspec{
|
||||
rsQuery=filteredQuery $ rsQuery rspec, -- query with depth/date parts removed
|
||||
rsOpts=ropts{
|
||||
depth_ =queryDepth $ rsQuery rspec, -- query's depth part
|
||||
_rsQuery=filteredQuery $ _rsQuery rspec, -- query with depth/date parts removed
|
||||
_rsReportOpts=ropts{
|
||||
depth_ =queryDepth $ _rsQuery rspec, -- query's depth part
|
||||
period_=periodfromoptsandargs, -- query's date part
|
||||
no_elide_=True, -- avoid squashing boring account names, for a more regular tree (unlike hledger)
|
||||
empty_=not $ empty_ ropts, -- show zero items by default, hide them with -E (unlike hledger)
|
||||
@ -115,7 +115,7 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportspec_=rsp
|
||||
}
|
||||
}
|
||||
where
|
||||
datespanfromargs = queryDateSpan (date2_ ropts) $ rsQuery rspec
|
||||
datespanfromargs = queryDateSpan (date2_ ropts) $ _rsQuery rspec
|
||||
periodfromoptsandargs =
|
||||
dateSpanAsPeriod $ spansIntersect [periodAsDateSpan $ period_ ropts, datespanfromargs]
|
||||
filteredQuery q = simplifyQuery $ And [queryFromFlags ropts, filtered q]
|
||||
|
@ -56,7 +56,7 @@ rsSetAccount a forceinclusive scr@RegisterScreen{} =
|
||||
rsSetAccount _ _ scr = scr
|
||||
|
||||
rsInit :: Day -> Bool -> UIState -> UIState
|
||||
rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}, ajournal=j, aScreen=s@RegisterScreen{..}} =
|
||||
rsInit d reset ui@UIState{aopts=_uopts@UIOpts{cliopts_=CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}, ajournal=j, aScreen=s@RegisterScreen{..}} =
|
||||
ui{aScreen=s{rsList=newitems'}}
|
||||
where
|
||||
-- gather arguments and queries
|
||||
@ -74,7 +74,7 @@ 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{rsToday=d}
|
||||
updateReportSpec ropts' rspec{_rsDay=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
|
||||
@ -84,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 (rsQuery rspec') thisacctq t
|
||||
RegisterScreenItem{rsItemDate = showDate $ transactionRegisterDate (_rsQuery rspec') thisacctq t
|
||||
,rsItemStatus = tstatus t
|
||||
,rsItemDescription = tdescription t
|
||||
,rsItemOtherAccounts = otheracctsstr
|
||||
@ -188,7 +188,7 @@ rsDraw UIState{aopts=_uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec}}
|
||||
render $ defaultLayout toplabel bottomlabel $ renderList (rsDrawItem colwidths) True rsList
|
||||
|
||||
where
|
||||
ropts = rsOpts rspec
|
||||
ropts = _rsReportOpts rspec
|
||||
ishistorical = balanceaccum_ ropts == Historical
|
||||
-- inclusive = tree_ ropts || rsForceInclusive
|
||||
|
||||
|
@ -60,7 +60,7 @@ tsInit _d _reset ui@UIState{aopts=UIOpts{cliopts_=CliOpts{reportspec_=_rspec}}
|
||||
tsInit _ _ _ = error "init function called with wrong screen type, should not happen" -- PARTIAL:
|
||||
|
||||
tsDraw :: UIState -> [Widget Name]
|
||||
tsDraw UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}
|
||||
tsDraw UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}
|
||||
,ajournal=j
|
||||
,aScreen=TransactionScreen{tsTransaction=(i,t')
|
||||
,tsTransactions=nts
|
||||
@ -85,7 +85,7 @@ tsDraw UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{
|
||||
|
||||
render . defaultLayout toplabel bottomlabel . str
|
||||
. T.unpack . showTransactionOneLineAmounts
|
||||
. maybe id (transactionApplyValuation prices styles periodlast (rsToday rspec)) (value_ ropts)
|
||||
. maybe id (transactionApplyValuation prices styles periodlast (_rsDay rspec)) (value_ ropts)
|
||||
$ case cost_ ropts of
|
||||
Cost -> transactionToCost styles t
|
||||
NoCost -> t
|
||||
|
@ -100,23 +100,23 @@ complement = ([minBound..maxBound] \\)
|
||||
|
||||
-- | Toggle between showing all and showing only nonempty (more precisely, nonzero) items.
|
||||
toggleEmpty :: UIState -> UIState
|
||||
toggleEmpty ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=toggleEmpty ropts}}}}
|
||||
toggleEmpty ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=toggleEmpty ropts}}}}
|
||||
where
|
||||
toggleEmpty ropts = ropts{empty_=not $ empty_ ropts}
|
||||
|
||||
-- | Toggle between showing the primary amounts or costs.
|
||||
toggleCost :: UIState -> UIState
|
||||
toggleCost ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{cost_ = toggle $ cost_ ropts}}}}}
|
||||
toggleCost ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=ropts{cost_ = toggle $ cost_ ropts}}}}}
|
||||
where
|
||||
toggle Cost = NoCost
|
||||
toggle NoCost = Cost
|
||||
|
||||
-- | Toggle between showing primary amounts or default valuation.
|
||||
toggleValue :: UIState -> UIState
|
||||
toggleValue ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{
|
||||
toggleValue ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=ropts{
|
||||
value_ = valuationToggleValue $ value_ ropts}}}}}
|
||||
|
||||
-- | Basic toggling of -V, for hledger-ui.
|
||||
@ -126,18 +126,18 @@ valuationToggleValue _ = Just $ AtEnd Nothing
|
||||
|
||||
-- | Set hierarchic account tree mode.
|
||||
setTree :: UIState -> UIState
|
||||
setTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{accountlistmode_=ALTree}}}}}
|
||||
setTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=ropts{accountlistmode_=ALTree}}}}}
|
||||
|
||||
-- | Set flat account list mode.
|
||||
setList :: UIState -> UIState
|
||||
setList ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{accountlistmode_=ALFlat}}}}}
|
||||
setList ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=ropts{accountlistmode_=ALFlat}}}}}
|
||||
|
||||
-- | Toggle between flat and tree mode. If current mode is unspecified/default, assume it's flat.
|
||||
toggleTree :: UIState -> UIState
|
||||
toggleTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=toggleTreeMode ropts}}}}
|
||||
toggleTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=toggleTreeMode ropts}}}}
|
||||
where
|
||||
toggleTreeMode ropts
|
||||
| accountlistmode_ ropts == ALTree = ropts{accountlistmode_=ALFlat}
|
||||
@ -145,8 +145,8 @@ toggleTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspe
|
||||
|
||||
-- | Toggle between historical balances and period balances.
|
||||
toggleHistorical :: UIState -> UIState
|
||||
toggleHistorical ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{balanceaccum_=b}}}}}
|
||||
toggleHistorical ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=ropts{balanceaccum_=b}}}}}
|
||||
where
|
||||
b | balanceaccum_ ropts == Historical = PerPeriod
|
||||
| otherwise = Historical
|
||||
@ -157,7 +157,7 @@ toggleHistorical ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec
|
||||
-- (which are usually but not necessarily future-dated).
|
||||
-- In normal mode, both of these are hidden.
|
||||
toggleForecast :: Day -> UIState -> UIState
|
||||
toggleForecast d ui@UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=ReportSpec{rsOpts=ropts}}}} =
|
||||
toggleForecast d ui@UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
uiSetForecast ui $
|
||||
case forecast_ ropts of
|
||||
Just _ -> Nothing
|
||||
@ -166,10 +166,10 @@ toggleForecast d ui@UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=Repo
|
||||
-- | Helper: set forecast mode (with the given forecast period) on or off in the UI state.
|
||||
uiSetForecast :: UIState -> Maybe DateSpan -> UIState
|
||||
uiSetForecast
|
||||
ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}}
|
||||
ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}}
|
||||
mforecast =
|
||||
-- we assume forecast mode has no effect on ReportSpec's derived fields
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{forecast_=mforecast}}}}}
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{_rsReportOpts=ropts{forecast_=mforecast}}}}}
|
||||
|
||||
-- | Toggle between showing all and showing only real (non-virtual) items.
|
||||
toggleReal :: UIState -> UIState
|
||||
@ -209,7 +209,7 @@ moveReportPeriodToDate d = updateReportPeriod (periodMoveTo d)
|
||||
|
||||
-- | Get the report period.
|
||||
reportPeriod :: UIState -> Period
|
||||
reportPeriod = period_ . rsOpts . reportspec_ . cliopts_ . aopts
|
||||
reportPeriod = period_ . _rsReportOpts . reportspec_ . cliopts_ . aopts
|
||||
|
||||
-- | Set the report period.
|
||||
setReportPeriod :: Period -> UIState -> UIState
|
||||
@ -237,11 +237,11 @@ setFilter s ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rsp
|
||||
|
||||
-- | Reset some filters & toggles.
|
||||
resetFilter :: UIState -> UIState
|
||||
resetFilter ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} =
|
||||
resetFilter ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}}} =
|
||||
ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{
|
||||
rsQuery=Any
|
||||
,rsQueryOpts=[]
|
||||
,rsOpts=ropts{
|
||||
_rsQuery=Any
|
||||
,_rsQueryOpts=[]
|
||||
,_rsReportOpts=ropts{
|
||||
empty_=True
|
||||
,statuses_=[]
|
||||
,real_=False
|
||||
@ -282,7 +282,7 @@ setDepth :: Maybe Int -> UIState -> UIState
|
||||
setDepth mdepth = updateReportDepth (const mdepth)
|
||||
|
||||
getDepth :: UIState -> Maybe Int
|
||||
getDepth = depth_ . rsOpts . reportspec_ . cliopts_ . aopts
|
||||
getDepth = depth_ . _rsReportOpts . reportspec_ . cliopts_ . aopts
|
||||
|
||||
-- | Update report depth by a applying a function. If asked to set a depth less
|
||||
-- than zero, it will leave it unchanged.
|
||||
@ -302,7 +302,7 @@ showMinibuffer ui = setMode (Minibuffer e) ui
|
||||
where
|
||||
e = applyEdit gotoEOL $ editor MinibufferEditor (Just 1) oldq
|
||||
oldq = T.unpack . T.unwords . map textQuoteIfNeeded
|
||||
. querystring_ . rsOpts . reportspec_ . cliopts_ $ aopts ui
|
||||
. querystring_ . _rsReportOpts . reportspec_ . cliopts_ $ aopts ui
|
||||
|
||||
-- | Close the minibuffer, discarding any edit in progress.
|
||||
closeMinibuffer :: UIState -> UIState
|
||||
|
@ -116,12 +116,12 @@ instance Yesod App where
|
||||
hideEmptyAccts <- (== Just "1") . lookup "hideemptyaccts" . reqCookies <$> getRequest
|
||||
|
||||
let rspec = reportspec_ (cliopts_ opts)
|
||||
ropts = rsOpts rspec
|
||||
ropts' = (rsOpts rspec)
|
||||
ropts = _rsReportOpts rspec
|
||||
ropts' = (_rsReportOpts rspec)
|
||||
{accountlistmode_ = ALTree -- force tree mode for sidebar
|
||||
,empty_ = not (empty_ ropts) -- show zero items by default
|
||||
}
|
||||
rspec' = rspec{rsQuery=m,rsOpts=ropts'}
|
||||
rspec' = rspec{_rsQuery=m,_rsReportOpts=ropts'}
|
||||
accounts =
|
||||
balanceReportAsHtml (JournalR, RegisterR) here hideEmptyAccts j q qopts $
|
||||
balanceReport rspec' j
|
||||
@ -198,14 +198,14 @@ instance Show Text.Blaze.Markup where show _ = "<blaze markup>"
|
||||
-- | Gather data used by handlers and templates in the current request.
|
||||
getViewData :: Handler ViewData
|
||||
getViewData = do
|
||||
App{appOpts=opts@WebOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts}}}, appJournal} <- getYesod
|
||||
App{appOpts=opts@WebOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts}}}, appJournal} <- getYesod
|
||||
today <- liftIO getCurrentDay
|
||||
|
||||
-- try to read the latest journal content, keeping the old content
|
||||
-- if there's an error
|
||||
(j, mjerr) <- getCurrentJournal
|
||||
appJournal
|
||||
copts{reportspec_=rspec{rsOpts=rsOpts{no_elide_=True}}}
|
||||
copts{reportspec_=rspec{_rsReportOpts=_rsReportOpts{no_elide_=True}}}
|
||||
today
|
||||
|
||||
-- try to parse the query param, assuming no query if there's an error
|
||||
@ -259,7 +259,7 @@ getCurrentJournal jref opts d = do
|
||||
j <- liftIO (readIORef jref)
|
||||
(ej, changed) <- liftIO $ journalReloadIfChanged opts d j
|
||||
-- re-apply any initial filter specified at startup
|
||||
let initq = rsQuery $ reportspec_ opts
|
||||
let initq = _rsQuery $ reportspec_ opts
|
||||
case (changed, filterJournalTransactions initq <$> ej) of
|
||||
(False, _) -> return (j, Nothing)
|
||||
(True, Right j') -> do
|
||||
|
@ -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)])
|
||||
rspec = (reportspec_ $ cliopts_ opts){rsQuery = m}
|
||||
rspec = (reportspec_ $ cliopts_ opts){_rsQuery = m}
|
||||
items = reverse $ entriesReport rspec j
|
||||
transactionFrag = transactionFragment j
|
||||
|
||||
|
@ -105,5 +105,5 @@ getAccounttransactionsR a = do
|
||||
rspec = defreportspec
|
||||
thisacctq = Acct $ accountNameToAccountRegex a -- includes subs
|
||||
selectRep $ do
|
||||
provideJson $ accountTransactionsReport rspec{rsQuery=Any} j thisacctq
|
||||
provideJson $ accountTransactionsReport rspec{_rsQuery=Any} j thisacctq
|
||||
|
||||
|
@ -44,9 +44,9 @@ getRegisterR = do
|
||||
zip xs $
|
||||
zip (map (T.unpack . accountSummarisedName . paccount) xs) $
|
||||
tail $ (", "<$xs) ++ [""]
|
||||
items = accountTransactionsReport rspec{rsQuery=m} j acctQuery
|
||||
items = accountTransactionsReport rspec{_rsQuery=m} j acctQuery
|
||||
balancelabel
|
||||
| isJust (inAccount qopts), balanceaccum_ (rsOpts rspec) == Historical = "Historical Total"
|
||||
| isJust (inAccount qopts), balanceaccum_ (_rsReportOpts rspec) == Historical = "Historical Total"
|
||||
| isJust (inAccount qopts) = "Period Total"
|
||||
| otherwise = "Total"
|
||||
transactionFrag = transactionFragment j
|
||||
|
@ -66,7 +66,7 @@ hledgerWebMain = do
|
||||
-- | The hledger web command.
|
||||
web :: WebOpts -> Journal -> IO ()
|
||||
web opts j = do
|
||||
let initq = rsQuery . reportspec_ $ cliopts_ opts
|
||||
let initq = _rsQuery . reportspec_ $ cliopts_ opts
|
||||
j' = filterJournalTransactions initq j
|
||||
h = host_ opts
|
||||
p = port_ opts
|
||||
|
@ -527,7 +527,7 @@ getHledgerCliOpts' mode' args' = do
|
||||
putStrLn $ "running: " ++ progname'
|
||||
putStrLn $ "raw args: " ++ show args'
|
||||
putStrLn $ "processed opts:\n" ++ show opts
|
||||
putStrLn $ "search query: " ++ show (rsQuery $ reportspec_ opts)
|
||||
putStrLn $ "search query: " ++ show (_rsQuery $ reportspec_ opts)
|
||||
|
||||
getHledgerCliOpts :: Mode RawOpts -> IO CliOpts
|
||||
getHledgerCliOpts mode' = do
|
||||
|
@ -44,7 +44,7 @@ accountsmode = hledgerCommandMode
|
||||
|
||||
-- | The accounts command.
|
||||
accounts :: CliOpts -> Journal -> IO ()
|
||||
accounts CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{rsQuery=query,rsOpts=ropts}} j = do
|
||||
accounts CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query,_rsReportOpts=ropts}} j = do
|
||||
|
||||
-- 1. identify the accounts we'll show
|
||||
let tree = tree_ ropts
|
||||
|
@ -33,7 +33,7 @@ activity :: CliOpts -> Journal -> IO ()
|
||||
activity CliOpts{reportspec_=rspec} j = putStr $ showHistogram rspec j
|
||||
|
||||
showHistogram :: ReportSpec -> Journal -> String
|
||||
showHistogram ReportSpec{rsQuery=q,rsOpts=ReportOpts{interval_=i,date2_=date2}} j =
|
||||
showHistogram ReportSpec{_rsQuery=q,_rsReportOpts=ReportOpts{interval_=i,date2_=date2}} j =
|
||||
concatMap (printDayWith countBar) spanps
|
||||
where
|
||||
interval | i == NoInterval = Days 1
|
||||
|
@ -464,7 +464,7 @@ registerFromString s = do
|
||||
return . postingsReportAsText opts $ postingsReport rspec j
|
||||
where
|
||||
ropts = defreportopts{empty_=True}
|
||||
rspec = defreportspec{rsOpts=ropts}
|
||||
rspec = defreportspec{_rsReportOpts=ropts}
|
||||
opts = defcliopts{reportspec_=rspec}
|
||||
|
||||
capitalize :: String -> String
|
||||
|
@ -79,7 +79,7 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
||||
-- gather report options
|
||||
inclusive = True -- tree_ ropts
|
||||
thisacctq = Acct $ (if inclusive then accountNameToAccountRegex else accountNameToAccountOnlyRegex) acct
|
||||
ropts' = (rsOpts rspec) {
|
||||
ropts' = (_rsReportOpts rspec) {
|
||||
-- ignore any depth limit, as in postingsReport; allows register's total to match balance reports (cf #1468)
|
||||
depth_=Nothing
|
||||
-- always show historical balance
|
||||
@ -95,8 +95,8 @@ aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
||||
items' = (if empty_ ropts' then id else filter (not . mixedAmountLooksZero . fifth6)) $
|
||||
reverse items
|
||||
-- select renderer
|
||||
render | fmt=="txt" = accountTransactionsReportAsText opts (rsQuery rspec') thisacctq
|
||||
| fmt=="csv" = printCSV . accountTransactionsReportAsCsv (rsQuery rspec') 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
|
||||
@ -130,7 +130,7 @@ accountTransactionsReportAsText copts reportq thisacctq items
|
||||
amtwidth = maximumStrict $ 12 : map (wbWidth . showamt . itemamt) items
|
||||
balwidth = maximumStrict $ 12 : map (wbWidth . showamt . itembal) items
|
||||
showamt = showMixedAmountB oneLine{displayMinWidth=Just 12, displayMaxWidth=mmax} -- color_
|
||||
where mmax = if no_elide_ . rsOpts . reportspec_ $ copts then Nothing else Just 32
|
||||
where mmax = if no_elide_ . _rsReportOpts . reportspec_ $ copts then Nothing else Just 32
|
||||
itemamt (_,_,_,_,a,_) = a
|
||||
itembal (_,_,_,_,_,a) = a
|
||||
-- show a title indicating which account was picked, which can be confusing otherwise
|
||||
@ -155,7 +155,7 @@ accountTransactionsReportAsText copts reportq thisacctq items
|
||||
--
|
||||
accountTransactionsReportItemAsText :: CliOpts -> Query -> Query -> Int -> Int -> AccountTransactionsReportItem -> TB.Builder
|
||||
accountTransactionsReportItemAsText
|
||||
copts@CliOpts{reportspec_=ReportSpec{rsOpts=ReportOpts{color_}}}
|
||||
copts@CliOpts{reportspec_=ReportSpec{_rsReportOpts=ReportOpts{color_}}}
|
||||
reportq thisacctq preferredamtwidth preferredbalwidth
|
||||
(t@Transaction{tdescription}, _, _issplit, otheracctsstr, change, balance) =
|
||||
-- Transaction -- the transaction, unmodified
|
||||
|
@ -341,7 +341,7 @@ balance opts@CliOpts{reportspec_=rspec} j = case balancecalc_ of
|
||||
_ -> error' $ unsupportedOutputFormatError fmt -- PARTIAL:
|
||||
writeOutputLazyText opts $ render ropts report
|
||||
where
|
||||
ropts@ReportOpts{..} = rsOpts rspec
|
||||
ropts@ReportOpts{..} = _rsReportOpts rspec
|
||||
multiperiod = interval_ /= NoInterval
|
||||
fmt = outputFormatFromOpts opts
|
||||
|
||||
@ -661,8 +661,8 @@ tests_Balance = tests "Balance" [
|
||||
tests "balanceReportAsText" [
|
||||
test "unicode in balance layout" $ do
|
||||
j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n"
|
||||
let rspec = defreportspec{rsOpts=defreportopts{no_total_=True}}
|
||||
TB.toLazyText (balanceReportAsText (rsOpts rspec) (balanceReport rspec{rsToday=fromGregorian 2008 11 26} j))
|
||||
let rspec = defreportspec{_rsReportOpts=defreportopts{no_total_=True}}
|
||||
TB.toLazyText (balanceReportAsText (_rsReportOpts rspec) (balanceReport rspec{_rsDay=fromGregorian 2008 11 26} j))
|
||||
@?=
|
||||
TL.unlines
|
||||
[" -100 актив:наличные"
|
||||
|
@ -12,11 +12,11 @@ import Data.List (groupBy)
|
||||
journalCheckOrdereddates :: CliOpts -> Journal -> Either String ()
|
||||
journalCheckOrdereddates CliOpts{reportspec_=rspec} j = do
|
||||
let
|
||||
ropts = (rsOpts rspec){accountlistmode_=ALFlat}
|
||||
ropts = (_rsReportOpts rspec){accountlistmode_=ALFlat}
|
||||
-- check date ordering within each file, not across files
|
||||
filets =
|
||||
groupBy (\t1 t2 -> transactionFile t1 == transactionFile t2) $
|
||||
filter (rsQuery rspec `matchesTransaction`) $
|
||||
filter (_rsQuery rspec `matchesTransaction`) $
|
||||
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
|
||||
|
@ -89,7 +89,7 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
||||
-- - `-e 2021-01-01` (remember `-e` specifies an exclusive report end date)
|
||||
-- - `-e 2021`"
|
||||
--
|
||||
q = rsQuery rspec
|
||||
q = _rsQuery rspec
|
||||
yesterday = addDays (-1) today
|
||||
yesterdayorjournalend = case journalLastDay False j of
|
||||
Just journalend -> max yesterday journalend
|
||||
@ -102,8 +102,8 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
|
||||
explicit = boolopt "explicit" rawopts
|
||||
|
||||
-- the balances to close
|
||||
ropts = (rsOpts rspec){balanceaccum_=Historical, accountlistmode_=ALFlat}
|
||||
rspec_ = rspec{rsOpts=ropts}
|
||||
ropts = (_rsReportOpts rspec){balanceaccum_=Historical, accountlistmode_=ALFlat}
|
||||
rspec_ = rspec{_rsReportOpts=ropts}
|
||||
(acctbals',_) = balanceReport rspec_ j
|
||||
acctbals = map (\(a,_,_,b) -> (a, if show_costs_ ropts then b else mixedAmountStripPrices b)) acctbals'
|
||||
totalamt = maSum $ map snd acctbals
|
||||
|
@ -34,6 +34,6 @@ codesmode = hledgerCommandMode
|
||||
codes :: CliOpts -> Journal -> IO ()
|
||||
codes CliOpts{reportspec_=rspec} j = do
|
||||
let ts = entriesReport rspec j
|
||||
codes = (if empty_ (rsOpts rspec) then id else filter (not . T.null)) $
|
||||
codes = (if empty_ (_rsReportOpts rspec) then id else filter (not . T.null)) $
|
||||
map tcode ts
|
||||
mapM_ T.putStrLn codes
|
||||
|
@ -102,7 +102,7 @@ unmatchedtxns s pp m =
|
||||
|
||||
-- | The diff command.
|
||||
diff :: CliOpts -> Journal -> IO ()
|
||||
diff CliOpts{file_=[f1, f2], reportspec_=ReportSpec{rsQuery=Acct acctRe}} _ = do
|
||||
diff CliOpts{file_=[f1, f2], reportspec_=ReportSpec{_rsQuery=Acct acctRe}} _ = do
|
||||
j1 <- readJournalFile' f1
|
||||
j2 <- readJournalFile' f2
|
||||
|
||||
|
@ -34,7 +34,7 @@ payeesmode = hledgerCommandMode
|
||||
|
||||
-- | The payees command.
|
||||
payees :: CliOpts -> Journal -> IO ()
|
||||
payees CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{rsQuery=query}} j = do
|
||||
payees CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query}} j = do
|
||||
let
|
||||
declared = boolopt "declared" rawopts
|
||||
used = boolopt "used" rawopts
|
||||
|
@ -29,7 +29,7 @@ pricesmode = hledgerCommandMode
|
||||
prices opts j = do
|
||||
let
|
||||
styles = journalCommodityStyles j
|
||||
q = rsQuery $ reportspec_ opts
|
||||
q = _rsQuery $ reportspec_ opts
|
||||
ps = filter (matchesPosting q) $ allPostings j
|
||||
mprices = jpricedirectives j
|
||||
cprices = map (stylePriceDirectiveExceptPrecision styles) $ concatMap postingsPriceDirectivesFromCosts ps
|
||||
|
@ -81,7 +81,7 @@ entriesReportAsText opts = TB.toLazyText . foldMap (TB.fromText . showTransactio
|
||||
-- Because of #551, and because of print -V valuing only one
|
||||
-- posting when there's an implicit txn price.
|
||||
-- So -B/-V/-X/--value implies -x. Is this ok ?
|
||||
|| (isJust . value_ . rsOpts $ reportspec_ opts) = id
|
||||
|| (isJust . value_ . _rsReportOpts $ reportspec_ opts) = id
|
||||
-- By default, use the original as-written-in-the-journal txn.
|
||||
| otherwise = originalTransaction
|
||||
|
||||
|
@ -187,7 +187,7 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
|
||||
_ -> (id,acctwidth)
|
||||
amt = showamt $ pamount p
|
||||
bal = showamt b
|
||||
showamt = showMixedAmountLinesB oneLine{displayColour=color_ . rsOpts $ reportspec_ opts}
|
||||
showamt = showMixedAmountLinesB oneLine{displayColour=color_ . _rsReportOpts $ reportspec_ opts}
|
||||
-- Since this will usually be called with the knot tied between this(amt|bal)width and
|
||||
-- preferred(amt|bal)width, make sure the former do not depend on the latter to avoid loops.
|
||||
thisamtwidth = maximumDef 0 $ map wbWidth amt
|
||||
|
@ -43,7 +43,7 @@ rewrite opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j@Journal{jtxns=ts} = d
|
||||
let modifiers = transactionModifierFromOpts opts : jtxnmodifiers j
|
||||
let j' = j{jtxns=either error' id $ modifyTransactions d modifiers ts} -- PARTIAL:
|
||||
-- run the print command, showing all transactions, or show diffs
|
||||
printOrDiff rawopts opts{reportspec_=rspec{rsQuery=Any}} j j'
|
||||
printOrDiff rawopts opts{reportspec_=rspec{_rsQuery=Any}} j j'
|
||||
|
||||
-- | Build a 'TransactionModifier' from any query arguments and --add-posting flags
|
||||
-- provided on the command line, or throw a parse error.
|
||||
|
@ -55,19 +55,19 @@ data OneSpan = OneSpan
|
||||
|
||||
|
||||
roi :: CliOpts -> Journal -> IO ()
|
||||
roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{rsOpts=ReportOpts{..}}} j = do
|
||||
roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{_rsReportOpts=ReportOpts{..}}} j = do
|
||||
d <- getCurrentDay
|
||||
-- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports".
|
||||
let
|
||||
priceOracle = journalPriceOracle infer_value_ j
|
||||
styles = journalCommodityStyles j
|
||||
today = rsToday rspec
|
||||
today = _rsDay rspec
|
||||
mixedAmountValue periodlast date =
|
||||
maybe id (mixedAmountApplyValuation priceOracle styles periodlast today date) value_
|
||||
. mixedAmountToCost cost_ styles
|
||||
|
||||
let
|
||||
ropts = rsOpts rspec
|
||||
ropts = _rsReportOpts rspec
|
||||
showCashFlow = boolopt "cashflow" rawopts
|
||||
prettyTables = pretty_tables_
|
||||
makeQuery flag = do
|
||||
|
@ -44,10 +44,10 @@ statsmode = hledgerCommandMode
|
||||
stats :: CliOpts -> Journal -> IO ()
|
||||
stats opts@CliOpts{reportspec_=rspec} j = do
|
||||
d <- getCurrentDay
|
||||
let q = rsQuery rspec
|
||||
let q = _rsQuery rspec
|
||||
l = ledgerFromJournal q j
|
||||
reportspan = ledgerDateSpan l `spanDefaultsFrom` queryDateSpan False q
|
||||
intervalspans = splitSpan (interval_ $ rsOpts rspec) reportspan
|
||||
intervalspans = splitSpan (interval_ $ _rsReportOpts rspec) reportspan
|
||||
showstats = showLedgerStats l d
|
||||
s = unlinesB $ map showstats intervalspans
|
||||
writeOutputLazyText opts $ TB.toLazyText s
|
||||
|
@ -34,11 +34,11 @@ tags CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do
|
||||
querystring = map T.pack $ drop 1 args
|
||||
values = boolopt "values" rawopts
|
||||
parsed = boolopt "parsed" rawopts
|
||||
empty = empty_ $ rsOpts rspec
|
||||
empty = empty_ $ _rsReportOpts rspec
|
||||
|
||||
argsquery <- either usageError (return . fst) $ parseQueryList d querystring
|
||||
let
|
||||
q = simplifyQuery $ And [queryFromFlags $ rsOpts rspec, argsquery]
|
||||
q = simplifyQuery $ And [queryFromFlags $ _rsReportOpts rspec, argsquery]
|
||||
txns = filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j
|
||||
tagsorvalues =
|
||||
(if parsed then id else nubSort)
|
||||
|
@ -100,7 +100,7 @@ compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> I
|
||||
compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=rspec, rawopts_=rawopts} j = do
|
||||
writeOutputLazyText opts $ render cbr
|
||||
where
|
||||
ropts@ReportOpts{..} = rsOpts rspec
|
||||
ropts@ReportOpts{..} = _rsReportOpts rspec
|
||||
-- use the default balance type for this report, unless the user overrides
|
||||
mbalanceAccumulationOverride = balanceAccumulationOverride rawopts
|
||||
balanceaccumulation = fromMaybe cbcaccum mbalanceAccumulationOverride
|
||||
@ -153,7 +153,7 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
|
||||
_ -> False
|
||||
|
||||
-- make a CompoundBalanceReport.
|
||||
cbr' = compoundBalanceReport rspec{rsOpts=ropts'} j cbcqueries
|
||||
cbr' = compoundBalanceReport rspec{_rsReportOpts=ropts'} j cbcqueries
|
||||
cbr = cbr'{cbrTitle=title}
|
||||
|
||||
-- render appropriately
|
||||
|
@ -154,9 +154,9 @@ main = do
|
||||
dbgIO "isInternalCommand" isInternalCommand
|
||||
dbgIO "isExternalCommand" isExternalCommand
|
||||
dbgIO "isBadCommand" isBadCommand
|
||||
dbgIO "period from opts" (period_ . rsOpts $ reportspec_ opts)
|
||||
dbgIO "interval from opts" (interval_ . rsOpts $ reportspec_ opts)
|
||||
dbgIO "query from opts & args" (rsQuery $ reportspec_ opts)
|
||||
dbgIO "period from opts" (period_ . _rsReportOpts $ reportspec_ opts)
|
||||
dbgIO "interval from opts" (interval_ . _rsReportOpts $ reportspec_ opts)
|
||||
dbgIO "query from opts & args" (_rsQuery $ reportspec_ opts)
|
||||
let
|
||||
journallesserror = error $ cmd++" tried to read the journal but is not supposed to"
|
||||
runHledgerCommand
|
||||
|
@ -125,8 +125,8 @@ journalAddForecast CliOpts{inputopts_=iopts, reportspec_=rspec} j =
|
||||
Just _ -> either (error') id . journalApplyCommodityStyles $ -- PARTIAL:
|
||||
journalBalanceTransactions' iopts j{ jtxns = concat [jtxns j, forecasttxns'] }
|
||||
where
|
||||
today = rsToday rspec
|
||||
ropts = rsOpts rspec
|
||||
today = _rsDay rspec
|
||||
ropts = _rsReportOpts rspec
|
||||
|
||||
-- "They can start no earlier than: the day following the latest normal transaction in the journal (or today if there are none)."
|
||||
mjournalend = dbg2 "journalEndDate" $ journalEndDate False j -- ignore secondary dates
|
||||
@ -310,7 +310,7 @@ journalSimilarTransaction cliopts j desc = mbestmatch
|
||||
bestmatches =
|
||||
dbg1With (unlines . ("similar transactions:":) . map (\(score,Transaction{..}) -> printf "%0.3f %s %s" score (show tdate) tdescription)) $
|
||||
journalTransactionsSimilarTo j q desc 10
|
||||
q = queryFromFlags $ rsOpts $ reportspec_ cliopts
|
||||
q = queryFromFlags $ _rsReportOpts $ reportspec_ cliopts
|
||||
|
||||
tests_Cli_Utils = tests "Utils" [
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user