diff --git a/data/balance-multicol.journal b/data/balance-multicol.journal new file mode 100644 index 000000000..ca3787293 --- /dev/null +++ b/data/balance-multicol.journal @@ -0,0 +1,19 @@ +; A sample journal for testing multi-column balance report. See tests/balance-multicol.test. + +2012/12/31 + (assets:checking) 10 + +2013/1/1 + (assets:checking) 1 + +2013/1/15 + (assets:checking) -1 + +2013/2/1 + (assets:cash) 1 + +2013/2/2 + (assets) 1 + +2013/3/1 + (assets:checking) 1 diff --git a/hledger-lib/Hledger/Data/Dates.hs b/hledger-lib/Hledger/Data/Dates.hs index ab1cb74f7..7b347e6fa 100644 --- a/hledger-lib/Hledger/Data/Dates.hs +++ b/hledger-lib/Hledger/Data/Dates.hs @@ -40,6 +40,9 @@ module Hledger.Data.Dates ( failIfInvalidYear, datesepchar, datesepchars, + spanStart, + spanEnd, + spansSpan, spanIntersect, spansIntersect, spanUnion, @@ -65,7 +68,7 @@ import Data.Time.Calendar import Data.Time.Calendar.OrdinalDate import Data.Time.Clock import Data.Time.LocalTime -import Safe (readMay) +import Safe (headMay, lastMay, readMay) import System.Locale (defaultTimeLocale) import Test.HUnit import Text.ParserCombinators.Parsec @@ -108,6 +111,16 @@ getCurrentYear = do elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a elapsedSeconds t1 = realToFrac . diffUTCTime t1 +spanStart :: DateSpan -> Maybe Day +spanStart (DateSpan d _) = d + +spanEnd :: DateSpan -> Maybe Day +spanEnd (DateSpan _ d) = d + +-- | Get overall span enclosing multiple sequentially ordered spans. +spansSpan :: [DateSpan] -> DateSpan +spansSpan spans = DateSpan (maybe Nothing spanStart $ headMay spans) (maybe Nothing spanEnd $ lastMay spans) + -- | Split a DateSpan into one or more consecutive spans at the specified interval. splitSpan :: Interval -> DateSpan -> [DateSpan] splitSpan _ (DateSpan Nothing Nothing) = [DateSpan Nothing Nothing] @@ -154,7 +167,9 @@ spanContainsDate (DateSpan (Just b) Nothing) d = d >= b spanContainsDate (DateSpan (Just b) (Just e)) d = d >= b && d < e -- | Combine two datespans, filling any unspecified dates in the first --- with dates from the second. +-- with dates from the second. Not a clip operation, just uses the +-- second's start/end dates as defaults when the first does not +-- specify them. orDatesFrom (DateSpan a1 b1) (DateSpan a2 b2) = DateSpan a b where a = if isJust a1 then a1 else a2 b = if isJust b1 then b1 else b2 diff --git a/hledger-lib/Hledger/Reports.hs b/hledger-lib/Hledger/Reports.hs index b1d4a0635..72d6c6a65 100644 --- a/hledger-lib/Hledger/Reports.hs +++ b/hledger-lib/Hledger/Reports.hs @@ -1,16 +1,18 @@ -{-# LANGUAGE RecordWildCards, DeriveDataTypeable #-} +{-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-} {-| Generate several common kinds of report from a journal, as \"*Report\" - simple intermediate data structures intended to be easily rendered as text, html, json, csv etc. by hledger commands, hamlet templates, -javascript, or whatever. This is under Hledger.Cli since it depends -on the command-line options, should move to hledger-lib later. +javascript, or whatever. -} module Hledger.Reports ( + -- * Report options + -- | ReportOpts(..), + BalanceType(..), DisplayExp, FormatStr, defreportopts, @@ -21,16 +23,20 @@ module Hledger.Reports ( journalSelectingAmountFromOpts, queryFromOpts, queryOptsFromOpts, + reportSpans, -- * Entries report + -- | EntriesReport, EntriesReportItem, entriesReport, -- * Postings report + -- | PostingsReport, PostingsReportItem, postingsReport, mkpostingsReportItem, -- XXX for showPostingWithBalanceForVty in Hledger.Cli.Register -- * Transactions report + -- | TransactionsReport, TransactionsReportItem, triDate, @@ -39,16 +45,25 @@ module Hledger.Reports ( transactionsReportByCommodity, journalTransactionsReport, accountTransactionsReport, - -- * Accounts report - AccountsReport, - AccountsReportItem, - accountsReport, - -- * Accounts report - FlowReport, - FlowReportItem, - flowReport, - -- * Other "reports" + + -- * Balance reports + {-| + These are used for the various modes of the balance command + (see "Hledger.Cli.Balance"). + -} + BalanceReport, + BalanceReportItem, + balanceReport, + MultiBalanceReport(..), + MultiBalanceReportItem, + RenderableAccountName, + periodBalanceReport, + cumulativeOrHistoricalBalanceReport, + + -- * Other reports + -- | accountBalanceHistory, + -- * Tests tests_Hledger_Reports ) @@ -59,7 +74,6 @@ import Data.List import Data.Maybe -- import qualified Data.Map as M import Data.Ord -import Data.PPrint import Data.Time.Calendar -- import Data.Tree import Safe (headMay, lastMay) @@ -92,6 +106,7 @@ data ReportOpts = ReportOpts { ,empty_ :: Bool ,no_elide_ :: Bool ,real_ :: Bool + ,balancetype_ :: BalanceType -- for balance command ,flat_ :: Bool -- for balance command ,drop_ :: Int -- " ,no_total_ :: Bool -- " @@ -109,6 +124,13 @@ data ReportOpts = ReportOpts { type DisplayExp = String type FormatStr = String +-- | Which balance is being shown in a multi-column balance report. +data BalanceType = PeriodBalance -- ^ The change of balance in each period. + | CumulativeBalance -- ^ The accumulated balance at each period's end, starting from zero at the report start date. + | HistoricalBalance -- ^ The historical balance at each period's end, starting from the account balances at the report start date. + deriving (Eq,Show,Data,Typeable) +instance Default BalanceType where def = PeriodBalance + defreportopts = ReportOpts def def @@ -134,6 +156,7 @@ defreportopts = ReportOpts def def def + def instance Default ReportOpts where def = defreportopts @@ -284,8 +307,8 @@ postingsReport opts q j = -- trace ("q: "++show q++"\nq': "++show q') $ $ dbg "ps3" $ (if related_ opts then concatMap relatedPostings else id) $ dbg "ps2" $ filter (q' `matchesPosting`) $ dbg "ps1" $ journalPostings j' - dbg :: Show a => String -> a -> a - dbg = flip const + -- enable to debug just this function + -- dbg :: Show a => String -> a -> a -- dbg = lstrace empty = queryEmpty q @@ -590,21 +613,28 @@ filterTransactionPostings m t@Transaction{tpostings=ps} = t{tpostings=filter (m ------------------------------------------------------------------------------- --- | An accounts report is a list of account names (full and short --- variants) with their balances, appropriate indentation for rendering as --- a hierarchy, and grand total. This is used eg by the balance command. -type AccountsReport = ([AccountsReportItem] -- line items, one per account +-- | A list of account names plus rendering info, along with their +-- balances as of the end of the reporting period, and the grand +-- total. Used for the balance command's single-column mode. +type BalanceReport = ([BalanceReportItem] -- line items, one per account ,MixedAmount -- total balance of all accounts ) -type AccountsReportItem = (AccountName -- full account name - ,AccountName -- short account name for display (the leaf name, prefixed by any boring parents immediately above) - ,Int -- how many steps to indent this account (0 with --flat, otherwise the 0-based account depth excluding boring parents) - ,MixedAmount) -- account balance, includes subs -- XXX unless --flat is present +-- | * Full account name, +-- +-- * short account name for display (the leaf name, prefixed by any boring parents immediately above), +-- +-- * how many steps to indent this account (the 0-based account depth excluding boring parents, or 0 with --flat), +-- +-- * account balance (including subaccounts (XXX unless --flat)). +type BalanceReportItem = (AccountName + ,AccountName + ,Int + ,MixedAmount) -- | Select accounts, and get their balances at the end of the selected -- period, and misc. display information, for an accounts report. -accountsReport :: ReportOpts -> Query -> Journal -> AccountsReport -accountsReport opts q j = (items, total) +balanceReport :: ReportOpts -> Query -> Journal -> BalanceReport +balanceReport opts q j = (items, total) where l = ledgerFromJournal q $ journalSelectingAmountFromOpts opts j accts = clipAccounts (queryDepth q) $ ledgerRootAccount l @@ -618,8 +648,9 @@ accountsReport opts q j = (items, total) | otherwise = fromMaybe nullacct . pruneAccounts (isZeroMixedAmount.aibalance) markboring | no_elide_ opts = id | otherwise = markBoringParentAccounts - items = map (accountsReportItem opts) accts' + 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 -- | In an account tree with zero-balance leaves removed, mark the -- elidable parent accounts (those with one subaccount and no balance @@ -630,8 +661,8 @@ markBoringParentAccounts = tieAccountParents . mapAccounts mark mark a | length (asubs a) == 1 && isZeroMixedAmount (aebalance a) = a{aboring=True} | otherwise = a -accountsReportItem :: ReportOpts -> Account -> AccountsReportItem -accountsReportItem opts a@Account{aname=name, aibalance=ibal} +balanceReportItem :: ReportOpts -> Account -> BalanceReportItem +balanceReportItem opts a@Account{aname=name, aibalance=ibal} | flat_ opts = (name, name, 0, ibal) | otherwise = (name, elidedname, indent, ibal) where @@ -643,57 +674,56 @@ accountsReportItem opts a@Account{aname=name, aibalance=ibal} ------------------------------------------------------------------------------- --- There are two kinds of report we want here. A "periodic flow" --- report shows the change of account balance in each period, or --- equivalently (assuming accurate postings) the sum of postings in --- each period. Eg below, 20 is the sum of income postings in --- Jan. This is like a periodic income statement or (with cash --- accounts) cashflow statement. +-- | A multi(column) balance report is a list of accounts, each with a list of +-- balances corresponding to the report's column periods. The balances' meaning depends +-- on the type of balance report (see 'BalanceType' and "Hledger.Cli.Balance"). +-- Also included are the overall total for each period, the date span for each period, +-- and some additional rendering info for the accounts. -- --- Account Jan Feb Mar --- income 20 10 -5 --- --- A "periodic balance" report shows the final account balance in each --- period, equivalent to the sum of all postings before the end of the --- period. Eg below, 120 is the sum of all asset postings before the --- end of Jan, including postings before january (or perhaps an --- "opening balance" posting). This is like a periodic balance sheet. --- --- Acct Jan Feb Mar --- asset 120 130 125 --- --- If the columns are consecutive periods, balances can be calculated --- from flows by beginning with the start-of-period balance (above, --- 100) and summing the flows rightward. - --- | A flow report is a list of account names (and associated --- rendering info), plus their change in balance during one or more --- periods (date spans). The periods are included, and also an overall --- total for each one. --- -type FlowReport = - ([DateSpan] -- the date span for each report column - ,[FlowReportItem] -- line items, one per account - ,[MixedAmount] -- the final total for each report column +-- * The date span for each report column, +-- +-- * line items (one per account), +-- +-- * the final total for each report column. +newtype MultiBalanceReport = MultiBalanceReport + ([DateSpan] + ,[MultiBalanceReportItem] + ,[MixedAmount] ) -type FlowReportItem = --- (RenderableAccountName -- the account name and rendering hints - (AccountName - ,[MixedAmount] -- the account's change of (inclusive) balance in each of the report's periods +-- | * The account name with rendering hints, +-- +-- * the account's balance (per-period balance, cumulative ending +-- balance, or historical ending balance) in each of the report's +-- periods. +type MultiBalanceReportItem = + (RenderableAccountName + ,[MixedAmount] ) +-- | * Full account name, +-- +-- * ledger-style short account name (the leaf name, prefixed by any boring parents immediately above), +-- +-- * indentation steps to use when rendering a ledger-style account tree +-- (the 0-based depth of this account excluding boring parents; or with --flat, 0) type RenderableAccountName = - (AccountName -- full account name - ,AccountName -- ledger-style short account name (the leaf name, prefixed by any boring parents immediately above) - ,Int -- indentation (in steps) to use when rendering a ledger-style account tree - -- (the 0-based depth of this account excluding boring parents; or with --flat, 0) + (AccountName + ,AccountName + ,Int ) --- | Select accounts and get their flows (change of balance) in each --- period, plus misc. display information, for a flow report. -flowReport :: ReportOpts -> Query -> Journal -> FlowReport -flowReport opts q j = (spans, items, totals) +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 + -- and wrap tuples and lists properly + show (MultiBalanceReport (spans, items, totals)) = + "MultiBalanceReport (ignore extra quotes):\n" ++ ppShow (show spans, map show items, totals) + +-- | Select accounts and get their period balance (change of balance) in each +-- period, plus misc. display information, for a period balance report. +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`) @@ -716,39 +746,97 @@ flowReport opts q j = (spans, items, totals) -- 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 + 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] | ps <- psPerSpan] + 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 - items = dbg "9" $ zip acctnames $ map (map snd) balsPerAcct - totals = dbg "10" $ [sum [b | (a,b) <- bals, accountNameLevel a == 1] | bals <- 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 - dbg,dbg' :: Show a => String -> a -> a - dbg = flip const - dbg' = lstrace +------------------------------------------------------------------------------- + +-- | Calculate the overall span and per-period date spans for a report +-- based on command-line options, the parsed search query, and the +-- journal data. If a reporting interval is specified, the report span +-- will be enlarged to include a whole number of report periods. +-- Reports will sometimes trim these spans further when appropriate. +reportSpans :: ReportOpts -> Query -> Journal -> (DateSpan, [DateSpan]) +reportSpans opts q j = (reportspan, spans) + where + -- get the requested span from the query, which is based on + -- -b/-e/-p opts and query args. + requestedspan = queryDateSpan (date2_ opts) q + + -- set the start and end date to the journal's if not specified + requestedspan' = requestedspan `orDatesFrom` journalDateSpan j + + -- if there's a reporting interval, calculate the report periods + -- which enclose the requested span + spans = dbg "spans" $ splitSpan (intervalFromOpts opts) requestedspan' + + -- the overall report span encloses the periods + reportspan = DateSpan + (maybe Nothing spanStart $ headMay spans) + (maybe Nothing spanEnd $ lastMay spans) + +-- | Select accounts and get their ending balance in each period, plus +-- account name display information, for a cumulative or historical balance report. +cumulativeOrHistoricalBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport +cumulativeOrHistoricalBalanceReport opts q j = MultiBalanceReport (periodbalancespans, items, totals) + where + -- select/adjust basic report dates + (reportspan, _) = reportSpans opts q j + + -- rewrite query to use adjusted dates + 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 + -- acctsWithStartingBalance = map fst $ filter (not . isZeroMixedAmount . snd) 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 + 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 + + -- sum balance changes to get ending balances for each period + endingBalancesFor a = + dbg "ending balances" $ drop 1 $ scanl (+) (startingBalanceFor a) $ + dbg "balance changes" $ 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 + where + 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 - -- accts' - -- | flat_ opts = filterzeros $ tail $ flattenAccounts accts - -- | otherwise = filter (not.aboring) $ tail $ flattenAccounts $ markboring $ prunezeros 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 - --- flowReportItem :: ReportOpts -> Account -> FlowReportItem --- flowReportItem opts a@Account{aname=name, aibalance=ibal} --- | flat_ opts = (name, name, 0, ibal) --- | otherwise = (name, elidedname, indent, ibal) --- where --- elidedname = accountNameFromComponents (adjacentboringparentnames ++ [accountLeafName name]) --- adjacentboringparentnames = reverse $ map (accountLeafName.aname) $ takeWhile aboring $ parents --- indent = length $ filter (not.aboring) parents --- parents = init $ parentAccounts a - ------------------------------------------------------------------------------- -- | Get the historical running inclusive balance of a particular account, @@ -932,20 +1020,20 @@ tests_postingsReport = [ -} ] -tests_accountsReport = +tests_balanceReport = let (opts,journal) `gives` r = do let (eitems, etotal) = r - (aitems, atotal) = accountsReport opts (queryFromOpts nulldate opts) journal + (aitems, atotal) = balanceReport opts (queryFromOpts nulldate opts) journal assertEqual "items" eitems aitems -- assertEqual "" (length eitems) (length aitems) -- mapM (\(e,a) -> assertEqual "" e a) $ zip eitems aitems assertEqual "total" etotal atotal in [ - "accountsReport with no args on null journal" ~: do + "balanceReport with no args on null journal" ~: do (defreportopts, nulljournal) `gives` ([], Mixed [nullamt]) - ,"accountsReport with no args on sample journal" ~: do + ,"balanceReport with no args on sample journal" ~: do (defreportopts, samplejournal) `gives` ([ ("assets","assets",0, mamountp' "$-1.00") @@ -961,7 +1049,7 @@ tests_accountsReport = ], Mixed [nullamt]) - ,"accountsReport with --depth=N" ~: do + ,"balanceReport with --depth=N" ~: do (defreportopts{depth_=Just 1}, samplejournal) `gives` ([ ("assets", "assets", 0, mamountp' "$-1.00") @@ -971,7 +1059,7 @@ tests_accountsReport = ], Mixed [nullamt]) - ,"accountsReport with depth:N" ~: do + ,"balanceReport with depth:N" ~: do (defreportopts{query_="depth:1"}, samplejournal) `gives` ([ ("assets", "assets", 0, mamountp' "$-1.00") @@ -981,7 +1069,7 @@ tests_accountsReport = ], Mixed [nullamt]) - ,"accountsReport with a date or secondary date span" ~: do + ,"balanceReport with a date or secondary date span" ~: do (defreportopts{query_="date:'in 2009'"}, samplejournal2) `gives` ([], Mixed [nullamt]) @@ -992,7 +1080,7 @@ tests_accountsReport = ], Mixed [nullamt]) - ,"accountsReport with desc:" ~: do + ,"balanceReport with desc:" ~: do (defreportopts{query_="desc:income"}, samplejournal) `gives` ([ ("assets:bank:checking","assets:bank:checking",0,mamountp' "$1.00") @@ -1000,7 +1088,7 @@ tests_accountsReport = ], Mixed [nullamt]) - ,"accountsReport with not:desc:" ~: do + ,"balanceReport with not:desc:" ~: do (defreportopts{query_="not:desc:income"}, samplejournal) `gives` ([ ("assets","assets",0, mamountp' "$-2.00") @@ -1124,7 +1212,7 @@ tests_accountsReport = ," c:d " ]) >>= either error' return let j' = journalCanonicaliseAmounts $ journalConvertAmountsToCost j -- enable cost basis adjustment - accountsReportAsText defreportopts (accountsReport defreportopts Any j') `is` + balanceReportAsText defreportopts (balanceReport defreportopts Any j') `is` [" $500 a:b" ," $-500 c:d" ,"--------------------" @@ -1169,7 +1257,7 @@ tests_Hledger_Reports = TestList $ ++ tests_summarisePostingsByInterval ++ tests_postingsReport -- ++ tests_isInterestingIndented - ++ tests_accountsReport + ++ tests_balanceReport ++ [ -- ,"summarisePostingsInDateSpan" ~: do -- let gives (b,e,depth,showempty,ps) = diff --git a/hledger-web/Handler/Common.hs b/hledger-web/Handler/Common.hs index 985c77be2..fdd3cb5ca 100644 --- a/hledger-web/Handler/Common.hs +++ b/hledger-web/Handler/Common.hs @@ -48,7 +48,7 @@ $maybe m' <- msg -- | The sidebar used on most views. sidebar :: ViewData -> HtmlUrl AppRoute -sidebar vd@VD{..} = accountsReportAsHtml opts vd $ accountsReport (reportopts_ $ cliopts_ opts){empty_=True} am j +sidebar vd@VD{..} = balanceReportAsHtml opts vd $ balanceReport (reportopts_ $ cliopts_ opts){empty_=True} am j -- -- | Navigation link, preserving parameters and possibly highlighted. -- navlink :: ViewData -> String -> AppRoute -> String -> HtmlUrl AppRoute @@ -285,9 +285,9 @@ nulltemplate = [hamlet||] ---------------------------------------------------------------------- -- hledger report renderers --- | Render an "AccountsReport" as html. -accountsReportAsHtml :: WebOpts -> ViewData -> AccountsReport -> HtmlUrl AppRoute -accountsReportAsHtml _ vd@VD{..} (items',total) = +-- | Render an "BalanceReport" as html. +balanceReportAsHtml :: WebOpts -> ViewData -> BalanceReport -> HtmlUrl AppRoute +balanceReportAsHtml _ vd@VD{..} (items',total) = [hamlet| [+] @@ -329,7 +329,7 @@ accountsReportAsHtml _ vd@VD{..} (items',total) = inacctmatcher = inAccountQuery qopts allaccts = isNothing inacctmatcher items = items' -- maybe items' (\m -> filter (matchesAccount m . \(a,_,_,_)->a) items') showacctmatcher - itemAsHtml :: ViewData -> AccountsReportItem -> HtmlUrl AppRoute + itemAsHtml :: ViewData -> BalanceReportItem -> HtmlUrl AppRoute itemAsHtml _ (acct, adisplay, aindent, abal) = [hamlet| diff --git a/hledger/Hledger/Cli/Balance.hs b/hledger/Hledger/Cli/Balance.hs index 7ef864921..af24425be 100644 --- a/hledger/Hledger/Cli/Balance.hs +++ b/hledger/Hledger/Cli/Balance.hs @@ -1,10 +1,19 @@ {-| -A ledger-compatible @balance@ command. +A ledger-compatible @balance@ command, with additional support for +multi-column reports. -ledger's balance command is easy to use but not easy to describe -precisely. In the examples below we'll use sample.journal, which has the -following account tree: +Here is a description/specification for the balance command. See also +"Hledger.Reports" -> \"Balance reports\". + + +/Basic balance report/ + +With no reporting interval (@--monthly@ etc.), hledger's balance +command emulates ledger's, showing accounts indented according to +hierarchy, along with their total amount posted (including subaccounts). + +Here's an example. With @data/sample.journal@, which defines the following account tree: @ assets @@ -22,10 +31,7 @@ following account tree: debts @ -The balance command shows accounts with their aggregate balances. -Subaccounts are displayed indented below their parent. Each balance is the -sum of any transactions in that account plus any balances from -subaccounts: +the basic @balance@ command gives this output: @ $ hledger -f sample.journal balance @@ -39,16 +45,44 @@ subaccounts: $-1 gifts $-1 salary $1 liabilities:debts +-------------------- + 0 @ -Usually, the non-interesting accounts are elided or omitted. Above, -@checking@ is omitted because it has no subaccounts and a zero balance. -@bank@ is elided because it has only a single displayed subaccount -(@saving@) and it would be showing the same balance as that ($1). Ditto -for @liabilities@. We will return to this in a moment. +Subaccounts are displayed indented below their parent. Only the account leaf name (the final part) is shown. +(With @--flat@, account names are shown in full and unindented.) -The --depth argument can be used to limit the depth of the balance report. -So, to see just the top level accounts: +Each account's \"balance\" is the sum of postings in that account and any subaccounts during the report period. +When the report period includes all transactions, this is equivalent to the account's current balance. + +The overall total of the highest-level displayed accounts is shown below the line. +(The @--no-total/-N@ flag prevents this.) + +/Eliding and omitting/ + +Accounts which have a zero balance, and no non-zero subaccount +balances, are normally omitted from the report. +(The @--empty/-E@ flag forces such accounts to be displayed.) +Eg, above @checking@ is omitted because it has a zero balance and no subaccounts. + +Accounts which have a single subaccount also being displayed, with the same balance, +are normally elided into the subaccount's line. +(The @--no-elide@ flag prevents this.) +Eg, above @bank@ is elided to @bank:saving@ because it has only a +single displayed subaccount (@saving@) and their balance is the same +($1). Similarly, @liabilities@ is elided to @liabilities:debts@. + +/Date limiting/ + +The default report period is that of the whole journal, including all +known transactions. The @--begin\/-b@, @--end\/-e@, @--period\/-p@ +options or @date:@/@date2:@ patterns can be used to report only +on transactions before and/or after specified dates. + +/Depth limiting/ + +The @--depth@ option can be used to limit the depth of the balance report. +Eg, to see just the top level accounts (still including their subaccount balances): @ $ hledger -f sample.journal balance --depth 1 @@ -56,14 +90,15 @@ $ hledger -f sample.journal balance --depth 1 $2 expenses $-2 income $1 liabilities +-------------------- + 0 @ -This time liabilities has no displayed subaccounts (due to --depth) and -is not elided. +/Account limiting/ -With one or more account pattern arguments, the balance command shows -accounts whose name matches one of the patterns, plus their parents -(elided) and subaccounts. So with the pattern o we get: +With one or more account pattern arguments, the report is restricted +to accounts whose name matches one of the patterns, plus their parents +and subaccounts. Eg, adding the pattern @o@ to the first example gives: @ $ hledger -f sample.journal balance o @@ -75,27 +110,134 @@ accounts whose name matches one of the patterns, plus their parents $-1 @ -The o pattern matched @food@ and @income@, so they are shown. Unmatched -parents of matched accounts are also shown (elided) for context (@expenses@). +* The @o@ pattern matched @food@ and @income@, so they are shown. -Also, the balance report shows the total of all displayed accounts, when -that is non-zero. Here, it is displayed because the accounts shown add up -to $-1. +* @food@'s parent (@expenses@) is shown even though the pattern didn't + match it, to clarify the hierarchy. The usual eliding rules cause it to be elided here. -Also, non-interesting accounts may be elided. Here's an imperfect -description of the ledger balance command's eliding behaviour: -\"Interesting\" accounts are displayed on their own line. An account less -deep than the report's max depth, with just one interesting subaccount, -and the same balance as the subaccount, is non-interesting, and prefixed -to the subaccount's line, unless (hledger's) --no-elide is in effect. -An account with a zero inclusive balance and less than two interesting -subaccounts is not displayed at all, unless --empty is in effect. +* @income@'s subaccounts are also shown. + +/Multi-column balance report/ + +hledger's balance command will show multiple columns when a reporting +interval is specified (eg with @--monthly@), one column for each sub-period. + +There are three kinds of multi-column balance report, indicated by the heading: + +* A \"period balance\" (or \"flow\") report (the default) shows the change of account + balance in each period, which is equivalent to the sum of postings in each + period. Here, checking's balance increased by 10 in Feb: + + > Change of balance (flow): + > + > Jan Feb Mar + > assets:checking 20 10 -5 + +* A \"cumulative balance\" report (with @--cumulative@) shows the accumulated ending balance + across periods, starting from zero at the report's start date. + Here, 30 is the sum of checking postings during Jan and Feb: + + > Ending balance (cumulative): + > + > Jan Feb Mar + > assets:checking 20 30 25 + +* A \"historical balance\" report (with @--historical/-H@) also shows ending balances, + but it includes the starting balance from any postings before the report start date. + Here, 130 is the balance from all checking postings at the end of Feb, including + pre-Jan postings which created a starting balance of 100: + + > Ending balance (historical): + > + > Jan Feb Mar + > assets:checking 120 130 125 + +/Eliding and omitting, 2/ + +Here's a (imperfect?) specification for the eliding/omitting behaviour: + +* Each account is normally displayed on its own line. + +* An account less deep than the report's max depth, with just one +interesting subaccount, and the same balance as the subaccount, is +non-interesting, and prefixed to the subaccount's line, unless +@--no-elide@ is in effect. + +* An account with a zero inclusive balance and less than two interesting +subaccounts is not displayed at all, unless @--empty@ is in effect. + +* Multi-column balance reports show full account names with no eliding + (like @--flat@). Accounts (and periods) are omitted as described below. + +/Which accounts to show in balance reports/ + +By default: + +* single-column: accounts with non-zero balance in report period. + (With @--flat@: accounts with non-zero balance and postings.) + +* periodic: accounts with postings and non-zero period balance in any period + +* cumulative: accounts with non-zero cumulative balance in any period + +* historical: accounts with non-zero historical balance in any period + +With @-E/--empty@: + +* single-column: accounts with postings in report period + +* periodic: accounts with postings in report period + +* cumulative: accounts with postings in report period + +* historical: accounts with non-zero starting balance + + accounts with postings in report period + +/Which periods (columns) to show in balance reports/ + +An empty period/column is one where no report account has any postings. +A zero period/column is one where no report account has a non-zero period balance. + +Currently, + +by default: + +* single-column: N/A + +* periodic: all periods within the overall report period, + except for leading and trailing empty periods + +* cumulative: all periods within the overall report period, + except for leading and trailing empty periods + +* historical: all periods within the overall report period, + except for leading and trailing empty periods + +With @-E/--empty@: + +* single-column: N/A + +* periodic: all periods within the overall report period + +* cumulative: all periods within the overall report period + +* historical: all periods within the overall report period + +/What to show in empty cells/ + +An empty periodic balance report cell is one which has no corresponding postings. +An empty cumulative/historical balance report cell is one which has no correponding +or prior postings, ie the account doesn't exist yet. +Currently, empty cells show 0. -} module Hledger.Cli.Balance ( balance - ,accountsReportAsText + ,balanceReportAsText + ,periodBalanceReportAsText + ,cumulativeBalanceReportAsText + ,historicalBalanceReportAsText ,tests_Hledger_Cli_Balance ) where @@ -116,19 +258,24 @@ import Hledger.Cli.Options balance :: CliOpts -> Journal -> IO () balance CliOpts{reportopts_=ropts} j = do d <- getCurrentDay - let lines = case formatFromOpts ropts of - Left err -> [err] - Right _ -> case intervalFromOpts ropts of - NoInterval -> accountsReportAsText ropts $ accountsReport ropts (queryFromOpts d ropts) j - _ -> flowReportAsText ropts $ flowReport ropts (queryFromOpts d ropts) j - putStr $ unlines lines + let output = + case formatFromOpts ropts of + Left err -> [err] + Right _ -> + case (intervalFromOpts ropts, balancetype_ ropts) of + (NoInterval,_) -> balanceReportAsText ropts $ balanceReport ropts (queryFromOpts d ropts) j + (_,PeriodBalance) -> periodBalanceReportAsText ropts $ periodBalanceReport ropts (queryFromOpts d ropts) j + (_,CumulativeBalance) -> cumulativeBalanceReportAsText ropts $ cumulativeOrHistoricalBalanceReport ropts (queryFromOpts d ropts) j + (_,HistoricalBalance) -> historicalBalanceReportAsText ropts $ cumulativeOrHistoricalBalanceReport ropts (queryFromOpts d ropts) j --- | Render an old-style balance report (single-column balance/balance change report) as plain text. -accountsReportAsText :: ReportOpts -> AccountsReport -> [String] -accountsReportAsText opts ((items, total)) = concat lines ++ t + putStr $ unlines output + +-- | Render an old-style single-column balance report as plain text. +balanceReportAsText :: ReportOpts -> BalanceReport -> [String] +balanceReportAsText opts ((items, total)) = concat lines ++ t where lines = case formatFromOpts opts of - Right f -> map (accountsReportItemAsText opts f) items + Right f -> map (balanceReportItemAsText opts f) items Left err -> [[err]] t = if no_total_ opts then [] @@ -137,13 +284,13 @@ accountsReportAsText opts ((items, total)) = concat lines ++ t ,padleft 20 $ showMixedAmountWithoutPrice total ] -tests_accountsReportAsText = [ - "accountsReportAsText" ~: do +tests_balanceReportAsText = [ + "balanceReportAsText" ~: do -- "unicode in balance layout" ~: do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let opts = defreportopts - accountsReportAsText opts (accountsReport opts (queryFromOpts (parsedate "2008/11/26") opts) j) `is` + balanceReportAsText opts (balanceReport opts (queryFromOpts (parsedate "2008/11/26") opts) j) `is` [" -100 актив:наличные" ," 100 расходы:покупки" ,"--------------------" @@ -162,26 +309,26 @@ This implementation turned out to be a bit convoluted but implements the followi b USD -1 ; Account 'b' has two amounts. The account name is printed on the last line. -} -- | Render one balance report line item as plain text suitable for console output. -accountsReportItemAsText :: ReportOpts -> [FormatString] -> AccountsReportItem -> [String] -accountsReportItemAsText opts format (_, accountName, depth, Mixed amounts) = +balanceReportItemAsText :: ReportOpts -> [FormatString] -> BalanceReportItem -> [String] +balanceReportItemAsText opts format (_, accountName, depth, Mixed amounts) = -- 'amounts' could contain several quantities of the same commodity with different price. -- In order to combine them into single value (which is expected) we take the first price and -- use it for the whole mixed amount. This could be suboptimal. XXX let Mixed normAmounts = normaliseMixedAmountPreservingFirstPrice (Mixed amounts) in case normAmounts of [] -> [] - [a] -> [formatAccountsReportItem opts (Just accountName) depth a format] + [a] -> [formatBalanceReportItem opts (Just accountName) depth a format] (as) -> multiline as where multiline :: [Amount] -> [String] multiline [] = [] - multiline [a] = [formatAccountsReportItem opts (Just accountName) depth a format] - multiline (a:as) = (formatAccountsReportItem opts Nothing depth a format) : multiline as + multiline [a] = [formatBalanceReportItem opts (Just accountName) depth a format] + multiline (a:as) = (formatBalanceReportItem opts Nothing depth a format) : multiline as -formatAccountsReportItem :: ReportOpts -> Maybe AccountName -> Int -> Amount -> [FormatString] -> String -formatAccountsReportItem _ _ _ _ [] = "" -formatAccountsReportItem opts accountName depth amount (fmt:fmts) = - s ++ (formatAccountsReportItem opts accountName depth amount fmts) +formatBalanceReportItem :: ReportOpts -> Maybe AccountName -> Int -> Amount -> [FormatString] -> String +formatBalanceReportItem _ _ _ _ [] = "" +formatBalanceReportItem opts accountName depth amount (fmt:fmts) = + s ++ (formatBalanceReportItem opts accountName depth amount fmts) where s = case fmt of FormatLiteral l -> l @@ -196,24 +343,75 @@ formatField opts accountName depth total ljust min max field = case field of TotalField -> formatValue ljust min max $ showAmountWithoutPrice total _ -> "" --- | Render a flow report (multi-column balance change report) as plain text suitable for console output. -flowReportAsText :: ReportOpts -> FlowReport -> [String] -flowReportAsText opts (colspans, items, coltotals) = +-- | Render a multi-column period balance report as plain text suitable for console output. +periodBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> [String] +periodBalanceReportAsText opts (MultiBalanceReport (colspans, items, coltotals)) = + (["Change of balance (flow):"] ++) $ trimborder $ lines $ - render id ((" "++) . showDateSpan) showMixedAmountWithoutPrice $ - Table + render + id + ((" "++) . showDateSpan) + showMixedAmountWithoutPrice + $ Table (Group NoLine $ map (Header . padright acctswidth) accts) (Group NoLine $ map Header colspans) - (map snd items) + (map snd items') +----+ totalrow where trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init) - accts = map fst items + items' | empty_ opts = items + | otherwise = items -- dbg "2" $ filter (any (not . isZeroMixedAmount) . snd) $ dbg "1" items + accts = map renderacct items' + renderacct ((a,a',_i),_) + | flat_ opts = a + | otherwise = a' -- replicate i ' ' ++ acctswidth = maximum $ map length $ accts totalrow | no_total_ opts = row "" [] | otherwise = row "" coltotals +-- | Render a multi-column cumulative balance report as plain text suitable for console output. +cumulativeBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> [String] +cumulativeBalanceReportAsText opts (MultiBalanceReport (colspans, items, coltotals)) = + (["Ending balance (cumulative):"] ++) $ + trimborder $ lines $ + render id ((" "++) . maybe "" (showDate . prevday) . spanEnd) showMixedAmountWithoutPrice $ + addtotalrow $ + Table + (Group NoLine $ map (Header . padright acctswidth) accts) + (Group NoLine $ map Header colspans) + (map snd items) + where + trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init) + accts = map renderacct items + renderacct ((a,a',_),_) + | flat_ opts = a + | otherwise = a' -- replicate i ' ' ++ + acctswidth = maximum $ map length $ accts + addtotalrow | no_total_ opts = id + | otherwise = (+----+ row "" coltotals) + +-- | Render a multi-column historical balance report as plain text suitable for console output. +historicalBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> [String] +historicalBalanceReportAsText opts (MultiBalanceReport (colspans, items, coltotals)) = + (["Ending balance (historical):"] ++) $ + trimborder $ lines $ + render id ((" "++) . maybe "" (showDate . prevday) . spanEnd) showMixedAmountWithoutPrice $ + addtotalrow $ + Table + (Group NoLine $ map (Header . padright acctswidth) accts) + (Group NoLine $ map Header colspans) + (map snd items) + where + trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init) + accts = map renderacct items + renderacct ((a,a',_),_) + | flat_ opts = a + | otherwise = a' -- replicate i ' ' ++ + acctswidth = maximum $ map length $ accts + addtotalrow | no_total_ opts = id + | otherwise = (+----+ row "" coltotals) + tests_Hledger_Cli_Balance = TestList - tests_accountsReportAsText + tests_balanceReportAsText diff --git a/hledger/Hledger/Cli/Balancesheet.hs b/hledger/Hledger/Cli/Balancesheet.hs index 1bb3c688f..4c7a35412 100644 --- a/hledger/Hledger/Cli/Balancesheet.hs +++ b/hledger/Hledger/Cli/Balancesheet.hs @@ -25,15 +25,15 @@ balancesheet CliOpts{reportopts_=ropts} j = do -- let lines = case formatFromOpts ropts of Left err, Right ... d <- getCurrentDay let q = queryFromOpts d (withoutBeginDate ropts) - assetreport@(_,assets) = accountsReport ropts (And [q, journalAssetAccountQuery j]) j - liabilityreport@(_,liabilities) = accountsReport ropts (And [q, journalLiabilityAccountQuery j]) j + assetreport@(_,assets) = balanceReport ropts (And [q, journalAssetAccountQuery j]) j + liabilityreport@(_,liabilities) = balanceReport ropts (And [q, journalLiabilityAccountQuery j]) j total = assets + liabilities LT.putStr $ [lt|Balance Sheet Assets: -#{unlines $ accountsReportAsText ropts assetreport} +#{unlines $ balanceReportAsText ropts assetreport} Liabilities: -#{unlines $ accountsReportAsText ropts liabilityreport} +#{unlines $ balanceReportAsText ropts liabilityreport} Total: -------------------- diff --git a/hledger/Hledger/Cli/Cashflow.hs b/hledger/Hledger/Cli/Cashflow.hs index 1fa1da1df..8930df6bb 100644 --- a/hledger/Hledger/Cli/Cashflow.hs +++ b/hledger/Hledger/Cli/Cashflow.hs @@ -28,15 +28,15 @@ cashflow CliOpts{reportopts_=ropts} j = do -- let lines = case formatFromOpts ropts of Left err, Right ... d <- getCurrentDay let q = queryFromOpts d ropts - cashreport@(_,total) = accountsReport ropts (And [q, journalCashAccountQuery j]) j - -- operatingreport@(_,operating) = accountsReport ropts (And [q, journalOperatingAccountMatcher j]) j - -- investingreport@(_,investing) = accountsReport ropts (And [q, journalInvestingAccountMatcher j]) j - -- financingreport@(_,financing) = accountsReport ropts (And [q, journalFinancingAccountMatcher j]) j + cashreport@(_,total) = balanceReport ropts (And [q, journalCashAccountQuery j]) j + -- operatingreport@(_,operating) = balanceReport ropts (And [q, journalOperatingAccountMatcher j]) j + -- investingreport@(_,investing) = balanceReport ropts (And [q, journalInvestingAccountMatcher j]) j + -- financingreport@(_,financing) = balanceReport ropts (And [q, journalFinancingAccountMatcher j]) j -- total = operating + investing + financing LT.putStr $ [lt|Cashflow Statement Cash flows: -#{unlines $ accountsReportAsText ropts cashreport} +#{unlines $ balanceReportAsText ropts cashreport} Total: -------------------- diff --git a/hledger/Hledger/Cli/Incomestatement.hs b/hledger/Hledger/Cli/Incomestatement.hs index 4c644a4fe..823b602f3 100644 --- a/hledger/Hledger/Cli/Incomestatement.hs +++ b/hledger/Hledger/Cli/Incomestatement.hs @@ -23,15 +23,15 @@ incomestatement :: CliOpts -> Journal -> IO () incomestatement CliOpts{reportopts_=ropts} j = do d <- getCurrentDay let q = queryFromOpts d ropts - incomereport@(_,income) = accountsReport ropts (And [q, journalIncomeAccountQuery j]) j - expensereport@(_,expenses) = accountsReport ropts (And [q, journalExpenseAccountQuery j]) j + incomereport@(_,income) = balanceReport ropts (And [q, journalIncomeAccountQuery j]) j + expensereport@(_,expenses) = balanceReport ropts (And [q, journalExpenseAccountQuery j]) j total = income + expenses LT.putStr $ [lt|Income Statement Revenues: -#{unlines $ accountsReportAsText ropts incomereport} +#{unlines $ balanceReportAsText ropts incomereport} Expenses: -#{unlines $ accountsReportAsText ropts expensereport} +#{unlines $ balanceReportAsText ropts expensereport} Total: -------------------- diff --git a/hledger/Hledger/Cli/Options.hs b/hledger/Hledger/Cli/Options.hs index 1b48ca1ca..745065970 100644 --- a/hledger/Hledger/Cli/Options.hs +++ b/hledger/Hledger/Cli/Options.hs @@ -285,7 +285,9 @@ balancemode = (defCommandMode $ ["balance"] ++ aliases) { modeHelp = "show matched accounts and their balances" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [ - flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show full account names, unindented" + flagNone ["cumulative"] (\opts -> setboolopt "cumulative" opts) "with a reporting interval, show accumulated totals starting from 0" + ,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) "with a reporting interval, show accurate historical ending balances" + ,flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show full account names, unindented" ,flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "with --flat, omit this many leading account name components" ,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format" ,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "no eliding at all, stronger than --empty" @@ -463,6 +465,7 @@ rawOptsToCliOpts rawopts = do ,empty_ = boolopt "empty" rawopts ,no_elide_ = boolopt "no-elide" rawopts ,real_ = boolopt "real" rawopts + ,balancetype_ = balancetypeopt rawopts -- balance ,flat_ = boolopt "flat" rawopts -- balance ,drop_ = intopt "drop" rawopts -- balance ,no_total_ = boolopt "no-total" rawopts -- balance @@ -616,6 +619,16 @@ maybeperiodopt d rawopts = Just $ parsePeriodExpr d s +balancetypeopt :: RawOpts -> BalanceType +balancetypeopt rawopts + | length [o | o <- ["cumulative","historical"], isset o] > 1 + = optserror "please specify at most one of --cumulative and --historical" + | isset "cumulative" = CumulativeBalance + | isset "historical" = HistoricalBalance + | otherwise = PeriodBalance + where + isset = flip boolopt rawopts + -- | Parse the format option if provided, possibly returning an error, -- otherwise get the default value. formatFromOpts :: ReportOpts -> Either String [FormatString] diff --git a/tests/balance-multicol.test b/tests/balance-multicol.test new file mode 100644 index 000000000..6231ff510 --- /dev/null +++ b/tests/balance-multicol.test @@ -0,0 +1,138 @@ +# multi-column balance reports + +# 1. Here are the postings used in most tests below: +hledgerdev -f data/balance-multicol.journal register +>>> +2012/12/31 (assets:checking) 10 10 +2013/01/01 (assets:checking) 1 11 +2013/01/15 (assets:checking) -1 10 +2013/02/01 (assets:cash) 1 11 +2013/02/02 (assets) 1 12 +2013/03/01 (assets:checking) 1 13 +>>>=0 + +# 2. A period balance (flow) report. +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:cash || 0 1 0 + assets:checking || 0 0 1 +-----------------++---------------------------------------------------------------------- + || + +>>>=0 + +# 3. With --empty, includes leading/trailing empty periods +#hledgerdev -f data/balance-multicol.journal balance -p 'quarterly in 2013' --empty +hledgerdev -f - balance -p 'quarterly in 2013' --empty +<<< +2012/12/31 + (a) 10 +2013/1/1 + (a) 1 +2013/3/1 + (a) 1 +>>> +Change of balance (flow): + + || 2013/01/01-2013/03/31 2013/04/01-2013/06/30 2013/07/01-2013/09/30 2013/10/01-2013/12/31 +===++============================================================================================= + a || 2 0 0 0 +---++--------------------------------------------------------------------------------------------- + || 2 0 0 0 + +>>>=0 + +# 4. A cumulative ending balance report. Column totals are the sum of +# the highest-level displayed accounts (here, assets). +hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --cumulative +>>> +Ending balance (cumulative): + + || 2013/01/31 2013/02/28 2013/03/31 +=================++===================================== + assets || 0 2 3 + assets:cash || 0 1 1 + assets:checking || 0 0 1 +-----------------++------------------------------------- + || 0 2 3 + +>>>=0 + +# 5. With the assets:cash account excluded. As with a single-column +# balance --flat report, or ledger's balance --flat, assets' balance +# includes the displayed subaccount and not the excluded one. +hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' --cumulative not:cash +>>> +Ending balance (cumulative): + + || 2013/01/31 2013/02/28 2013/03/31 +=================++===================================== + assets || 0 1 2 + assets:checking || 0 0 1 +-----------------++------------------------------------- + || 0 1 2 + +>>>=0 + +# 6. A historical ending balance report. +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 || 10 12 13 + assets:cash || 0 1 1 + assets:checking || 10 10 11 +-----------------++------------------------------------- + || 10 12 13 + +>>>=0 + +# 7. With top-level accounts excluded. As always, column totals are the sum of +# the highest-level displayed accounts, now assets:cash and assets:checking. +hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' not:assets$ +>>> +Change of balance (flow): + + || 2013/01/01-2013/01/31 2013/02/01-2013/02/28 2013/03/01-2013/03/31 +=================++====================================================================== + assets:cash || 0 1 0 + assets:checking || 0 0 1 +-----------------++---------------------------------------------------------------------- + || 0 1 1 + +>>>=0 + +# 8. cumulative: +hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' not:assets$ --cumulative +>>> +Ending balance (cumulative): + + || 2013/01/31 2013/02/28 2013/03/31 +=================++===================================== + assets:cash || 0 1 1 + assets:checking || 0 0 1 +-----------------++------------------------------------- + || 0 1 2 + +>>>=0 + +# 9. historical +hledgerdev -f data/balance-multicol.journal balance -p 'monthly in 2013' not:assets$ --historical +>>> +Ending balance (historical): + + || 2013/01/31 2013/02/28 2013/03/31 +=================++===================================== + assets:cash || 0 1 1 + assets:checking || 10 10 11 +-----------------++------------------------------------- + || 10 11 12 + +>>>=0