File: Balance.hs

package info (click to toggle)
haskell-hledger 0.23.3-1
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 272 kB
  • ctags: 1
  • sloc: haskell: 1,816; makefile: 5
file content (440 lines) | stat: -rw-r--r-- 17,097 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
{-|

A ledger-compatible @balance@ command, with additional support for
multi-column reports.

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
   bank
     checking
     saving
   cash
 expenses
   food
   supplies
 income
   gifts
   salary
 liabilities
   debts
@

the basic @balance@ command gives this output:

@
 $ hledger -f sample.journal balance
                 $-1  assets
                  $1    bank:saving
                 $-2    cash
                  $2  expenses
                  $1    food
                  $1    supplies
                 $-2  income
                 $-1    gifts
                 $-1    salary
                  $1  liabilities:debts
--------------------
                   0
@

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.)

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
                 $-1  assets
                  $2  expenses
                 $-2  income
                  $1  liabilities
--------------------
                   0
@

/Account limiting/

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
                  $1  expenses:food
                 $-2  income
                 $-1    gifts
                 $-1    salary
--------------------
                 $-1
@

* The @o@ pattern matched @food@ and @income@, so they are shown.

* @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.

* @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 (
  balancemode
 ,balance
 ,balanceReportAsText
 ,periodBalanceReportAsText
 ,cumulativeBalanceReportAsText
 ,historicalBalanceReportAsText
 ,tests_Hledger_Cli_Balance
) where

import Data.List
import Data.Maybe
-- import System.Console.CmdArgs
import System.Console.CmdArgs.Explicit as C
-- import System.Console.CmdArgs.Text
import Test.HUnit
import Text.Tabular as T
import Text.Tabular.AsciiArt

import Hledger
import Prelude hiding (putStr)
import Hledger.Utils.UTF8IOCompat (putStr)
import Hledger.Data.OutputFormat
import Hledger.Cli.Options


-- | Command line options for this command.
balancemode = (defCommandMode $ ["balance"] ++ aliases) { -- also accept but don't show the common bal alias
  modeHelp = "show accounts and balances" `withAliases` aliases
 ,modeGroupFlags = C.Group {
     groupUnnamed = [
      flagNone ["tree"] (\opts -> setboolopt "tree" opts) "show accounts as a tree (default in simple reports)"
     ,flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show accounts as a list (default in multicolumn)"
     ,flagReq  ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts"
     ,flagReq  ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "tree mode: use this custom line format"
     ,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "tree mode: don't squash boring parent accounts"
     ,flagNone ["no-total"] (\opts -> setboolopt "no-total" opts) "don't show the final total"
     ,flagNone ["cumulative"] (\opts -> setboolopt "cumulative" opts) "multicolumn mode: show accumulated ending balances"
     ,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) "multicolumn mode: show historical ending balances"
     ]
    ,groupHidden = []
    ,groupNamed = [generalflagsgroup1]
    }
 }
  where aliases = ["bal"]

-- | The balance command, prints a balance report.
balance :: CliOpts -> Journal -> IO ()
balance CliOpts{reportopts_=ropts} j = do
  d <- getCurrentDay
  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 $ multiBalanceReport ropts (queryFromOpts d ropts) j
            (_,CumulativeBalance) -> cumulativeBalanceReportAsText ropts $ multiBalanceReport ropts (queryFromOpts d ropts) j
            (_,HistoricalBalance) -> historicalBalanceReportAsText ropts $ multiBalanceReport ropts (queryFromOpts d ropts) j
  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 (balanceReportItemAsText opts f) items
                Left err -> [[err]]
      t = if no_total_ opts
           then []
           else ["--------------------"
                 -- TODO: This must use the format somehow
                ,padleft 20 $ showMixedAmountWithoutPrice total
                ]

tests_balanceReportAsText = [
  "balanceReportAsText" ~: do
  -- "unicode in balance layout" ~: do
    j <- readJournal'
      "2009/01/01 * медвежья шкура\n  расходы:покупки  100\n  актив:наличные\n"
    let opts = defreportopts
    balanceReportAsText opts (balanceReport opts (queryFromOpts (parsedate "2008/11/26") opts) j) `is`
      ["                -100  актив:наличные"
      ,"                 100  расходы:покупки"
      ,"--------------------"
      ,"                   0"
      ]
 ]

{-
This implementation turned out to be a bit convoluted but implements the following algorithm for formatting:

- If there is a single amount, print it with the account name directly:
- Otherwise, only print the account name on the last line.

    a         USD 1   ; Account 'a' has a single amount
              EUR -1
    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.
balanceReportItemAsText :: ReportOpts -> [OutputFormat] -> 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] -> [formatBalanceReportItem opts (Just accountName) depth a format]
      (as) -> multiline as
    where
      multiline :: [Amount] -> [String]
      multiline []     = []
      multiline [a]    = [formatBalanceReportItem opts (Just accountName) depth a format]
      multiline (a:as) = (formatBalanceReportItem opts Nothing depth a format) : multiline as

formatBalanceReportItem :: ReportOpts -> Maybe AccountName -> Int -> Amount -> [OutputFormat] -> String
formatBalanceReportItem _ _ _ _ [] = ""
formatBalanceReportItem opts accountName depth amount (fmt:fmts) =
  s ++ (formatBalanceReportItem opts accountName depth amount fmts)
  where
    s = case fmt of
         FormatLiteral l -> l
         FormatField ljust min max field  -> formatField opts accountName depth amount ljust min max field

formatField :: ReportOpts -> Maybe AccountName -> Int -> Amount -> Bool -> Maybe Int -> Maybe Int -> HledgerFormatField -> String
formatField opts accountName depth total ljust min max field = case field of
        AccountField     -> formatValue ljust min max $ maybe "" (accountNameDrop (drop_ opts)) accountName
        DepthSpacerField -> case min of
                               Just m  -> formatValue ljust Nothing max $ replicate (depth * m) ' '
                               Nothing -> formatValue ljust Nothing max $ replicate depth ' '
        TotalField       -> formatValue ljust min max $ showAmountWithoutPrice total
        _                  -> ""

-- | 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
      (T.Group NoLine $ map (Header . padright acctswidth) accts)
      (T.Group NoLine $ map Header colspans)
      (map snd items')
    +----+
    totalrow
  where
    trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init)
    items' | empty_ opts = items
           | otherwise   = items -- dbg "2" $ filter (any (not . isZeroMixedAmount) . snd) $ dbg "1" items
    accts = map renderacct items'
    renderacct ((a,a',i),_)
      | tree_ opts = replicate ((i-1)*2) ' ' ++ a'
      | otherwise  = accountNameDrop (drop_ opts) a
    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
       (T.Group NoLine $ map (Header . padright acctswidth) accts)
       (T.Group NoLine $ map Header colspans)
       (map snd items)
  where
    trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init)
    accts = map renderacct items
    renderacct ((a,a',i),_)
      | tree_ opts = replicate ((i-1)*2) ' ' ++ a'
      | otherwise  = accountNameDrop (drop_ opts) a
    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
       (T.Group NoLine $ map (Header . padright acctswidth) accts)
       (T.Group NoLine $ map Header colspans)
       (map snd items)
  where
    trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init)
    accts = map renderacct items
    renderacct ((a,a',i),_)
      | tree_ opts = replicate ((i-1)*2) ' ' ++ a'
      | otherwise  = accountNameDrop (drop_ opts) a
    acctswidth = maximum $ map length $ accts
    addtotalrow | no_total_ opts = id
                | otherwise      = (+----+ row "" coltotals)


tests_Hledger_Cli_Balance = TestList
  tests_balanceReportAsText