overhaul single- and multi-column balance reports
Changes include: - flat mode now shows exclusive (subaccount-excluding) balances. This is a deviation from ledger, but seems simpler and clearer for users and implementors across the various modes. - in flat mode, --depth now aggregates deeper accounts at the depth limit, rather than just excluding them from the report. This is more useful. - in flat mode, --empty no longer shows parent accounts with no postings. - more tests, more debug output, clearer code
This commit is contained in:
		
							parent
							
								
									4dc61e76bf
								
							
						
					
					
						commit
						6a928a03a8
					
				@ -120,6 +120,43 @@ clipAccounts d a = a{asubs=subs}
 | 
			
		||||
    where
 | 
			
		||||
      subs = map (clipAccounts (d-1)) $ asubs a
 | 
			
		||||
 | 
			
		||||
-- | Remove subaccounts below the specified depth, aggregating their balance at the depth limit
 | 
			
		||||
-- (accounts at the depth limit will have any sub-balances merged into their exclusive balance).
 | 
			
		||||
-- XXX may be incorrect in some cases.
 | 
			
		||||
clipAccountsAndAggregate :: Int -> [Account] -> [Account]
 | 
			
		||||
clipAccountsAndAggregate d as = combined
 | 
			
		||||
    where
 | 
			
		||||
      clipped  = [a{aname=clipAccountName d $ aname a} | a <- as]
 | 
			
		||||
      combined = [a{aebalance=sum (map aebalance same)}
 | 
			
		||||
                  | same@(a:_) <- groupBy (\a1 a2 -> aname a1 == aname a2) clipped]
 | 
			
		||||
{-
 | 
			
		||||
test cases, assuming d=1:
 | 
			
		||||
 | 
			
		||||
assets:cash 1 1
 | 
			
		||||
assets:checking 1 1
 | 
			
		||||
->
 | 
			
		||||
as:       [assets:cash 1 1, assets:checking 1 1]
 | 
			
		||||
clipped:  [assets 1 1, assets 1 1]
 | 
			
		||||
combined: [assets 2 2]
 | 
			
		||||
 | 
			
		||||
assets 0 2
 | 
			
		||||
 assets:cash 1 1
 | 
			
		||||
 assets:checking 1 1
 | 
			
		||||
->
 | 
			
		||||
as:       [assets 0 2, assets:cash 1 1, assets:checking 1 1]
 | 
			
		||||
clipped:  [assets 0 2, assets 1 1, assets 1 1]
 | 
			
		||||
combined: [assets 2 2]
 | 
			
		||||
 | 
			
		||||
assets 0 2
 | 
			
		||||
 assets:bank 1 2
 | 
			
		||||
  assets:bank:checking 1 1
 | 
			
		||||
->
 | 
			
		||||
as:       [assets 0 2, assets:bank 1 2, assets:bank:checking 1 1]
 | 
			
		||||
clipped:  [assets 0 2, assets 1 2, assets 1 1]
 | 
			
		||||
combined: [assets 2 2]
 | 
			
		||||
 | 
			
		||||
-}
 | 
			
		||||
 | 
			
		||||
-- | Remove all leaf accounts and subtrees matching a predicate.
 | 
			
		||||
pruneAccounts :: (Account -> Bool) -> Account -> Maybe Account
 | 
			
		||||
pruneAccounts p = headMay . prune
 | 
			
		||||
 | 
			
		||||
@ -1,4 +1,4 @@
 | 
			
		||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
 | 
			
		||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables #-}
 | 
			
		||||
{-|
 | 
			
		||||
 | 
			
		||||
Balance report, used by the balance command.
 | 
			
		||||
@ -10,6 +10,7 @@ module Hledger.Reports.BalanceReport (
 | 
			
		||||
  BalanceReportItem,
 | 
			
		||||
  RenderableAccountName,
 | 
			
		||||
  balanceReport,
 | 
			
		||||
  flatShowsExclusiveBalance,
 | 
			
		||||
 | 
			
		||||
  -- * Tests
 | 
			
		||||
  tests_Hledger_Reports_BalanceReport
 | 
			
		||||
@ -45,6 +46,15 @@ type BalanceReportItem = (RenderableAccountName, MixedAmount)
 | 
			
		||||
--   (normally the 0-based depth of this account excluding boring parents, or 0 with --flat).
 | 
			
		||||
type RenderableAccountName = (AccountName, AccountName, Int)
 | 
			
		||||
 | 
			
		||||
-- | 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.
 | 
			
		||||
flatShowsExclusiveBalance    = True
 | 
			
		||||
 | 
			
		||||
-- | Enabling this makes balance --flat --empty also show parent accounts without postings,
 | 
			
		||||
-- in addition to those with postings and a zero balance. Disabling it shows only the latter.
 | 
			
		||||
-- No longer supported, but leave this here for a bit.
 | 
			
		||||
-- flatShowsPostinglessAccounts = True
 | 
			
		||||
 | 
			
		||||
-- | Generate a simple balance report, containing the matched accounts and
 | 
			
		||||
-- their balances (change of balance) during the specified period.
 | 
			
		||||
-- This is like periodBalanceReport with a single column (but more mature,
 | 
			
		||||
@ -52,24 +62,32 @@ type RenderableAccountName = (AccountName, AccountName, Int)
 | 
			
		||||
balanceReport :: ReportOpts -> Query -> Journal -> BalanceReport
 | 
			
		||||
balanceReport opts q j = (items, total)
 | 
			
		||||
    where
 | 
			
		||||
      l =  ledgerFromJournal q $ journalSelectingAmountFromOpts opts j
 | 
			
		||||
      accts =
 | 
			
		||||
          dbg "accts1" $ 
 | 
			
		||||
          clipAccounts (queryDepth q) $ -- exclude accounts deeper than specified depth
 | 
			
		||||
          ledgerRootAccount l
 | 
			
		||||
      accts'
 | 
			
		||||
          | flat_ opts = filterzeros $ tail $ flattenAccounts accts
 | 
			
		||||
          | otherwise  = filter (not.aboring) $ tail $ flattenAccounts $ markboring $ prunezeros accts
 | 
			
		||||
      -- dbg = const id -- exclude from debug output
 | 
			
		||||
      dbg s = let p = "balanceReport" in Hledger.Utils.dbg (p++" "++s)  -- add prefix in debug output
 | 
			
		||||
 | 
			
		||||
      accts = ledgerRootAccount $ ledgerFromJournal q $ journalSelectingAmountFromOpts opts j
 | 
			
		||||
      accts' :: [Account]
 | 
			
		||||
          | flat_ opts = dbg "accts" $ 
 | 
			
		||||
                         filterzeros $
 | 
			
		||||
                         filterempty $
 | 
			
		||||
                         drop 1 $ clipAccountsAndAggregate (queryDepth q) $ flattenAccounts accts
 | 
			
		||||
          | otherwise  = dbg "accts" $ 
 | 
			
		||||
                         filter (not.aboring) $
 | 
			
		||||
                         drop 1 $ flattenAccounts $
 | 
			
		||||
                         markboring $ 
 | 
			
		||||
                         prunezeros $ clipAccounts (queryDepth q) accts
 | 
			
		||||
          where
 | 
			
		||||
            filterzeros | empty_ opts = id
 | 
			
		||||
                        | otherwise = filter (not . isZeroMixedAmount . aebalance)
 | 
			
		||||
            prunezeros | empty_ opts = id
 | 
			
		||||
                       | otherwise   = fromMaybe nullacct . pruneAccounts (isZeroMixedAmount.aibalance)
 | 
			
		||||
            markboring | no_elide_ opts = id
 | 
			
		||||
                       | otherwise      = markBoringParentAccounts
 | 
			
		||||
      items = map (balanceReportItem opts) accts'
 | 
			
		||||
      total = sum [amt | ((a,_,indent),amt) <- items, if flat_ opts then accountNameLevel a == 1 else indent == 0]
 | 
			
		||||
              -- XXX check account level == 1 is valid when top-level accounts excluded
 | 
			
		||||
            balance     = if flat_ opts then aebalance else aibalance
 | 
			
		||||
            filterzeros = if empty_ opts then id else filter (not . isZeroMixedAmount . balance)
 | 
			
		||||
            filterempty = filter (\a -> anumpostings a > 0 || not (isZeroMixedAmount (balance a)))
 | 
			
		||||
            prunezeros  = if empty_ opts then id else fromMaybe nullacct . pruneAccounts (isZeroMixedAmount . balance)
 | 
			
		||||
            markboring  = if no_elide_ opts then id else markBoringParentAccounts
 | 
			
		||||
      items = dbg "items" $ map (balanceReportItem opts q) accts'
 | 
			
		||||
      total | not (flat_ opts) = dbg "total" $ sum [amt | ((_,_,indent),amt) <- items, indent == 0]
 | 
			
		||||
            | otherwise        = dbg "total" $
 | 
			
		||||
                                 if flatShowsExclusiveBalance
 | 
			
		||||
                                 then sum $ map snd items
 | 
			
		||||
                                 else sum $ map aebalance $ clipAccountsAndAggregate 1 accts'
 | 
			
		||||
 | 
			
		||||
-- | In an account tree with zero-balance leaves removed, mark the
 | 
			
		||||
-- elidable parent accounts (those with one subaccount and no balance
 | 
			
		||||
@ -80,10 +98,10 @@ markBoringParentAccounts = tieAccountParents . mapAccounts mark
 | 
			
		||||
    mark a | length (asubs a) == 1 && isZeroMixedAmount (aebalance a) = a{aboring=True}
 | 
			
		||||
           | otherwise = a
 | 
			
		||||
 | 
			
		||||
balanceReportItem :: ReportOpts -> Account -> BalanceReportItem
 | 
			
		||||
balanceReportItem opts a@Account{aname=name, aibalance=ibal}
 | 
			
		||||
  | flat_ opts = ((name, name,       0),      ibal)
 | 
			
		||||
  | otherwise  = ((name, elidedname, indent), ibal)
 | 
			
		||||
balanceReportItem :: ReportOpts -> Query -> Account -> BalanceReportItem
 | 
			
		||||
balanceReportItem opts _ a@Account{aname=name}
 | 
			
		||||
  | flat_ opts = ((name, name,       0),      (if flatShowsExclusiveBalance then aebalance else aibalance) a)
 | 
			
		||||
  | otherwise  = ((name, elidedname, indent), aibalance a)
 | 
			
		||||
  where
 | 
			
		||||
    elidedname = accountNameFromComponents (adjacentboringparentnames ++ [accountLeafName name])
 | 
			
		||||
    adjacentboringparentnames = reverse $ map (accountLeafName.aname) $ takeWhile aboring $ parents
 | 
			
		||||
 | 
			
		||||
@ -1,4 +1,4 @@
 | 
			
		||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-}
 | 
			
		||||
{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances, ScopedTypeVariables #-}
 | 
			
		||||
{-|
 | 
			
		||||
 | 
			
		||||
Multi-column balance reports, used by the balance command.
 | 
			
		||||
@ -52,11 +52,14 @@ type MultiBalanceReportRow = (RenderableAccountName, [MixedAmount])
 | 
			
		||||
 | 
			
		||||
instance Show MultiBalanceReport where
 | 
			
		||||
    -- use ppShow to break long lists onto multiple lines
 | 
			
		||||
    -- we have to add some bogus extra shows here to help ppShow parse the output
 | 
			
		||||
    -- we add some bogus extra shows here to help ppShow parse the output
 | 
			
		||||
    -- and wrap tuples and lists properly
 | 
			
		||||
    show (MultiBalanceReport (spans, items, totals)) =
 | 
			
		||||
        "MultiBalanceReport (ignore extra quotes):\n" ++ ppShow (show spans, map show items, totals)
 | 
			
		||||
 | 
			
		||||
-- type alias just to remind us which AccountNames might be depth-clipped, below.
 | 
			
		||||
type ClippedAccountName = AccountName
 | 
			
		||||
 | 
			
		||||
-- | Generate a multi balance report for the matched accounts, showing
 | 
			
		||||
-- their change of balance in each of the specified periods.
 | 
			
		||||
-- Currently has some limitations compared to the simple balance report,
 | 
			
		||||
@ -64,16 +67,35 @@ instance Show MultiBalanceReport where
 | 
			
		||||
periodBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
 | 
			
		||||
periodBalanceReport opts q j = MultiBalanceReport (spans, items, totals)
 | 
			
		||||
    where
 | 
			
		||||
      (q',depthq)  = (filterQuery (not . queryIsDepth) q, filterQuery queryIsDepth q)
 | 
			
		||||
      clip = filter (depthq `matchesAccount`)
 | 
			
		||||
      j' = filterJournalPostings q' $ journalSelectingAmountFromOpts opts j
 | 
			
		||||
      ps = journalPostings $
 | 
			
		||||
           filterJournalPostingAmounts (filterQuery queryIsSym q) -- remove amount parts which the query's sym: terms would exclude
 | 
			
		||||
           j'
 | 
			
		||||
      -- dbg = const id                                   -- exclude from debug output
 | 
			
		||||
      dbg s = let p = "periodBalanceReport" in Hledger.Utils.dbg (p++" "++s)  -- add prefix in debug output
 | 
			
		||||
 | 
			
		||||
      -- the requested span is the span of the query (which is
 | 
			
		||||
      -- based on -b/-e/-p opts and query args IIRC).
 | 
			
		||||
      requestedspan = queryDateSpan (date2_ opts) q
 | 
			
		||||
      -- Example data below is from
 | 
			
		||||
      -- hledger -f data/balance-multicol.journal balance -p 'monthly2013' assets: --depth=1 --debug=1
 | 
			
		||||
      -- with flatShowsExclusiveBalance=True. To see more, run other commands from
 | 
			
		||||
      -- tests/balance-multicol.test with --debug=1.
 | 
			
		||||
 | 
			
		||||
      nodepthq = dbg "nodepthq" $ filterQuery (not . queryIsDepth) q
 | 
			
		||||
                 -- And ([Date (DateSpan (Just 2013-01-01) (Just 2014-01-01)),Acct "assets:"])
 | 
			
		||||
      depthq   = dbg "depthq"   $ filterQuery queryIsDepth q
 | 
			
		||||
                 -- Any
 | 
			
		||||
      depth    = queryDepth depthq
 | 
			
		||||
                 -- Depth 1
 | 
			
		||||
      symq     = dbg "symq"     $ filterQuery queryIsSym q
 | 
			
		||||
                 -- Any
 | 
			
		||||
 | 
			
		||||
      ps :: [Posting] =
 | 
			
		||||
           dbg "ps" $
 | 
			
		||||
           journalPostings $
 | 
			
		||||
           filterJournalPostingAmounts symq $     -- exclude amount parts excluded by cur:
 | 
			
		||||
           filterJournalPostings nodepthq $       -- exclude unmatched postings, but include all depths
 | 
			
		||||
           journalSelectingAmountFromOpts opts j
 | 
			
		||||
           -- 
 | 
			
		||||
           -- [(assets:checking)                 1
 | 
			
		||||
           -- ,(assets:checking)                -1
 | 
			
		||||
           -- ,(assets:cash)                     1
 | 
			
		||||
           -- ,(assets:checking)                 1
 | 
			
		||||
           -- ]
 | 
			
		||||
 | 
			
		||||
      -- the report's span will be the requested span intersected with
 | 
			
		||||
      -- the selected data's span; or with -E, the requested span
 | 
			
		||||
@ -81,24 +103,96 @@ periodBalanceReport opts q j = MultiBalanceReport (spans, items, totals)
 | 
			
		||||
      reportspan | empty_ opts = requestedspan `orDatesFrom` journalspan
 | 
			
		||||
                 | otherwise   = requestedspan `spanIntersect` matchedspan
 | 
			
		||||
        where
 | 
			
		||||
          journalspan = journalDateSpan j'
 | 
			
		||||
          requestedspan = queryDateSpan (date2_ opts) q -- based on -b/-e/-p opts and query args IIRC
 | 
			
		||||
          journalspan   = journalDateSpan j
 | 
			
		||||
          matchedspan   = postingsDateSpan ps
 | 
			
		||||
 | 
			
		||||
      -- first implementation, probably inefficient
 | 
			
		||||
      spans               = dbg "1 " $ splitSpan (intervalFromOpts opts) reportspan
 | 
			
		||||
      psPerSpan           = dbg "3"  $ [filter (isPostingInDateSpan s) ps | s <- spans]
 | 
			
		||||
      acctnames           = dbg "4"  $ sort $ clip $ 
 | 
			
		||||
                            -- expandAccountNames $ 
 | 
			
		||||
                            accountNamesFromPostings ps
 | 
			
		||||
      allAcctsZeros       = dbg "5"  $ [(a, nullmixedamt) | a <- acctnames]
 | 
			
		||||
      someAcctBalsPerSpan = dbg "6"  $ [[(aname a, aibalance a) | a <- drop 1 $ accountsFromPostings ps, depthq `matchesAccount` aname a, aname a `elem` acctnames] | ps <- psPerSpan]
 | 
			
		||||
      balsPerSpan         = dbg "7"  $ [sortBy (comparing fst) $ unionBy (\(a,_) (a',_) -> a == a') acctbals allAcctsZeros | acctbals <- someAcctBalsPerSpan]
 | 
			
		||||
      balsPerAcct         = dbg "8"  $ transpose balsPerSpan
 | 
			
		||||
      acctsAndBals        = dbg "8.5" $ zip acctnames (map (map snd) balsPerAcct)
 | 
			
		||||
      items               = dbg "9"  $ [((a, a, accountNameLevel a), bs) | (a,bs) <- acctsAndBals, empty_ opts || any (not . isZeroMixedAmount) bs]
 | 
			
		||||
      highestLevelBalsPerSpan =
 | 
			
		||||
                            dbg "9.5" $ [[b | (a,b) <- spanbals, not $ any (`elem` acctnames) $ init $ expandAccountName a] | spanbals <- balsPerSpan]
 | 
			
		||||
      totals              = dbg "10" $ map sum highestLevelBalsPerSpan
 | 
			
		||||
      spans :: [DateSpan] =
 | 
			
		||||
          dbg "spans" $
 | 
			
		||||
          splitSpan (intervalFromOpts opts) reportspan
 | 
			
		||||
          -- [DateSpan (Just 2013-01-01) (Just 2013-02-01)
 | 
			
		||||
          -- ,DateSpan (Just 2013-02-01) (Just 2013-03-01)
 | 
			
		||||
          -- ,DateSpan (Just 2013-03-01) (Just 2013-04-01)
 | 
			
		||||
          -- ]
 | 
			
		||||
 | 
			
		||||
      psBySpan :: [[Posting]] =
 | 
			
		||||
          dbg "psBySpan" $
 | 
			
		||||
          [filter (isPostingInDateSpan s) ps | s <- spans]
 | 
			
		||||
          -- [[(assets:checking)                 1, (assets:checking)                -1]
 | 
			
		||||
          -- ,[(assets:cash)                     1]
 | 
			
		||||
          -- ,[(assets:checking)                 1]
 | 
			
		||||
 | 
			
		||||
      postedAccts :: [AccountName] =
 | 
			
		||||
          dbg "postedAccts" $
 | 
			
		||||
          sort $ accountNamesFromPostings ps
 | 
			
		||||
          -- [ "assets:cash" , "assets:checking" ]
 | 
			
		||||
 | 
			
		||||
      displayedAccts :: [ClippedAccountName] =
 | 
			
		||||
          dbg "displayedAccts" $
 | 
			
		||||
          nub $ map (clipAccountName depth) postedAccts
 | 
			
		||||
          -- [ "assets" ]
 | 
			
		||||
 | 
			
		||||
      zeroes :: [(ClippedAccountName, MixedAmount)] =
 | 
			
		||||
          dbg "zeroes" $
 | 
			
		||||
          [(a, nullmixedamt) | a <- displayedAccts]
 | 
			
		||||
          -- [ ( "assets" , 0 ) ]
 | 
			
		||||
 | 
			
		||||
      postedAcctBalsBySpan :: [[(ClippedAccountName, MixedAmount)]] =
 | 
			
		||||
          dbg "postedAcctBalsBySpan" $
 | 
			
		||||
          [postingAcctBals ps | ps <- psBySpan]
 | 
			
		||||
          where
 | 
			
		||||
            postingAcctBals :: [Posting] -> [(ClippedAccountName, MixedAmount)]
 | 
			
		||||
            postingAcctBals ps = [(aname a, (if flatShowsExclusiveBalance then aebalance else aibalance) a) | a <- as]
 | 
			
		||||
                where
 | 
			
		||||
                  as = depthLimit $ 
 | 
			
		||||
                       filter ((>0).anumpostings) $
 | 
			
		||||
                       drop 1 $ accountsFromPostings ps
 | 
			
		||||
                  depthLimit
 | 
			
		||||
                      | flatShowsExclusiveBalance = clipAccountsAndAggregate depth -- aggregate deeper balances at the depth limit
 | 
			
		||||
                      | otherwise                 = filter ((depthq `matchesAccount`).aname) -- exclude deeper balances
 | 
			
		||||
          -- [ [ ( "assets" , 0 ) ]
 | 
			
		||||
          -- , [ ( "assets" , 1 ) ]
 | 
			
		||||
          -- , [ ( "assets" , 1 ) ]
 | 
			
		||||
          -- ]
 | 
			
		||||
 | 
			
		||||
      displayedBalsBySpan :: [[(ClippedAccountName, MixedAmount)]] =
 | 
			
		||||
          dbg "displayedBalsBySpan" $
 | 
			
		||||
          [sortBy (comparing fst) $ unionBy (\(a,_) (a',_) -> a == a') postedacctbals zeroes
 | 
			
		||||
           | postedacctbals <- postedAcctBalsBySpan]
 | 
			
		||||
          --
 | 
			
		||||
          -- [ [ ( "assets" , 0 ) ]
 | 
			
		||||
          -- , [ ( "assets" , 1 ) ]
 | 
			
		||||
          -- , [ ( "assets" , 1 ) ]
 | 
			
		||||
          -- ]
 | 
			
		||||
 | 
			
		||||
      displayedBalsByAcct :: [[(ClippedAccountName, MixedAmount)]] =
 | 
			
		||||
          dbg "displayedBalsByAcct" $
 | 
			
		||||
          transpose displayedBalsBySpan
 | 
			
		||||
          -- [ [ ( "assets" , 0 ) , ( "assets" , 1 ) , ( "assets" , 1 ) ] ]
 | 
			
		||||
 | 
			
		||||
      acctBalsAlist :: [(ClippedAccountName, [MixedAmount])] =
 | 
			
		||||
          dbg "acctBalsAlist" $
 | 
			
		||||
          zip displayedAccts (map (map snd) [bs | bs <- displayedBalsByAcct
 | 
			
		||||
                                             -- , maybe False ((`elem` postedAccts).fst) $ headMay bs
 | 
			
		||||
                                            ])
 | 
			
		||||
          -- [ ( "assets" , [ 0 , 1 , 1 ] ) ]
 | 
			
		||||
 | 
			
		||||
      items :: [MultiBalanceReportRow] =
 | 
			
		||||
          dbg "items" $
 | 
			
		||||
          [((a, a, accountNameLevel a), bs) | (a,bs) <- acctBalsAlist, empty_ opts || any (not . isZeroMixedAmount) bs]
 | 
			
		||||
          -- [ ( ( "assets" , "assets" , 1 ) , [ 0 , 1 , 1 ] ) ]
 | 
			
		||||
 | 
			
		||||
      -- highestLevelBalsBySpan :: [[MixedAmount]] =
 | 
			
		||||
      --     dbg "highestLevelBalsBySpan" $
 | 
			
		||||
      --     [[b | (a,b) <- spanbals, not $ any (`elem` postedAccts) $ init $ expandAccountName a] | spanbals <- displayedBalsBySpan]
 | 
			
		||||
 | 
			
		||||
      totals :: [MixedAmount] =
 | 
			
		||||
          dbg "totals" $
 | 
			
		||||
          if flatShowsExclusiveBalance
 | 
			
		||||
          then map (sum . map snd) displayedBalsBySpan
 | 
			
		||||
          else map (sum . map pamount) psBySpan
 | 
			
		||||
          -- else map sum highestLevelBalsBySpan
 | 
			
		||||
          -- [ 0 , 1 , 1 ]
 | 
			
		||||
 | 
			
		||||
-- | Generate a multi balance report for the matched accounts, showing
 | 
			
		||||
-- their cumulative or (with -H) historical balance in each of the specified periods.
 | 
			
		||||
@ -106,50 +200,50 @@ periodBalanceReport opts q j = MultiBalanceReport (spans, items, totals)
 | 
			
		||||
cumulativeOrHistoricalBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport
 | 
			
		||||
cumulativeOrHistoricalBalanceReport opts q j = MultiBalanceReport (periodbalancespans, items, totals)
 | 
			
		||||
    where
 | 
			
		||||
      -- dbg = const id                                   -- exclude from debug output
 | 
			
		||||
      dbg s = let p = "cumulativeOrHistoricalBalanceReport" in Hledger.Utils.dbg (p++" "++s)  -- add prefix in debug output
 | 
			
		||||
 | 
			
		||||
      -- select/adjust basic report dates
 | 
			
		||||
      (reportspan, _) = reportSpans opts q j
 | 
			
		||||
      (reportspan, _) = dbg "report spans" $ reportSpans opts q j
 | 
			
		||||
 | 
			
		||||
      -- rewrite query to use adjusted dates
 | 
			
		||||
      -- starting balances and accounts from transactions before the report start date
 | 
			
		||||
      startacctbals = dbg "startacctbals" $ map (\((a,_,_),b) -> (a,b)) $ startbalanceitems
 | 
			
		||||
          where
 | 
			
		||||
            dateless              = filterQuery (not . queryIsDate)
 | 
			
		||||
      depthless = filterQuery (not . queryIsDepth)
 | 
			
		||||
      q' = dateless $ depthless q
 | 
			
		||||
      -- reportq = And [q', Date reportspan]
 | 
			
		||||
 | 
			
		||||
      -- get starting balances and accounts from preceding txns
 | 
			
		||||
      precedingq = And [q', Date $ DateSpan Nothing (spanStart reportspan)]
 | 
			
		||||
      (startbalanceitems,_) = balanceReport opts{flat_=True,empty_=True} precedingq j
 | 
			
		||||
      startacctbals = dbg "startacctbals"   $ map (\((a,_,_),b) -> (a,b)) startbalanceitems
 | 
			
		||||
            precedingq            = dbg "precedingq" $ And [dateless q, Date $ DateSpan Nothing (spanStart reportspan)]
 | 
			
		||||
            (startbalanceitems,_) = dbg "starting balance report" $ balanceReport opts{flat_=True,empty_=True} precedingq j
 | 
			
		||||
      -- acctsWithStartingBalance = map fst $ filter (not . isZeroMixedAmount . snd) startacctbals
 | 
			
		||||
      startingBalanceFor a | balancetype_ opts == HistoricalBalance = fromMaybe nullmixedamt $ lookup a startacctbals
 | 
			
		||||
      startingBalanceFor a
 | 
			
		||||
          | balancetype_ opts == HistoricalBalance = fromMaybe nullmixedamt $ lookup a startacctbals
 | 
			
		||||
          | otherwise                              = nullmixedamt
 | 
			
		||||
 | 
			
		||||
      -- get balance changes by period
 | 
			
		||||
      MultiBalanceReport (periodbalancespans,periodbalanceitems,_) = dbg "changes" $ periodBalanceReport opts q j
 | 
			
		||||
      -- balance changes in each period for each account
 | 
			
		||||
      MultiBalanceReport (periodbalancespans,periodbalanceitems,_) = dbg "balance changes report" $ periodBalanceReport opts q j
 | 
			
		||||
      balanceChangesByAcct    = map (\((a,_,_),bs) -> (a,bs)) periodbalanceitems
 | 
			
		||||
      acctsWithBalanceChanges = map fst $ filter ((any (not . isZeroMixedAmount)) . snd) balanceChangesByAcct
 | 
			
		||||
      balanceChangesFor a     = fromMaybe (error $ "no data for account: a") $ -- XXX
 | 
			
		||||
                                lookup a balanceChangesByAcct
 | 
			
		||||
 | 
			
		||||
      -- accounts to report on
 | 
			
		||||
      reportaccts -- = dbg' "reportaccts" $ (dbg' "acctsWithStartingBalance" acctsWithStartingBalance) `union` (dbg' "acctsWithBalanceChanges" acctsWithBalanceChanges)
 | 
			
		||||
                  = acctsWithBalanceChanges
 | 
			
		||||
      reportaccts = dbg "reportaccts"
 | 
			
		||||
                    acctsWithBalanceChanges
 | 
			
		||||
                    -- $ (dbg' "acctsWithStartingBalance" acctsWithStartingBalance) `union` (dbg' "acctsWithBalanceChanges" acctsWithBalanceChanges)
 | 
			
		||||
 | 
			
		||||
      -- sum balance changes to get ending balances for each period
 | 
			
		||||
      -- ending balances in each period (starting balance plus balance changes) for an account
 | 
			
		||||
      endingBalancesFor a = 
 | 
			
		||||
          dbg "ending balances" $ drop 1 $ scanl (+) (startingBalanceFor a) $
 | 
			
		||||
          dbg "balance changes" $ balanceChangesFor a
 | 
			
		||||
          dbg ("balance changes for "++a) $ balanceChangesFor a
 | 
			
		||||
 | 
			
		||||
      items  = dbg "items"  $ [((a,a,0), endingBalancesFor a) | a <- reportaccts]
 | 
			
		||||
 | 
			
		||||
      -- sum highest-level account balances in each column for column totals
 | 
			
		||||
      totals = dbg "totals" $ map sum highestlevelbalsbycol
 | 
			
		||||
      totals = dbg "totals" $ 
 | 
			
		||||
          if flatShowsExclusiveBalance
 | 
			
		||||
          then map sum balsbycol
 | 
			
		||||
          else map sum highestlevelbalsbycol
 | 
			
		||||
          where
 | 
			
		||||
            balsbycol             = transpose $ map endingBalancesFor reportaccts
 | 
			
		||||
            highestlevelbalsbycol = transpose $ map endingBalancesFor highestlevelaccts
 | 
			
		||||
            highestlevelaccts     =
 | 
			
		||||
                dbg "highestlevelaccts" $
 | 
			
		||||
                [a | a <- reportaccts, not $ any (`elem` reportaccts) $ init $ expandAccountName a]
 | 
			
		||||
 | 
			
		||||
      -- enable to debug just this function
 | 
			
		||||
      -- dbg :: Show a => String -> a -> a
 | 
			
		||||
      -- dbg = lstrace
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@ -1,31 +0,0 @@
 | 
			
		||||
# issue 94: total balance should be that of top-level accounts, with and without --flat
 | 
			
		||||
# 1. 
 | 
			
		||||
hledgerdev -f - balance
 | 
			
		||||
<<<
 | 
			
		||||
1/1
 | 
			
		||||
    (a)     1
 | 
			
		||||
 | 
			
		||||
1/1
 | 
			
		||||
    (a:aa)  1
 | 
			
		||||
>>>
 | 
			
		||||
                   2  a
 | 
			
		||||
                   1    aa
 | 
			
		||||
--------------------
 | 
			
		||||
                   2
 | 
			
		||||
>>>= 0
 | 
			
		||||
 | 
			
		||||
# 2. 
 | 
			
		||||
hledgerdev -f - balance --flat
 | 
			
		||||
<<<
 | 
			
		||||
1/1
 | 
			
		||||
    (a)     1
 | 
			
		||||
 | 
			
		||||
1/1
 | 
			
		||||
    (a:aa)  1
 | 
			
		||||
>>>
 | 
			
		||||
                   2  a
 | 
			
		||||
                   1  a:aa
 | 
			
		||||
--------------------
 | 
			
		||||
                   2
 | 
			
		||||
>>>= 0
 | 
			
		||||
 | 
			
		||||
							
								
								
									
										51
									
								
								tests/balance-flat.test
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										51
									
								
								tests/balance-flat.test
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,51 @@
 | 
			
		||||
# --flat shows inclusive balances; total balance should be that of top-level accounts (issue 94)
 | 
			
		||||
# # 1. 
 | 
			
		||||
# hledgerdev -f - balance --flat
 | 
			
		||||
# <<<
 | 
			
		||||
# 1/1
 | 
			
		||||
#     (a)     1
 | 
			
		||||
#     (a:aa)  1
 | 
			
		||||
# >>>
 | 
			
		||||
#                    2  a
 | 
			
		||||
#                    1  a:aa
 | 
			
		||||
# --------------------
 | 
			
		||||
#                    2
 | 
			
		||||
# >>>= 0
 | 
			
		||||
 | 
			
		||||
# --flat shows exclusive balances
 | 
			
		||||
# 1. 
 | 
			
		||||
hledgerdev -f - balance --flat
 | 
			
		||||
<<<
 | 
			
		||||
1/1
 | 
			
		||||
 (a:aa)       1
 | 
			
		||||
 (a:aa:aaa)   1
 | 
			
		||||
 (a:aa:bbb)   1
 | 
			
		||||
 (b)          1
 | 
			
		||||
 (b:bb:bbb)   1
 | 
			
		||||
>>>
 | 
			
		||||
                   1  a:aa
 | 
			
		||||
                   1  a:aa:aaa
 | 
			
		||||
                   1  a:aa:bbb
 | 
			
		||||
                   1  b
 | 
			
		||||
                   1  b:bb:bbb
 | 
			
		||||
--------------------
 | 
			
		||||
                   5
 | 
			
		||||
>>>= 0
 | 
			
		||||
 | 
			
		||||
# --flat --depth shows the same accounts, but clipped and aggregated at the depth limit
 | 
			
		||||
# 2. 
 | 
			
		||||
hledgerdev -f - balance --flat --depth 2
 | 
			
		||||
<<<
 | 
			
		||||
1/1
 | 
			
		||||
 (a:aa)       1
 | 
			
		||||
 (a:aa:aaa)   1
 | 
			
		||||
 (a:aa:bbb)   1
 | 
			
		||||
 (b)          1
 | 
			
		||||
 (b:bb:bbb)   1
 | 
			
		||||
>>>
 | 
			
		||||
                   3  a:aa
 | 
			
		||||
                   1  b
 | 
			
		||||
                   1  b:bb
 | 
			
		||||
--------------------
 | 
			
		||||
                   5
 | 
			
		||||
>>>= 0
 | 
			
		||||
@ -11,14 +11,14 @@ hledgerdev -f data/balance-multicol.journal register
 | 
			
		||||
2013/03/01                      (assets:checking)                1            13
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# 2. A period balance (flow) report.
 | 
			
		||||
# 2. A period balance (flow) report. --no-total also works but isn't pretty.
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --no-total
 | 
			
		||||
>>>
 | 
			
		||||
Change of balance (flow):
 | 
			
		||||
 | 
			
		||||
                 ||  2013/01/01-2013/01/31  2013/02/01-2013/02/28  2013/03/01-2013/03/31 
 | 
			
		||||
=================++======================================================================
 | 
			
		||||
 assets          ||                      0                      2                      1 
 | 
			
		||||
 assets          ||                      0                      1                      0 
 | 
			
		||||
 assets:cash     ||                      0                      1                      0 
 | 
			
		||||
 assets:checking ||                      0                      0                      1 
 | 
			
		||||
-----------------++----------------------------------------------------------------------
 | 
			
		||||
@ -55,7 +55,7 @@ Ending balance (cumulative):
 | 
			
		||||
 | 
			
		||||
                 ||  2013/01/31  2013/02/28  2013/03/31 
 | 
			
		||||
=================++=====================================
 | 
			
		||||
 assets          ||           0           2           3 
 | 
			
		||||
 assets          ||           0           1           1 
 | 
			
		||||
 assets:cash     ||           0           1           1 
 | 
			
		||||
 assets:checking ||           0           0           1 
 | 
			
		||||
-----------------++-------------------------------------
 | 
			
		||||
@ -72,7 +72,7 @@ Ending balance (cumulative):
 | 
			
		||||
 | 
			
		||||
                 ||  2013/01/31  2013/02/28  2013/03/31 
 | 
			
		||||
=================++=====================================
 | 
			
		||||
 assets          ||           0           1           2 
 | 
			
		||||
 assets          ||           0           1           1 
 | 
			
		||||
 assets:checking ||           0           0           1 
 | 
			
		||||
-----------------++-------------------------------------
 | 
			
		||||
                 ||           0           1           2 
 | 
			
		||||
@ -86,7 +86,7 @@ Ending balance (historical):
 | 
			
		||||
 | 
			
		||||
                 ||  2013/01/31  2013/02/28  2013/03/31 
 | 
			
		||||
=================++=====================================
 | 
			
		||||
 assets          ||          10          12          13 
 | 
			
		||||
 assets          ||           0           1           1 
 | 
			
		||||
 assets:cash     ||           0           1           1 
 | 
			
		||||
 assets:checking ||          10          10          11 
 | 
			
		||||
-----------------++-------------------------------------
 | 
			
		||||
@ -124,15 +124,70 @@ Ending balance (cumulative):
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# 9. historical
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' not:assets$ --historical
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --historical
 | 
			
		||||
>>>
 | 
			
		||||
Ending balance (historical):
 | 
			
		||||
 | 
			
		||||
                 ||  2013/01/31  2013/02/28  2013/03/31 
 | 
			
		||||
=================++=====================================
 | 
			
		||||
 assets          ||           0           1           1 
 | 
			
		||||
 assets:cash     ||           0           1           1 
 | 
			
		||||
 assets:checking ||          10          10          11 
 | 
			
		||||
-----------------++-------------------------------------
 | 
			
		||||
                 ||          10          11          12 
 | 
			
		||||
                 ||          10          12          13 
 | 
			
		||||
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# --depth
 | 
			
		||||
 | 
			
		||||
# 10. A flow report with depth limiting. The depth limit aggregates the three accounts as "assets".
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --depth 1
 | 
			
		||||
>>>
 | 
			
		||||
Change of balance (flow):
 | 
			
		||||
 | 
			
		||||
        ||  2013/01/01-2013/01/31  2013/02/01-2013/02/28  2013/03/01-2013/03/31 
 | 
			
		||||
========++======================================================================
 | 
			
		||||
 assets ||                      0                      2                      1 
 | 
			
		||||
--------++----------------------------------------------------------------------
 | 
			
		||||
        ||                      0                      2                      1 
 | 
			
		||||
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# 11. As above, but postings in the top-level assets account have been excluded.
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --depth 1 assets:
 | 
			
		||||
>>>
 | 
			
		||||
Change of balance (flow):
 | 
			
		||||
 | 
			
		||||
        ||  2013/01/01-2013/01/31  2013/02/01-2013/02/28  2013/03/01-2013/03/31 
 | 
			
		||||
========++======================================================================
 | 
			
		||||
 assets ||                      0                      1                      1 
 | 
			
		||||
--------++----------------------------------------------------------------------
 | 
			
		||||
        ||                      0                      1                      1 
 | 
			
		||||
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# 12. A cumulative balance report with depth limiting.
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --depth 1 --cumulative
 | 
			
		||||
>>>
 | 
			
		||||
Ending balance (cumulative):
 | 
			
		||||
 | 
			
		||||
        ||  2013/01/31  2013/02/28  2013/03/31 
 | 
			
		||||
========++=====================================
 | 
			
		||||
 assets ||           0           2           3 
 | 
			
		||||
--------++-------------------------------------
 | 
			
		||||
        ||           0           2           3 
 | 
			
		||||
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# 13. A historical balance report with depth limiting.
 | 
			
		||||
hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --depth 1 --historical
 | 
			
		||||
>>>
 | 
			
		||||
Ending balance (historical):
 | 
			
		||||
 | 
			
		||||
        ||  2013/01/31  2013/02/28  2013/03/31 
 | 
			
		||||
========++=====================================
 | 
			
		||||
 assets ||          10          12          13 
 | 
			
		||||
--------++-------------------------------------
 | 
			
		||||
        ||          10          12          13 
 | 
			
		||||
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
		Loading…
	
		Reference in New Issue
	
	Block a user