mirror of
https://github.com/simonmichael/hledger.git
synced 2024-11-08 07:09:28 +03:00
hlint-clean BalanceReport, MultiBalanceReport
This commit is contained in:
parent
bd5c7669d1
commit
67a76b297a
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-}
|
||||
{-# LANGUAGE FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-}
|
||||
{-|
|
||||
|
||||
Balance report, used by the balance command.
|
||||
@ -127,7 +127,7 @@ balanceReportItem opts q a
|
||||
name | queryDepth q > 0 = aname a
|
||||
| otherwise = "..."
|
||||
elidedname = accountNameFromComponents (adjacentboringparentnames ++ [accountLeafName name])
|
||||
adjacentboringparentnames = reverse $ map (accountLeafName.aname) $ takeWhile aboring $ parents
|
||||
adjacentboringparentnames = reverse $ map (accountLeafName.aname) $ takeWhile aboring parents
|
||||
indent = length $ filter (not.aboring) parents
|
||||
-- parents exclude the tree's root node
|
||||
parents = case parentAccounts a of [] -> []
|
||||
@ -147,7 +147,7 @@ balanceReportValue :: Journal -> Day -> BalanceReport -> BalanceReport
|
||||
balanceReportValue j d r = r'
|
||||
where
|
||||
(items,total) = r
|
||||
r' = dbg8 "balanceReportValue" $
|
||||
r' = dbg8 "balanceReportValue"
|
||||
([(n, mixedAmountValue j d a) |(n,a) <- items], mixedAmountValue j d total)
|
||||
|
||||
mixedAmountValue :: Journal -> Day -> MixedAmount -> MixedAmount
|
||||
@ -385,27 +385,28 @@ tests_balanceReport =
|
||||
-}
|
||||
]
|
||||
|
||||
Right samplejournal2 = journalBalanceTransactions $
|
||||
nulljournal
|
||||
{jtxns = [
|
||||
txnTieKnot $ Transaction {
|
||||
tindex=0,
|
||||
tsourcepos=nullsourcepos,
|
||||
tdate=parsedate "2008/01/01",
|
||||
tdate2=Just $ parsedate "2009/01/01",
|
||||
tstatus=Uncleared,
|
||||
tcode="",
|
||||
tdescription="income",
|
||||
tcomment="",
|
||||
ttags=[],
|
||||
tpostings=
|
||||
[posting {paccount="assets:bank:checking", pamount=Mixed [usd 1]}
|
||||
,posting {paccount="income:salary", pamount=missingmixedamt}
|
||||
],
|
||||
tpreceding_comment_lines=""
|
||||
}
|
||||
]
|
||||
}
|
||||
Right samplejournal2 =
|
||||
journalBalanceTransactions
|
||||
nulljournal{
|
||||
jtxns = [
|
||||
txnTieKnot Transaction{
|
||||
tindex=0,
|
||||
tsourcepos=nullsourcepos,
|
||||
tdate=parsedate "2008/01/01",
|
||||
tdate2=Just $ parsedate "2009/01/01",
|
||||
tstatus=Uncleared,
|
||||
tcode="",
|
||||
tdescription="income",
|
||||
tcomment="",
|
||||
ttags=[],
|
||||
tpostings=
|
||||
[posting {paccount="assets:bank:checking", pamount=Mixed [usd 1]}
|
||||
,posting {paccount="income:salary", pamount=missingmixedamt}
|
||||
],
|
||||
tpreceding_comment_lines=""
|
||||
}
|
||||
]
|
||||
}
|
||||
|
||||
-- tests_isInterestingIndented = [
|
||||
-- "isInterestingIndented" ~: do
|
||||
@ -416,5 +417,5 @@ Right samplejournal2 = journalBalanceTransactions $
|
||||
-- ]
|
||||
|
||||
tests_Hledger_Reports_BalanceReport :: Test
|
||||
tests_Hledger_Reports_BalanceReport = TestList $
|
||||
tests_balanceReport
|
||||
tests_Hledger_Reports_BalanceReport = TestList
|
||||
tests_balanceReport
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables #-}
|
||||
{-# LANGUAGE FlexibleInstances, ScopedTypeVariables #-}
|
||||
{-|
|
||||
|
||||
Multi-column balance reports, used by the balance command.
|
||||
@ -100,12 +100,12 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow
|
||||
displayspans = dbg1 "displayspans" $ splitSpan (interval_ opts) displayspan
|
||||
where
|
||||
displayspan
|
||||
| empty_ opts = dbg1 "displayspan (-E)" $ reportspan -- all the requested intervals
|
||||
| empty_ opts = dbg1 "displayspan (-E)" reportspan -- all the requested intervals
|
||||
| otherwise = dbg1 "displayspan" $ requestedspan `spanIntersect` matchedspan -- exclude leading/trailing empty intervals
|
||||
matchedspan = dbg1 "matchedspan" $ postingsDateSpan' (whichDateFromOpts opts) ps
|
||||
|
||||
psPerSpan :: [[Posting]] =
|
||||
dbg1 "psPerSpan" $
|
||||
dbg1 "psPerSpan"
|
||||
[filter (isPostingInDateSpan' (whichDateFromOpts opts) s) ps | s <- displayspans]
|
||||
|
||||
postedAcctBalChangesPerSpan :: [[(ClippedAccountName, MixedAmount)]] =
|
||||
@ -141,17 +141,17 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow
|
||||
if empty_ opts then nub $ sort $ startAccts ++ postedAccts else postedAccts
|
||||
|
||||
acctBalChangesPerSpan :: [[(ClippedAccountName, MixedAmount)]] =
|
||||
dbg1 "acctBalChangesPerSpan" $
|
||||
dbg1 "acctBalChangesPerSpan"
|
||||
[sortBy (comparing fst) $ unionBy (\(a,_) (a',_) -> a == a') postedacctbals zeroes
|
||||
| postedacctbals <- postedAcctBalChangesPerSpan]
|
||||
where zeroes = [(a, nullmixedamt) | a <- displayedAccts]
|
||||
|
||||
acctBalChanges :: [(ClippedAccountName, [MixedAmount])] =
|
||||
dbg1 "acctBalChanges" $
|
||||
dbg1 "acctBalChanges"
|
||||
[(a, map snd abs) | abs@((a,_):_) <- transpose acctBalChangesPerSpan] -- never null, or used when null...
|
||||
|
||||
items :: [MultiBalanceReportRow] =
|
||||
dbg1 "items" $
|
||||
dbg1 "items"
|
||||
[((a, accountLeafName a, accountNameLevel a), displayedBals, rowtot, rowavg)
|
||||
| (a,changes) <- acctBalChanges
|
||||
, let displayedBals = case balancetype_ opts of
|
||||
@ -169,11 +169,11 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow
|
||||
where
|
||||
balsbycol = transpose [bs | ((a,_,_),bs,_,_) <- items, not (tree_ opts) || a `elem` highestlevelaccts]
|
||||
highestlevelaccts =
|
||||
dbg1 "highestlevelaccts" $
|
||||
dbg1 "highestlevelaccts"
|
||||
[a | a <- displayedAccts, not $ any (`elem` displayedAccts) $ init $ expandAccountName a]
|
||||
|
||||
totalsrow :: MultiBalanceTotalsRow =
|
||||
dbg1 "totalsrow" $
|
||||
dbg1 "totalsrow"
|
||||
(totals, sum totals, averageMixedAmounts totals)
|
||||
|
||||
dbg1 s = let p = "multiBalanceReport" in Hledger.Utils.dbg1 (p++" "++s) -- add prefix in this function's debug output
|
||||
|
Loading…
Reference in New Issue
Block a user