1{-|
2
3Postings report, used by the register command.
4
5-}
6
7{-# LANGUAGE FlexibleInstances #-}
8{-# LANGUAGE OverloadedStrings #-}
9{-# LANGUAGE RecordWildCards #-}
10{-# LANGUAGE ScopedTypeVariables #-}
11{-# LANGUAGE TupleSections #-}
12
13module Hledger.Reports.PostingsReport (
14  PostingsReport,
15  PostingsReportItem,
16  postingsReport,
17  mkpostingsReportItem,
18
19  -- * Tests
20  tests_PostingsReport
21)
22where
23
24import Data.List
25import Data.List.Extra (nubSort)
26import Data.Maybe
27-- import Data.Text (Text)
28import qualified Data.Text as T
29import Data.Time.Calendar
30import Safe (headMay, lastMay)
31
32import Hledger.Data
33import Hledger.Query
34import Hledger.Utils
35import Hledger.Reports.ReportOptions
36
37
38-- | A postings report is a list of postings with a running total, a label
39-- for the total field, and a little extra transaction info to help with rendering.
40-- This is used eg for the register command.
41type PostingsReport = (String               -- label for the running balance column XXX remove
42                      ,[PostingsReportItem] -- line items, one per posting
43                      )
44type PostingsReportItem = (Maybe Day    -- The posting date, if this is the first posting in a
45                                        -- transaction or if it's different from the previous
46                                        -- posting's date. Or if this a summary posting, the
47                                        -- report interval's start date if this is the first
48                                        -- summary posting in the interval.
49                          ,Maybe Day    -- If this is a summary posting, the report interval's
50                                        -- end date if this is the first summary posting in
51                                        -- the interval.
52                          ,Maybe String -- The posting's transaction's description, if this is the first posting in the transaction.
53                          ,Posting      -- The posting, possibly with the account name depth-clipped.
54                          ,MixedAmount  -- The running total after this posting, or with --average,
55                                        -- the running average posting amount. With --historical,
56                                        -- postings before the report start date are included in
57                                        -- the running total/average.
58                          )
59
60-- | A summary posting summarises the activity in one account within a report
61-- interval. It is kludgily represented by a regular Posting with no description,
62-- the interval's start date stored as the posting date, and the interval's end
63-- date attached with a tuple.
64type SummaryPosting = (Posting, Day)
65
66-- | Select postings from the journal and add running balance and other
67-- information to make a postings report. Used by eg hledger's register command.
68postingsReport :: ReportOpts -> Query -> Journal -> PostingsReport
69postingsReport ropts@ReportOpts{..} q j =
70  (totallabel, items)
71    where
72      reportspan  = adjustReportDates ropts q j
73      whichdate   = whichDateFromOpts ropts
74      mdepth      = queryDepth q
75      styles      = journalCommodityStyles j
76      priceoracle = journalPriceOracle infer_value_ j
77      multiperiod = interval_ /= NoInterval
78      today       = fromMaybe (error' "postingsReport: could not pick a valuation date, ReportOpts today_ is unset") today_  -- PARTIAL:
79
80      -- postings to be included in the report, and similarly-matched postings before the report start date
81      (precedingps, reportps) = matchedPostingsBeforeAndDuring ropts q j reportspan
82
83      -- Postings, or summary postings with their subperiod's end date, to be displayed.
84      displayps :: [(Posting, Maybe Day)]
85        | multiperiod =
86            let summaryps = summarisePostingsByInterval interval_ whichdate mdepth showempty reportspan reportps
87            in [(pvalue p lastday, Just periodend) | (p, periodend) <- summaryps, let lastday = addDays (-1) periodend]
88        | otherwise =
89            [(pvalue p reportorjournallast, Nothing) | p <- reportps]
90        where
91          showempty = empty_ || average_
92          -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports".
93          pvalue p periodlast = maybe p (postingApplyValuation priceoracle styles periodlast mreportlast today multiperiod p) value_
94            where
95              mreportlast = reportPeriodLastDay ropts
96          reportorjournallast =
97            fromMaybe (error' "postingsReport: expected a non-empty journal") $  -- PARTIAL: shouldn't happen
98            reportPeriodOrJournalLastDay ropts j
99
100      -- Posting report items ready for display.
101      items =
102        dbg4 "postingsReport items" $
103        postingsReportItems displayps (nullposting,Nothing) whichdate mdepth startbal runningcalc startnum
104        where
105          -- In historical mode we'll need a starting balance, which we
106          -- may be converting to value per hledger_options.m4.md "Effect
107          -- of --value on reports".
108          -- XXX balance report doesn't value starting balance.. should this ?
109          historical = balancetype_ == HistoricalBalance
110          startbal | average_  = if historical then bvalue precedingavg else 0
111                   | otherwise = if historical then bvalue precedingsum else 0
112            where
113              precedingsum = sumPostings precedingps
114              precedingavg | null precedingps = 0
115                           | otherwise        = divideMixedAmount (fromIntegral $ length precedingps) precedingsum
116              bvalue = maybe id (mixedAmountApplyValuation priceoracle styles daybeforereportstart Nothing today multiperiod) value_
117                  -- XXX constrain valuation type to AtDate daybeforereportstart here ?
118                where
119                  daybeforereportstart =
120                    maybe (error' "postingsReport: expected a non-empty journal")  -- PARTIAL: shouldn't happen
121                    (addDays (-1))
122                    $ reportPeriodOrJournalStart ropts j
123
124          runningcalc = registerRunningCalculationFn ropts
125          startnum = if historical then length precedingps + 1 else 1
126
127-- | Based on the given report options, return a function that does the appropriate
128-- running calculation for the register report, ie a running average or running total.
129-- This function will take the item number, previous average/total, and new posting amount,
130-- and return the new average/total.
131registerRunningCalculationFn :: ReportOpts -> (Int -> MixedAmount -> MixedAmount -> MixedAmount)
132registerRunningCalculationFn ropts
133  | average_ ropts = \i avg amt -> avg + divideMixedAmount (fromIntegral i) (amt - avg)
134  | otherwise      = \_ bal amt -> bal + amt
135
136totallabel = "Total"
137
138-- | Adjust report start/end dates to more useful ones based on
139-- journal data and report intervals. Ie:
140-- 1. If the start date is unspecified, use the earliest date in the journal (if any)
141-- 2. If the end date is unspecified, use the latest date in the journal (if any)
142-- 3. If a report interval is specified, enlarge the dates to enclose whole intervals
143adjustReportDates :: ReportOpts -> Query -> Journal -> DateSpan
144adjustReportDates opts q j = reportspan
145  where
146    -- see also multiBalanceReport
147    requestedspan       = dbg3 "requestedspan"       $ queryDateSpan' q                                       -- span specified by -b/-e/-p options and query args
148    journalspan         = dbg3 "journalspan"         $ dates `spanUnion` date2s                               -- earliest and latest dates (or date2s) in the journal
149      where
150        dates  = journalDateSpan False j
151        date2s = journalDateSpan True  j
152    requestedspanclosed = dbg3 "requestedspanclosed" $ requestedspan `spanDefaultsFrom` journalspan           -- if open-ended, close it using the journal's dates (if any)
153    intervalspans       = dbg3 "intervalspans"       $ splitSpan (interval_ opts) requestedspanclosed  -- get the whole intervals enclosing that
154    mreportstart        = dbg3 "reportstart"         $ maybe Nothing spanStart $ headMay intervalspans        -- start of the first interval, or open ended
155    mreportend          = dbg3 "reportend"           $ maybe Nothing spanEnd   $ lastMay intervalspans        -- end of the last interval, or open ended
156    reportspan          = dbg3 "reportspan"          $ DateSpan mreportstart mreportend                       -- the requested span enlarged to whole intervals if possible
157
158-- | Find postings matching a given query, within a given date span,
159-- and also any similarly-matched postings before that date span.
160-- Date restrictions and depth restrictions in the query are ignored.
161-- A helper for the postings report.
162matchedPostingsBeforeAndDuring :: ReportOpts -> Query -> Journal -> DateSpan -> ([Posting],[Posting])
163matchedPostingsBeforeAndDuring opts q j (DateSpan mstart mend) =
164  dbg5 "beforeps, duringps" $ span (beforestartq `matchesPosting`) beforeandduringps
165  where
166    beforestartq = dbg3 "beforestartq" $ dateqtype $ DateSpan Nothing mstart
167    beforeandduringps =
168      dbg5 "ps5" $ sortOn sortdate $                                           -- sort postings by date or date2
169      dbg5 "ps4" $ (if invert_ opts then map negatePostingAmount else id) $    -- with --invert, invert amounts
170      dbg5 "ps3" $ map (filterPostingAmount symq) $                            -- remove amount parts which the query's cur: terms would exclude
171      dbg5 "ps2" $ (if related_ opts then concatMap relatedPostings else id) $ -- with -r, replace each with its sibling postings
172      dbg5 "ps1" $ filter (beforeandduringq `matchesPosting`) $                -- filter postings by the query, with no start date or depth limit
173                  journalPostings $
174                  journalSelectingAmountFromOpts opts j    -- maybe convert to cost early, will be seen by amt:. XXX what about converting to value ?
175      where
176        beforeandduringq = dbg4 "beforeandduringq" $ And [depthless $ dateless q, beforeendq]
177          where
178            depthless  = filterQuery (not . queryIsDepth)
179            dateless   = filterQuery (not . queryIsDateOrDate2)
180            beforeendq = dateqtype $ DateSpan Nothing mend
181        sortdate = if date2_ opts then postingDate2 else postingDate
182        symq = dbg4 "symq" $ filterQuery queryIsSym q
183    dateqtype
184      | queryIsDate2 dateq || (queryIsDate dateq && date2_ opts) = Date2
185      | otherwise = Date
186      where
187        dateq = dbg4 "dateq" $ filterQuery queryIsDateOrDate2 $ dbg4 "q" q  -- XXX confused by multiple date:/date2: ?
188
189-- | Generate postings report line items from a list of postings or (with
190-- non-Nothing dates attached) summary postings.
191postingsReportItems :: [(Posting,Maybe Day)] -> (Posting,Maybe Day) -> WhichDate -> Maybe Int -> MixedAmount -> (Int -> MixedAmount -> MixedAmount -> MixedAmount) -> Int -> [PostingsReportItem]
192postingsReportItems [] _ _ _ _ _ _ = []
193postingsReportItems ((p,menddate):ps) (pprev,menddateprev) wd d b runningcalcfn itemnum =
194    i:(postingsReportItems ps (p,menddate) wd d b' runningcalcfn (itemnum+1))
195  where
196    i = mkpostingsReportItem showdate showdesc wd menddate p' b'
197    (showdate, showdesc) | isJust menddate = (menddate /= menddateprev,        False)
198                         | otherwise       = (isfirstintxn || isdifferentdate, isfirstintxn)
199    isfirstintxn = ptransaction p /= ptransaction pprev
200    isdifferentdate = case wd of PrimaryDate   -> postingDate p  /= postingDate pprev
201                                 SecondaryDate -> postingDate2 p /= postingDate2 pprev
202    p' = p{paccount= clipOrEllipsifyAccountName d $ paccount p}
203    b' = runningcalcfn itemnum b (pamount p)
204
205-- | Generate one postings report line item, containing the posting,
206-- the current running balance, and optionally the posting date and/or
207-- the transaction description.
208mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Day -> Posting -> MixedAmount -> PostingsReportItem
209mkpostingsReportItem showdate showdesc wd menddate p b =
210  (if showdate then Just date else Nothing
211  ,menddate
212  ,if showdesc then Just desc else Nothing
213  ,p
214  ,b
215  )
216  where
217    date = case wd of PrimaryDate   -> postingDate p
218                      SecondaryDate -> postingDate2 p
219    desc = T.unpack $ maybe "" tdescription $ ptransaction p
220
221-- | Convert a list of postings into summary postings, one per interval,
222-- aggregated to the specified depth if any.
223-- Each summary posting will have a non-Nothing interval end date.
224summarisePostingsByInterval :: Interval -> WhichDate -> Maybe Int -> Bool -> DateSpan -> [Posting] -> [SummaryPosting]
225summarisePostingsByInterval interval wd mdepth showempty reportspan ps = concatMap summarisespan $ splitSpan interval reportspan
226  where
227    summarisespan s = summarisePostingsInDateSpan s wd mdepth showempty (postingsinspan s)
228    postingsinspan s = filter (isPostingInDateSpan' wd s) ps
229
230-- | Given a date span (representing a report interval) and a list of
231-- postings within it, aggregate the postings into one summary posting per
232-- account. Each summary posting will have a non-Nothing interval end date.
233--
234-- When a depth argument is present, postings to accounts of greater
235-- depth are also aggregated where possible. If the depth is 0, all
236-- postings in the span are aggregated into a single posting with
237-- account name "...".
238--
239-- The showempty flag includes spans with no postings and also postings
240-- with 0 amount.
241--
242summarisePostingsInDateSpan :: DateSpan -> WhichDate -> Maybe Int -> Bool -> [Posting] -> [SummaryPosting]
243summarisePostingsInDateSpan (DateSpan b e) wd mdepth showempty ps
244  | null ps && (isNothing b || isNothing e) = []
245  | null ps && showempty = [(summaryp, e')]
246  | otherwise = summarypes
247  where
248    postingdate = if wd == PrimaryDate then postingDate else postingDate2
249    b' = fromMaybe (maybe nulldate postingdate $ headMay ps) b
250    e' = fromMaybe (maybe (addDays 1 nulldate) postingdate $ lastMay ps) e
251    summaryp = nullposting{pdate=Just b'}
252    clippedanames = nub $ map (clipAccountName mdepth) anames
253    summaryps | mdepth == Just 0 = [summaryp{paccount="...",pamount=sum $ map pamount ps}]
254              | otherwise        = [summaryp{paccount=a,pamount=balance a} | a <- clippedanames]
255    summarypes = map (, e') $ (if showempty then id else filter (not . mixedAmountLooksZero . pamount)) summaryps
256    anames = nubSort $ map paccount ps
257    -- aggregate balances by account, like ledgerFromJournal, then do depth-clipping
258    accts = accountsFromPostings ps
259    balance a = maybe nullmixedamt bal $ lookupAccount a accts
260      where
261        bal = if isclipped a then aibalance else aebalance
262        isclipped a = maybe True (accountNameLevel a >=) mdepth
263
264negatePostingAmount :: Posting -> Posting
265negatePostingAmount p = p { pamount = negate $ pamount p }
266
267
268-- tests
269
270tests_PostingsReport = tests "PostingsReport" [
271
272   test "postingsReport" $ do
273    let (query, journal) `gives` n = (length $ snd $ postingsReport defreportopts query journal) @?= n
274    -- with the query specified explicitly
275    (Any, nulljournal) `gives` 0
276    (Any, samplejournal) `gives` 13
277    -- register --depth just clips account names
278    (Depth 2, samplejournal) `gives` 13
279    (And [Depth 1, StatusQ Cleared, Acct (toRegex' "expenses")], samplejournal) `gives` 2
280    (And [And [Depth 1, StatusQ Cleared], Acct (toRegex' "expenses")], samplejournal) `gives` 2
281    -- with query and/or command-line options
282    (length $ snd $ postingsReport defreportopts Any samplejournal) @?= 13
283    (length $ snd $ postingsReport defreportopts{interval_=Months 1} Any samplejournal) @?= 11
284    (length $ snd $ postingsReport defreportopts{interval_=Months 1, empty_=True} Any samplejournal) @?= 20
285    (length $ snd $ postingsReport defreportopts (Acct (toRegex' "assets:bank:checking")) samplejournal) @?= 5
286
287     -- (defreportopts, And [Acct "a a", Acct "'b"], samplejournal2) `gives` 0
288     -- [(Just (fromGregorian 2008 01 01,"income"),assets:bank:checking             $1,$1)
289     -- ,(Nothing,income:salary                   $-1,0)
290     -- ,(Just (2008-06-01,"gift"),assets:bank:checking             $1,$1)
291     -- ,(Nothing,income:gifts                    $-1,0)
292     -- ,(Just (2008-06-02,"save"),assets:bank:saving               $1,$1)
293     -- ,(Nothing,assets:bank:checking            $-1,0)
294     -- ,(Just (2008-06-03,"eat & shop"),expenses:food                    $1,$1)
295     -- ,(Nothing,expenses:supplies                $1,$2)
296     -- ,(Nothing,assets:cash                     $-2,0)
297     -- ,(Just (2008-12-31,"pay off"),liabilities:debts                $1,$1)
298     -- ,(Nothing,assets:bank:checking            $-1,0)
299
300    {-
301        let opts = defreportopts
302        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
303         ["2008/01/01 income               assets:bank:checking             $1           $1"
304         ,"                                income:salary                   $-1            0"
305         ,"2008/06/01 gift                 assets:bank:checking             $1           $1"
306         ,"                                income:gifts                    $-1            0"
307         ,"2008/06/02 save                 assets:bank:saving               $1           $1"
308         ,"                                assets:bank:checking            $-1            0"
309         ,"2008/06/03 eat & shop           expenses:food                    $1           $1"
310         ,"                                expenses:supplies                $1           $2"
311         ,"                                assets:cash                     $-2            0"
312         ,"2008/12/31 pay off              liabilities:debts                $1           $1"
313         ,"                                assets:bank:checking            $-1            0"
314         ]
315
316      ,"postings report with cleared option" ~:
317       do
318        let opts = defreportopts{cleared_=True}
319        j <- readJournal' sample_journal_str
320        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
321         ["2008/06/03 eat & shop           expenses:food                    $1           $1"
322         ,"                                expenses:supplies                $1           $2"
323         ,"                                assets:cash                     $-2            0"
324         ,"2008/12/31 pay off              liabilities:debts                $1           $1"
325         ,"                                assets:bank:checking            $-1            0"
326         ]
327
328      ,"postings report with uncleared option" ~:
329       do
330        let opts = defreportopts{uncleared_=True}
331        j <- readJournal' sample_journal_str
332        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
333         ["2008/01/01 income               assets:bank:checking             $1           $1"
334         ,"                                income:salary                   $-1            0"
335         ,"2008/06/01 gift                 assets:bank:checking             $1           $1"
336         ,"                                income:gifts                    $-1            0"
337         ,"2008/06/02 save                 assets:bank:saving               $1           $1"
338         ,"                                assets:bank:checking            $-1            0"
339         ]
340
341      ,"postings report sorts by date" ~:
342       do
343        j <- readJournal' $ unlines
344            ["2008/02/02 a"
345            ,"  b  1"
346            ,"  c"
347            ,""
348            ,"2008/01/01 d"
349            ,"  e  1"
350            ,"  f"
351            ]
352        let opts = defreportopts
353        registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/02/02"]
354
355      ,"postings report with account pattern" ~:
356       do
357        j <- samplejournal
358        let opts = defreportopts{patterns_=["cash"]}
359        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
360         ["2008/06/03 eat & shop           assets:cash                     $-2          $-2"
361         ]
362
363      ,"postings report with account pattern, case insensitive" ~:
364       do
365        j <- samplejournal
366        let opts = defreportopts{patterns_=["cAsH"]}
367        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
368         ["2008/06/03 eat & shop           assets:cash                     $-2          $-2"
369         ]
370
371      ,"postings report with display expression" ~:
372       do
373        j <- samplejournal
374        let gives displayexpr =
375                (registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is`)
376                    where opts = defreportopts
377        "d<[2008/6/2]"  `gives` ["2008/01/01","2008/06/01"]
378        "d<=[2008/6/2]" `gives` ["2008/01/01","2008/06/01","2008/06/02"]
379        "d=[2008/6/2]"  `gives` ["2008/06/02"]
380        "d>=[2008/6/2]" `gives` ["2008/06/02","2008/06/03","2008/12/31"]
381        "d>[2008/6/2]"  `gives` ["2008/06/03","2008/12/31"]
382
383      ,"postings report with period expression" ~:
384       do
385        j <- samplejournal
386        let periodexpr `gives` dates = do
387              j' <- samplejournal
388              registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j') `is` dates
389                  where opts = defreportopts{period_=maybePeriod date1 periodexpr}
390        ""     `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
391        "2008" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
392        "2007" `gives` []
393        "june" `gives` ["2008/06/01","2008/06/02","2008/06/03"]
394        "monthly" `gives` ["2008/01/01","2008/06/01","2008/12/01"]
395        "quarterly" `gives` ["2008/01/01","2008/04/01","2008/10/01"]
396        let opts = defreportopts{period_=maybePeriod date1 "yearly"}
397        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
398         ["2008/01/01 - 2008/12/31         assets:bank:saving               $1           $1"
399         ,"                                assets:cash                     $-2          $-1"
400         ,"                                expenses:food                    $1            0"
401         ,"                                expenses:supplies                $1           $1"
402         ,"                                income:gifts                    $-1            0"
403         ,"                                income:salary                   $-1          $-1"
404         ,"                                liabilities:debts                $1            0"
405         ]
406        let opts = defreportopts{period_=maybePeriod date1 "quarterly"}
407        registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/04/01","2008/10/01"]
408        let opts = defreportopts{period_=maybePeriod date1 "quarterly",empty_=True}
409        registerdates (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` ["2008/01/01","2008/04/01","2008/07/01","2008/10/01"]
410
411      ]
412
413      , "postings report with depth arg" ~:
414       do
415        j <- samplejournal
416        let opts = defreportopts{depth_=Just 2}
417        (postingsReportAsText opts $ postingsReport opts (queryFromOpts date1 opts) j) `is` unlines
418         ["2008/01/01 income               assets:bank                      $1           $1"
419         ,"                                income:salary                   $-1            0"
420         ,"2008/06/01 gift                 assets:bank                      $1           $1"
421         ,"                                income:gifts                    $-1            0"
422         ,"2008/06/02 save                 assets:bank                      $1           $1"
423         ,"                                assets:bank                     $-1            0"
424         ,"2008/06/03 eat & shop           expenses:food                    $1           $1"
425         ,"                                expenses:supplies                $1           $2"
426         ,"                                assets:cash                     $-2            0"
427         ,"2008/12/31 pay off              liabilities:debts                $1           $1"
428         ,"                                assets:bank                     $-1            0"
429         ]
430
431    -}
432
433  ,test "summarisePostingsByInterval" $
434    summarisePostingsByInterval (Quarters 1) PrimaryDate Nothing False (DateSpan Nothing Nothing) [] @?= []
435
436  -- ,tests_summarisePostingsInDateSpan = [
437    --  "summarisePostingsInDateSpan" ~: do
438    --   let gives (b,e,depth,showempty,ps) =
439    --           (summarisePostingsInDateSpan (DateSpan b e) depth showempty ps `is`)
440    --   let ps =
441    --           [
442    --            nullposting{lpdescription="desc",lpaccount="expenses:food:groceries",lpamount=Mixed [usd 1]}
443    --           ,nullposting{lpdescription="desc",lpaccount="expenses:food:dining",   lpamount=Mixed [usd 2]}
444    --           ,nullposting{lpdescription="desc",lpaccount="expenses:food",          lpamount=Mixed [usd 4]}
445    --           ,nullposting{lpdescription="desc",lpaccount="expenses:food:dining",   lpamount=Mixed [usd 8]}
446    --           ]
447    --   ("2008/01/01","2009/01/01",0,9999,False,[]) `gives`
448    --    []
449    --   ("2008/01/01","2009/01/01",0,9999,True,[]) `gives`
450    --    [
451    --     nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31"}
452    --    ]
453    --   ("2008/01/01","2009/01/01",0,9999,False,ts) `gives`
454    --    [
455    --     nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31",lpaccount="expenses:food",          lpamount=Mixed [usd 4]}
456    --    ,nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31",lpaccount="expenses:food:dining",   lpamount=Mixed [usd 10]}
457    --    ,nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31",lpaccount="expenses:food:groceries",lpamount=Mixed [usd 1]}
458    --    ]
459    --   ("2008/01/01","2009/01/01",0,2,False,ts) `gives`
460    --    [
461    --     nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31",lpaccount="expenses:food",lpamount=Mixed [usd 15]}
462    --    ]
463    --   ("2008/01/01","2009/01/01",0,1,False,ts) `gives`
464    --    [
465    --     nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31",lpaccount="expenses",lpamount=Mixed [usd 15]}
466    --    ]
467    --   ("2008/01/01","2009/01/01",0,0,False,ts) `gives`
468    --    [
469    --     nullposting{lpdate=fromGregorian 2008 01 01,lpdescription="- 2008/12/31",lpaccount="",lpamount=Mixed [usd 15]}
470    --    ]
471
472 ]
473