lib: simplify balance report types; haddocks
This commit is contained in:
		
							parent
							
								
									ae03428e8e
								
							
						
					
					
						commit
						974b1e3be0
					
				| @ -52,10 +52,12 @@ nullacct = Account | ||||
|   , aboring = False | ||||
|   } | ||||
| 
 | ||||
| -- | Derive 1. an account tree and 2. their total changes from a list of postings. | ||||
| -- (ledger's core feature). The accounts are returned in a list, but | ||||
| --- also reference each other as a tree structure; the first account is | ||||
| --- the root of the tree. | ||||
| -- | Derive 1. an account tree and 2. each account's total exclusive | ||||
| -- and inclusive changes from a list of postings. | ||||
| -- This is the core of the balance command (and of *ledger). | ||||
| -- The accounts are returned as a list in flattened tree order, | ||||
| -- and also reference each other as a tree. | ||||
| -- (The first account is the root of the tree.) | ||||
| accountsFromPostings :: [Posting] -> [Account] | ||||
| accountsFromPostings ps = | ||||
|   let | ||||
|  | ||||
| @ -1,4 +1,3 @@ | ||||
| {-# LANGUAGE FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-} | ||||
| {-| | ||||
| 
 | ||||
| Balance report, used by the balance command. | ||||
| @ -12,10 +11,11 @@ Balance report, used by the balance command. | ||||
| 
 | ||||
| 
 | ||||
| 
 | ||||
| {-# LANGUAGE FlexibleInstances, ScopedTypeVariables, OverloadedStrings #-} | ||||
| 
 | ||||
| module Hledger.Reports.BalanceReport ( | ||||
|   BalanceReport, | ||||
|   BalanceReportItem, | ||||
|   RenderableAccountName, | ||||
|   balanceReport, | ||||
|   balanceReportValue, | ||||
|   mixedAmountValue, | ||||
| @ -46,22 +46,23 @@ import Hledger.Reports.ReportOptions | ||||
| 
 | ||||
| -- | A simple single-column balance report. It has: | ||||
| -- | ||||
| -- 1. a list of rows, each containing a renderable account name and a corresponding amount | ||||
| -- 1. a list of items, one per account, each containing: | ||||
| -- | ||||
| --   * the full account name | ||||
| -- | ||||
| --   * the Ledger-style elided short account name | ||||
| --     (the leaf account name, prefixed by any boring parents immediately above); | ||||
| --     or with --flat, the full account name again | ||||
| -- | ||||
| --   * the number of indentation steps for rendering a Ledger-style account tree, | ||||
| --     taking into account elided boring parents, --no-elide and --flat | ||||
| -- | ||||
| --   * an amount | ||||
| -- | ||||
| -- 2. the total of all amounts | ||||
| -- | ||||
| -- 2. the final total of the amounts | ||||
| type BalanceReport = ([BalanceReportItem], MixedAmount) | ||||
| type BalanceReportItem = (RenderableAccountName, MixedAmount) | ||||
| 
 | ||||
| -- | A renderable account name includes some additional hints for rendering accounts in a balance report. | ||||
| -- It has: | ||||
| -- | ||||
| -- * The full account name | ||||
| -- | ||||
| -- * The ledger-style short elided account name (the leaf name, prefixed by any boring parents immediately above) | ||||
| -- | ||||
| -- * The number of indentation steps to use when rendering a ledger-style account tree | ||||
| --   (normally the 0-based depth of this account excluding boring parents, or 0 with --flat). | ||||
| type RenderableAccountName = (AccountName, AccountName, Int) | ||||
| type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount) | ||||
| 
 | ||||
| -- | When true (the default), this makes balance --flat reports and their implementation clearer. | ||||
| -- Single/multi-col balance reports currently aren't all correct if this is false. | ||||
| @ -104,10 +105,10 @@ balanceReport opts q j = (items, total) | ||||
|             prunezeros  = if empty_ opts then id else fromMaybe nullacct . pruneAccounts (isZeroMixedAmount . balance) | ||||
|             markboring  = if no_elide_ opts then id else markBoringParentAccounts | ||||
|       items = dbg1 "items" $ map (balanceReportItem opts q) accts' | ||||
|       total | not (flat_ opts) = dbg1 "total" $ sum [amt | ((_,_,indent),amt) <- items, indent == 0] | ||||
|       total | not (flat_ opts) = dbg1 "total" $ sum [amt | (_,_,indent,amt) <- items, indent == 0] | ||||
|             | otherwise        = dbg1 "total" $ | ||||
|                                  if flatShowsExclusiveBalance | ||||
|                                  then sum $ map snd items | ||||
|                                  then sum $ map fourth4 items | ||||
|                                  else sum $ map aebalance $ clipAccountsAndAggregate 1 accts' | ||||
| 
 | ||||
| -- | In an account tree with zero-balance leaves removed, mark the | ||||
| @ -121,8 +122,8 @@ markBoringParentAccounts = tieAccountParents . mapAccounts mark | ||||
| 
 | ||||
| balanceReportItem :: ReportOpts -> Query -> Account -> BalanceReportItem | ||||
| balanceReportItem opts q a | ||||
|   | flat_ opts = ((name, name,       0),      (if flatShowsExclusiveBalance then aebalance else aibalance) a) | ||||
|   | otherwise  = ((name, elidedname, indent), aibalance a) | ||||
|   | flat_ opts = (name, name,       0,      (if flatShowsExclusiveBalance then aebalance else aibalance) a) | ||||
|   | otherwise  = (name, elidedname, indent, aibalance a) | ||||
|   where | ||||
|     name | queryDepth q > 0 = aname a | ||||
|          | otherwise        = "..." | ||||
| @ -148,7 +149,7 @@ balanceReportValue j d r = r' | ||||
|   where | ||||
|     (items,total) = r | ||||
|     r' = dbg8 "balanceReportValue" | ||||
|          ([(n, mixedAmountValue j d a) |(n,a) <- items], mixedAmountValue j d total) | ||||
|          ([(n, n', i, mixedAmountValue j d a) |(n,n',i,a) <- items], mixedAmountValue j d total) | ||||
| 
 | ||||
| mixedAmountValue :: Journal -> Day -> MixedAmount -> MixedAmount | ||||
| mixedAmountValue j d (Mixed as) = Mixed $ map (amountValue j d) as | ||||
| @ -188,7 +189,7 @@ tests_balanceReport = | ||||
|     (opts,journal) `gives` r = do | ||||
|       let (eitems, etotal) = r | ||||
|           (aitems, atotal) = balanceReport opts (queryFromOpts nulldate opts) journal | ||||
|           showw (acct,amt) = (acct, showMixedAmountDebug amt) | ||||
|           showw (acct,acct',indent,amt) = (acct, acct', indent, showMixedAmountDebug amt) | ||||
|       assertEqual "items" (map showw eitems) (map showw aitems) | ||||
|       assertEqual "total" (showMixedAmountDebug etotal) (showMixedAmountDebug atotal) | ||||
|     usd0 = usd 0 | ||||
| @ -200,36 +201,36 @@ tests_balanceReport = | ||||
|   ,"balanceReport with no args on sample journal" ~: do | ||||
|    (defreportopts, samplejournal) `gives` | ||||
|     ([ | ||||
|       (("assets","assets",0), mamountp' "$-1.00") | ||||
|      ,(("assets:bank:saving","bank:saving",1), mamountp' "$1.00") | ||||
|      ,(("assets:cash","cash",1), mamountp' "$-2.00") | ||||
|      ,(("expenses","expenses",0), mamountp' "$2.00") | ||||
|      ,(("expenses:food","food",1), mamountp' "$1.00") | ||||
|      ,(("expenses:supplies","supplies",1), mamountp' "$1.00") | ||||
|      ,(("income","income",0), mamountp' "$-2.00") | ||||
|      ,(("income:gifts","gifts",1), mamountp' "$-1.00") | ||||
|      ,(("income:salary","salary",1), mamountp' "$-1.00") | ||||
|      ,(("liabilities:debts","liabilities:debts",0), mamountp' "$1.00") | ||||
|       ("assets","assets",0, mamountp' "$-1.00") | ||||
|      ,("assets:bank:saving","bank:saving",1, mamountp' "$1.00") | ||||
|      ,("assets:cash","cash",1, mamountp' "$-2.00") | ||||
|      ,("expenses","expenses",0, mamountp' "$2.00") | ||||
|      ,("expenses:food","food",1, mamountp' "$1.00") | ||||
|      ,("expenses:supplies","supplies",1, mamountp' "$1.00") | ||||
|      ,("income","income",0, mamountp' "$-2.00") | ||||
|      ,("income:gifts","gifts",1, mamountp' "$-1.00") | ||||
|      ,("income:salary","salary",1, mamountp' "$-1.00") | ||||
|      ,("liabilities:debts","liabilities:debts",0, mamountp' "$1.00") | ||||
|      ], | ||||
|      Mixed [usd0]) | ||||
| 
 | ||||
|   ,"balanceReport with --depth=N" ~: do | ||||
|    (defreportopts{depth_=Just 1}, samplejournal) `gives` | ||||
|     ([ | ||||
|       (("assets",      "assets",      0), mamountp' "$-1.00") | ||||
|      ,(("expenses",    "expenses",    0), mamountp'  "$2.00") | ||||
|      ,(("income",      "income",      0), mamountp' "$-2.00") | ||||
|      ,(("liabilities", "liabilities", 0), mamountp'  "$1.00") | ||||
|       ("assets",      "assets",      0, mamountp' "$-1.00") | ||||
|      ,("expenses",    "expenses",    0, mamountp'  "$2.00") | ||||
|      ,("income",      "income",      0, mamountp' "$-2.00") | ||||
|      ,("liabilities", "liabilities", 0, mamountp'  "$1.00") | ||||
|      ], | ||||
|      Mixed [usd0]) | ||||
| 
 | ||||
|   ,"balanceReport with depth:N" ~: do | ||||
|    (defreportopts{query_="depth:1"}, samplejournal) `gives` | ||||
|     ([ | ||||
|       (("assets",      "assets",      0), mamountp' "$-1.00") | ||||
|      ,(("expenses",    "expenses",    0), mamountp'  "$2.00") | ||||
|      ,(("income",      "income",      0), mamountp' "$-2.00") | ||||
|      ,(("liabilities", "liabilities", 0), mamountp'  "$1.00") | ||||
|       ("assets",      "assets",      0, mamountp' "$-1.00") | ||||
|      ,("expenses",    "expenses",    0, mamountp'  "$2.00") | ||||
|      ,("income",      "income",      0, mamountp' "$-2.00") | ||||
|      ,("liabilities", "liabilities", 0, mamountp'  "$1.00") | ||||
|      ], | ||||
|      Mixed [usd0]) | ||||
| 
 | ||||
| @ -239,32 +240,32 @@ tests_balanceReport = | ||||
|      Mixed [nullamt]) | ||||
|    (defreportopts{query_="date2:'in 2009'"}, samplejournal2) `gives` | ||||
|     ([ | ||||
|       (("assets:bank:checking","assets:bank:checking",0),mamountp' "$1.00") | ||||
|      ,(("income:salary","income:salary",0),mamountp' "$-1.00") | ||||
|       ("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00") | ||||
|      ,("income:salary","income:salary",0,mamountp' "$-1.00") | ||||
|      ], | ||||
|      Mixed [usd0]) | ||||
| 
 | ||||
|   ,"balanceReport with desc:" ~: do | ||||
|    (defreportopts{query_="desc:income"}, samplejournal) `gives` | ||||
|     ([ | ||||
|       (("assets:bank:checking","assets:bank:checking",0),mamountp' "$1.00") | ||||
|      ,(("income:salary","income:salary",0), mamountp' "$-1.00") | ||||
|       ("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00") | ||||
|      ,("income:salary","income:salary",0, mamountp' "$-1.00") | ||||
|      ], | ||||
|      Mixed [usd0]) | ||||
| 
 | ||||
|   ,"balanceReport with not:desc:" ~: do | ||||
|    (defreportopts{query_="not:desc:income"}, samplejournal) `gives` | ||||
|     ([ | ||||
|       (("assets","assets",0), mamountp' "$-2.00") | ||||
|      ,(("assets:bank","bank",1), Mixed [usd0]) | ||||
|      ,(("assets:bank:checking","checking",2),mamountp' "$-1.00") | ||||
|      ,(("assets:bank:saving","saving",2), mamountp' "$1.00") | ||||
|      ,(("assets:cash","cash",1), mamountp' "$-2.00") | ||||
|      ,(("expenses","expenses",0), mamountp' "$2.00") | ||||
|      ,(("expenses:food","food",1), mamountp' "$1.00") | ||||
|      ,(("expenses:supplies","supplies",1), mamountp' "$1.00") | ||||
|      ,(("income:gifts","income:gifts",0), mamountp' "$-1.00") | ||||
|      ,(("liabilities:debts","liabilities:debts",0), mamountp' "$1.00") | ||||
|       ("assets","assets",0, mamountp' "$-2.00") | ||||
|      ,("assets:bank","bank",1, Mixed [usd0]) | ||||
|      ,("assets:bank:checking","checking",2,mamountp' "$-1.00") | ||||
|      ,("assets:bank:saving","saving",2, mamountp' "$1.00") | ||||
|      ,("assets:cash","cash",1, mamountp' "$-2.00") | ||||
|      ,("expenses","expenses",0, mamountp' "$2.00") | ||||
|      ,("expenses:food","food",1, mamountp' "$1.00") | ||||
|      ,("expenses:supplies","supplies",1, mamountp' "$1.00") | ||||
|      ,("income:gifts","income:gifts",0, mamountp' "$-1.00") | ||||
|      ,("liabilities:debts","liabilities:debts",0, mamountp' "$1.00") | ||||
|      ], | ||||
|      Mixed [usd0]) | ||||
| 
 | ||||
|  | ||||
| @ -32,32 +32,34 @@ import Hledger.Reports.BalanceReport | ||||
| 
 | ||||
| -- | A multi balance report is a balance report with one or more columns. It has: | ||||
| -- | ||||
| -- 1. a list of each column's date span | ||||
| -- 1. a list of each column's period (date span) | ||||
| -- | ||||
| -- 2. a list of rows, each containing a renderable account name and the amounts to show in each column | ||||
| -- 2. a list of row items, each containing: | ||||
| -- | ||||
| -- 3. a list of each column's final total | ||||
| --   * the full account name | ||||
| -- | ||||
| --   * the leaf account name | ||||
| -- | ||||
| --   * the account's depth | ||||
| -- | ||||
| --   * the amounts to show in each column | ||||
| -- | ||||
| --   * the total of the row's amounts | ||||
| -- | ||||
| --   * the average of the row's amounts | ||||
| -- | ||||
| -- 3. the column totals and the overall total and average | ||||
| -- | ||||
| -- The meaning of the amounts depends on the type of multi balance | ||||
| -- report, of which there are three: periodic, cumulative and historical | ||||
| -- (see 'BalanceType' and "Hledger.Cli.Balance"). | ||||
| newtype MultiBalanceReport = MultiBalanceReport ([DateSpan] | ||||
| newtype MultiBalanceReport = | ||||
|   MultiBalanceReport ([DateSpan] | ||||
|                      ,[MultiBalanceReportRow] | ||||
|                                                 ,MultiBalanceTotalsRow | ||||
|                      ,MultiBalanceReportTotals | ||||
|                      ) | ||||
| 
 | ||||
| -- | A row in a multi balance report has | ||||
| -- | ||||
| -- * An account name, with rendering hints | ||||
| -- | ||||
| -- * A list of amounts to be shown in each of the report's columns. | ||||
| -- | ||||
| -- * The total of the row amounts. | ||||
| -- | ||||
| -- * The average of the row amounts. | ||||
| type MultiBalanceReportRow = (RenderableAccountName, [MixedAmount], MixedAmount, MixedAmount) | ||||
| 
 | ||||
| type MultiBalanceTotalsRow = ([MixedAmount], MixedAmount, MixedAmount) | ||||
| type MultiBalanceReportRow    = (AccountName, AccountName, Int, [MixedAmount], MixedAmount, MixedAmount) | ||||
| type MultiBalanceReportTotals = ([MixedAmount], MixedAmount, MixedAmount) | ||||
| 
 | ||||
| instance Show MultiBalanceReport where | ||||
|     -- use ppShow to break long lists onto multiple lines | ||||
| @ -125,7 +127,7 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow | ||||
|       postedAccts :: [AccountName] = dbg1 "postedAccts" $ sort $ accountNamesFromPostings ps | ||||
| 
 | ||||
|       -- starting balances and accounts from transactions before the report start date | ||||
|       startacctbals = dbg1 "startacctbals" $ map (\((a,_,_),b) -> (a,b)) startbalanceitems | ||||
|       startacctbals = dbg1 "startacctbals" $ map (\(a,_,_,b) -> (a,b)) startbalanceitems | ||||
|           where | ||||
|             (startbalanceitems,_) = dbg1 "starting balance report" $ balanceReport opts' precedingq j | ||||
|                                     where | ||||
| @ -152,7 +154,7 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow | ||||
| 
 | ||||
|       items :: [MultiBalanceReportRow] = | ||||
|           dbg1 "items" | ||||
|           [((a, accountLeafName a, accountNameLevel a), displayedBals, rowtot, rowavg) | ||||
|           [(a, accountLeafName a, accountNameLevel a, displayedBals, rowtot, rowavg) | ||||
|            | (a,changes) <- acctBalChanges | ||||
|            , let displayedBals = case balancetype_ opts of | ||||
|                                   HistoricalBalance -> drop 1 $ scanl (+) (startingBalanceFor a) changes | ||||
| @ -167,12 +169,12 @@ multiBalanceReport opts q j = MultiBalanceReport (displayspans, items, totalsrow | ||||
|           -- dbg1 "totals" $ | ||||
|           map sum balsbycol | ||||
|           where | ||||
|             balsbycol = transpose [bs | ((a,_,_),bs,_,_) <- items, not (tree_ opts) || a `elem` highestlevelaccts] | ||||
|             balsbycol = transpose [bs | (a,_,_,bs,_,_) <- items, not (tree_ opts) || a `elem` highestlevelaccts] | ||||
|             highestlevelaccts     = | ||||
|                 dbg1 "highestlevelaccts" | ||||
|                 [a | a <- displayedAccts, not $ any (`elem` displayedAccts) $ init $ expandAccountName a] | ||||
| 
 | ||||
|       totalsrow :: MultiBalanceTotalsRow = | ||||
|       totalsrow :: MultiBalanceReportTotals = | ||||
|           dbg1 "totalsrow" | ||||
|           (totals, sum totals, averageMixedAmounts totals) | ||||
| 
 | ||||
| @ -188,7 +190,7 @@ multiBalanceReportValue j d r = r' | ||||
|     MultiBalanceReport (spans, rows, (coltotals, rowtotaltotal, rowavgtotal)) = r | ||||
|     r' = MultiBalanceReport | ||||
|          (spans, | ||||
|           [(n, map convert rowamts, convert rowtotal, convert rowavg) | (n, rowamts, rowtotal, rowavg) <- rows], | ||||
|           [(acct, acct', depth, map convert rowamts, convert rowtotal, convert rowavg) | (acct, acct', depth, rowamts, rowtotal, rowavg) <- rows], | ||||
|           (map convert coltotals, convert rowtotaltotal, convert rowavgtotal)) | ||||
|     convert = mixedAmountValue j d | ||||
| 
 | ||||
|  | ||||
| @ -85,7 +85,7 @@ asInit d reset ui@UIState{ | ||||
|     (items,_total) = convert $ balanceReport ropts' q j | ||||
| 
 | ||||
|     -- pre-render the list items | ||||
|     displayitem ((fullacct, shortacct, indent), bal) = | ||||
|     displayitem (fullacct, shortacct, indent, bal) = | ||||
|       AccountsScreenItem{asItemIndentLevel        = indent | ||||
|                         ,asItemAccountName        = fullacct | ||||
|                         ,asItemDisplayAccountName = replaceHiddenAccountsNameWith "All" $ if flat_ ropts' then fullacct else shortacct | ||||
|  | ||||
| @ -201,7 +201,7 @@ balanceReportAsHtml _ vd@VD{..} (items',total) = | ||||
|    inacctmatcher = inAccountQuery qopts | ||||
|    items = items' -- maybe items' (\m -> filter (matchesAccount m . \(a,_,_,_)->a) items') showacctmatcher | ||||
|    itemAsHtml :: ViewData -> BalanceReportItem -> HtmlUrl AppRoute | ||||
|    itemAsHtml _ ((acct, adisplay, aindent), abal) = [hamlet| | ||||
|    itemAsHtml _ (acct, adisplay, aindent, abal) = [hamlet| | ||||
| <tr.item.#{inacctclass}> | ||||
|  <td.account.#{depthclass}> | ||||
|   \#{indent} | ||||
|  | ||||
| @ -332,7 +332,7 @@ balance opts@CliOpts{reportopts_=ropts} j = do | ||||
| balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV | ||||
| balanceReportAsCsv opts (items, total) = | ||||
|   ["account","balance"] : | ||||
|   [[T.unpack a, showMixedAmountOneLineWithoutPrice b] | ((a, _, _), b) <- items] | ||||
|   [[T.unpack a, showMixedAmountOneLineWithoutPrice b] | (a, _, _, b) <- items] | ||||
|   ++ | ||||
|   if no_total_ opts | ||||
|   then [] | ||||
| @ -353,7 +353,7 @@ balanceReportAsText opts ((items, total)) = unlines $ concat lines ++ t | ||||
|                Right fmt -> | ||||
|                 let | ||||
|                   -- abuse renderBalanceReportItem to render the total with similar format | ||||
|                   acctcolwidth = maximum' [T.length fullname | ((fullname, _, _), _) <- items] | ||||
|                   acctcolwidth = maximum' [T.length fullname | (fullname, _, _, _) <- items] | ||||
|                   totallines = map rstrip $ renderBalanceReportItem fmt (T.replicate (acctcolwidth+1) " ", 0, total) | ||||
|                   -- with a custom format, extend the line to the full report width; | ||||
|                   -- otherwise show the usual 20-char line for compatibility | ||||
| @ -393,7 +393,7 @@ This implementation turned out to be a bit convoluted but implements the followi | ||||
| -- differently-priced quantities of the same commodity will appear merged. | ||||
| -- The output will be one or more lines depending on the format and number of commodities. | ||||
| balanceReportItemAsText :: ReportOpts -> StringFormat -> BalanceReportItem -> [String] | ||||
| balanceReportItemAsText opts fmt ((_, accountName, depth), amt) = | ||||
| balanceReportItemAsText opts fmt (_, accountName, depth, amt) = | ||||
|   renderBalanceReportItem fmt ( | ||||
|     maybeAccountNameDrop opts accountName, | ||||
|     depth, | ||||
| @ -455,7 +455,7 @@ multiBalanceReportAsCsv opts (MultiBalanceReport (colspans, items, (coltotals,to | ||||
|    (amts | ||||
|     ++ (if row_total_ opts then [rowtot] else []) | ||||
|     ++ (if average_ opts then [rowavg] else [])) | ||||
|   | ((a,a',i), amts, rowtot, rowavg) <- items] | ||||
|   | (a,a',i, amts, rowtot, rowavg) <- items] | ||||
|   ++ | ||||
|   if no_total_ opts | ||||
|   then [] | ||||
| @ -486,11 +486,11 @@ periodBalanceReportAsText opts r@(MultiBalanceReport (colspans, items, (coltotal | ||||
|     items' | empty_ opts = items | ||||
|            | otherwise   = items -- dbg1 "2" $ filter (any (not . isZeroMixedAmount) . snd) $ dbg1 "1" items | ||||
|     accts = map renderacct items' | ||||
|     renderacct ((a,a',i),_,_,_) | ||||
|     renderacct (a,a',i,_,_,_) | ||||
|       | tree_ opts = T.replicate ((i-1)*2) " " <> a' | ||||
|       | otherwise  = maybeAccountNameDrop opts a | ||||
|     acctswidth = maximum' $ map textWidth accts | ||||
|     rowvals (_,as,rowtot,rowavg) = as | ||||
|     rowvals (_,_,_,as,rowtot,rowavg) = as | ||||
|                                    ++ (if row_total_ opts then [rowtot] else []) | ||||
|                                    ++ (if average_ opts then [rowavg] else []) | ||||
|     addtotalrow | no_total_ opts = id | ||||
| @ -518,11 +518,11 @@ cumulativeBalanceReportAsText opts r@(MultiBalanceReport (colspans, items, (colt | ||||
|                   ++ (if row_total_ opts then ["  Total"] else []) | ||||
|                   ++ (if average_ opts then ["Average"] else []) | ||||
|     accts = map renderacct items | ||||
|     renderacct ((a,a',i),_,_,_) | ||||
|     renderacct (a,a',i,_,_,_) | ||||
|       | tree_ opts = replicate ((i-1)*2) ' ' ++ T.unpack a' | ||||
|       | otherwise  = T.unpack $ maybeAccountNameDrop opts a | ||||
|     acctswidth = maximum' $ map strWidth accts | ||||
|     rowvals (_,as,rowtot,rowavg) = as | ||||
|     rowvals (_,_,_,as,rowtot,rowavg) = as | ||||
|                                    ++ (if row_total_ opts then [rowtot] else []) | ||||
|                                    ++ (if average_ opts then [rowavg] else []) | ||||
|     addtotalrow | no_total_ opts = id | ||||
| @ -550,11 +550,11 @@ historicalBalanceReportAsText opts r@(MultiBalanceReport (colspans, items, (colt | ||||
|                   ++ (if row_total_ opts then ["  Total"] else []) | ||||
|                   ++ (if average_ opts then ["Average"] else []) | ||||
|     accts = map renderacct items | ||||
|     renderacct ((a,a',i),_,_,_) | ||||
|     renderacct (a,a',i,_,_,_) | ||||
|       | tree_ opts = replicate ((i-1)*2) ' ' ++ T.unpack a' | ||||
|       | otherwise  = T.unpack $ maybeAccountNameDrop opts a | ||||
|     acctswidth = maximum' $ map strWidth accts | ||||
|     rowvals (_,as,rowtot,rowavg) = as | ||||
|     rowvals (_,_,_,as,rowtot,rowavg) = as | ||||
|                              ++ (if row_total_ opts then [rowtot] else []) | ||||
|                              ++ (if average_ opts then [rowavg] else []) | ||||
|     addtotalrow | no_total_ opts = id | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user