fix!: register: Tighten up spacing around the date in register reports. (#1655)
As a side effect, this changes the Json representation of the PostingsReport. The maybe report end date is now replaced with a maybe period.
This commit is contained in:
		
							parent
							
								
									4b654fff94
								
							
						
					
					
						commit
						06312c353a
					
				@ -121,6 +121,7 @@ instance ToJSON PeriodicTransaction
 | 
			
		||||
instance ToJSON PriceDirective
 | 
			
		||||
instance ToJSON DateSpan
 | 
			
		||||
instance ToJSON Interval
 | 
			
		||||
instance ToJSON Period
 | 
			
		||||
instance ToJSON AccountAlias
 | 
			
		||||
instance ToJSON AccountType
 | 
			
		||||
instance ToJSONKey AccountType
 | 
			
		||||
@ -225,6 +226,7 @@ instance FromJSON (DecimalRaw Integer)
 | 
			
		||||
-- instance FromJSON Commodity
 | 
			
		||||
-- instance FromJSON DateSpan
 | 
			
		||||
-- instance FromJSON Interval
 | 
			
		||||
-- instance FromJSON Period
 | 
			
		||||
-- instance FromJSON PeriodicTransaction
 | 
			
		||||
-- instance FromJSON PriceDirective
 | 
			
		||||
-- instance FromJSON TimeclockCode
 | 
			
		||||
 | 
			
		||||
@ -13,6 +13,7 @@ module Hledger.Data.Period (
 | 
			
		||||
  ,simplifyPeriod
 | 
			
		||||
  ,isLastDayOfMonth
 | 
			
		||||
  ,isStandardPeriod
 | 
			
		||||
  ,periodTextWidth
 | 
			
		||||
  ,showPeriod
 | 
			
		||||
  ,showPeriodMonthAbbrev
 | 
			
		||||
  ,periodStart
 | 
			
		||||
@ -155,6 +156,20 @@ isStandardPeriod = isStandardPeriod' . simplifyPeriod
 | 
			
		||||
    isStandardPeriod' (YearPeriod _) = True
 | 
			
		||||
    isStandardPeriod' _ = False
 | 
			
		||||
 | 
			
		||||
-- | The width of a period of this type when displayed.
 | 
			
		||||
periodTextWidth :: Period -> Int
 | 
			
		||||
periodTextWidth = periodTextWidth' . simplifyPeriod
 | 
			
		||||
  where
 | 
			
		||||
    periodTextWidth' DayPeriod{}     = 10  -- 2021-01-01
 | 
			
		||||
    periodTextWidth' WeekPeriod{}    = 13  -- 2021-01-01W52
 | 
			
		||||
    periodTextWidth' MonthPeriod{}   = 7   -- 2021-01
 | 
			
		||||
    periodTextWidth' QuarterPeriod{} = 6   -- 2021Q1
 | 
			
		||||
    periodTextWidth' YearPeriod{}    = 4   -- 2021
 | 
			
		||||
    periodTextWidth' PeriodBetween{} = 22  -- 2021-01-01..2021-01-07
 | 
			
		||||
    periodTextWidth' PeriodFrom{}    = 12  -- 2021-01-01..
 | 
			
		||||
    periodTextWidth' PeriodTo{}      = 12  -- ..2021-01-01
 | 
			
		||||
    periodTextWidth' PeriodAll       = 2   -- ..
 | 
			
		||||
 | 
			
		||||
-- | Render a period as a compact display string suitable for user output.
 | 
			
		||||
--
 | 
			
		||||
-- >>> showPeriod (WeekPeriod (fromGregorian 2016 7 25))
 | 
			
		||||
 | 
			
		||||
@ -25,8 +25,8 @@ import Data.List (nub, sortOn)
 | 
			
		||||
import Data.List.Extra (nubSort)
 | 
			
		||||
import Data.Maybe (fromMaybe, isJust, isNothing)
 | 
			
		||||
import Data.Text (Text)
 | 
			
		||||
import Data.Time.Calendar (Day, addDays)
 | 
			
		||||
import Safe (headMay, lastMay)
 | 
			
		||||
import Data.Time.Calendar (Day)
 | 
			
		||||
import Safe (headMay)
 | 
			
		||||
 | 
			
		||||
import Hledger.Data
 | 
			
		||||
import Hledger.Query
 | 
			
		||||
@ -38,27 +38,25 @@ import Hledger.Reports.ReportOptions
 | 
			
		||||
-- transaction info to help with rendering.
 | 
			
		||||
-- This is used eg for the register command.
 | 
			
		||||
type PostingsReport = [PostingsReportItem] -- line items, one per posting
 | 
			
		||||
type PostingsReportItem = (Maybe Day    -- The posting date, if this is the first posting in a
 | 
			
		||||
                                        -- transaction or if it's different from the previous
 | 
			
		||||
                                        -- posting's date. Or if this a summary posting, the
 | 
			
		||||
                                        -- report interval's start date if this is the first
 | 
			
		||||
                                        -- summary posting in the interval.
 | 
			
		||||
                          ,Maybe Day    -- If this is a summary posting, the report interval's
 | 
			
		||||
                                        -- end date if this is the first summary posting in
 | 
			
		||||
                                        -- the interval.
 | 
			
		||||
                          ,Maybe Text   -- The posting's transaction's description, if this is the first posting in the transaction.
 | 
			
		||||
                          ,Posting      -- The posting, possibly with the account name depth-clipped.
 | 
			
		||||
                          ,MixedAmount  -- The running total after this posting, or with --average,
 | 
			
		||||
                                        -- the running average posting amount. With --historical,
 | 
			
		||||
                                        -- postings before the report start date are included in
 | 
			
		||||
                                        -- the running total/average.
 | 
			
		||||
type PostingsReportItem = (Maybe Day     -- The posting date, if this is the first posting in a
 | 
			
		||||
                                         -- transaction or if it's different from the previous
 | 
			
		||||
                                         -- posting's date. Or if this a summary posting, the
 | 
			
		||||
                                         -- report interval's start date if this is the first
 | 
			
		||||
                                         -- summary posting in the interval.
 | 
			
		||||
                          ,Maybe Period  -- If this is a summary posting, the report interval's period.
 | 
			
		||||
                          ,Maybe Text    -- The posting's transaction's description, if this is the first posting in the transaction.
 | 
			
		||||
                          ,Posting       -- The posting, possibly with the account name depth-clipped.
 | 
			
		||||
                          ,MixedAmount   -- The running total after this posting, or with --average,
 | 
			
		||||
                                         -- the running average posting amount. With --historical,
 | 
			
		||||
                                         -- postings before the report start date are included in
 | 
			
		||||
                                         -- the running total/average.
 | 
			
		||||
                          )
 | 
			
		||||
 | 
			
		||||
-- | A summary posting summarises the activity in one account within a report
 | 
			
		||||
-- interval. It is kludgily represented by a regular Posting with no description,
 | 
			
		||||
-- the interval's start date stored as the posting date, and the interval's end
 | 
			
		||||
-- date attached with a tuple.
 | 
			
		||||
type SummaryPosting = (Posting, Day)
 | 
			
		||||
-- interval. It is by a regular Posting with no description, the interval's
 | 
			
		||||
-- start date stored as the posting date, and the interval's Period attached
 | 
			
		||||
-- with a tuple.
 | 
			
		||||
type SummaryPosting = (Posting, Period)
 | 
			
		||||
 | 
			
		||||
-- | Select postings from the journal and add running balance and other
 | 
			
		||||
-- information to make a postings report. Used by eg hledger's register command.
 | 
			
		||||
@ -74,8 +72,8 @@ postingsReport rspec@ReportSpec{_rsReportOpts=ropts@ReportOpts{..}} j = items
 | 
			
		||||
      (precedingps, reportps) = matchedPostingsBeforeAndDuring rspec j reportspan
 | 
			
		||||
 | 
			
		||||
      -- Postings, or summary postings with their subperiod's end date, to be displayed.
 | 
			
		||||
      displayps :: [(Posting, Maybe Day)]
 | 
			
		||||
        | multiperiod = [(p, Just periodend) | (p, periodend) <- summariseps reportps]
 | 
			
		||||
      displayps :: [(Posting, Maybe Period)]
 | 
			
		||||
        | multiperiod = [(p, Just period) | (p, period) <- summariseps reportps]
 | 
			
		||||
        | otherwise   = [(p, Nothing) | p <- reportps]
 | 
			
		||||
        where
 | 
			
		||||
          summariseps = summarisePostingsByInterval interval_ whichdate mdepth showempty reportspan
 | 
			
		||||
@ -142,15 +140,15 @@ matchedPostingsBeforeAndDuring rspec@ReportSpec{_rsReportOpts=ropts,_rsQuery=q}
 | 
			
		||||
        dateq = dbg4 "dateq" $ filterQuery queryIsDateOrDate2 $ dbg4 "q" q  -- XXX confused by multiple date:/date2: ?
 | 
			
		||||
 | 
			
		||||
-- | Generate postings report line items from a list of postings or (with
 | 
			
		||||
-- non-Nothing dates attached) summary postings.
 | 
			
		||||
postingsReportItems :: [(Posting,Maybe Day)] -> (Posting,Maybe Day) -> WhichDate -> Maybe Int -> MixedAmount -> (Int -> MixedAmount -> MixedAmount -> MixedAmount) -> Int -> [PostingsReportItem]
 | 
			
		||||
-- non-Nothing periods attached) summary postings.
 | 
			
		||||
postingsReportItems :: [(Posting,Maybe Period)] -> (Posting,Maybe Period) -> WhichDate -> Maybe Int -> MixedAmount -> (Int -> MixedAmount -> MixedAmount -> MixedAmount) -> Int -> [PostingsReportItem]
 | 
			
		||||
postingsReportItems [] _ _ _ _ _ _ = []
 | 
			
		||||
postingsReportItems ((p,menddate):ps) (pprev,menddateprev) wd d b runningcalcfn itemnum =
 | 
			
		||||
    i:(postingsReportItems ps (p,menddate) wd d b' runningcalcfn (itemnum+1))
 | 
			
		||||
postingsReportItems ((p,mperiod):ps) (pprev,mperiodprev) wd d b runningcalcfn itemnum =
 | 
			
		||||
    i:(postingsReportItems ps (p,mperiod) wd d b' runningcalcfn (itemnum+1))
 | 
			
		||||
  where
 | 
			
		||||
    i = mkpostingsReportItem showdate showdesc wd menddate p' b'
 | 
			
		||||
    (showdate, showdesc) | isJust menddate = (menddate /= menddateprev,        False)
 | 
			
		||||
                         | otherwise       = (isfirstintxn || isdifferentdate, isfirstintxn)
 | 
			
		||||
    i = mkpostingsReportItem showdate showdesc wd mperiod p' b'
 | 
			
		||||
    (showdate, showdesc) | isJust mperiod = (mperiod /= mperiodprev,          False)
 | 
			
		||||
                         | otherwise      = (isfirstintxn || isdifferentdate, isfirstintxn)
 | 
			
		||||
    isfirstintxn = ptransaction p /= ptransaction pprev
 | 
			
		||||
    isdifferentdate = case wd of PrimaryDate   -> postingDate p  /= postingDate pprev
 | 
			
		||||
                                 SecondaryDate -> postingDate2 p /= postingDate2 pprev
 | 
			
		||||
@ -160,10 +158,10 @@ postingsReportItems ((p,menddate):ps) (pprev,menddateprev) wd d b runningcalcfn
 | 
			
		||||
-- | Generate one postings report line item, containing the posting,
 | 
			
		||||
-- the current running balance, and optionally the posting date and/or
 | 
			
		||||
-- the transaction description.
 | 
			
		||||
mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Day -> Posting -> MixedAmount -> PostingsReportItem
 | 
			
		||||
mkpostingsReportItem showdate showdesc wd menddate p b =
 | 
			
		||||
mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Period -> Posting -> MixedAmount -> PostingsReportItem
 | 
			
		||||
mkpostingsReportItem showdate showdesc wd mperiod p b =
 | 
			
		||||
  (if showdate then Just date else Nothing
 | 
			
		||||
  ,menddate
 | 
			
		||||
  ,mperiod
 | 
			
		||||
  ,if showdesc then tdescription <$> ptransaction p else Nothing
 | 
			
		||||
  ,p
 | 
			
		||||
  ,b
 | 
			
		||||
@ -194,19 +192,18 @@ summarisePostingsByInterval interval wd mdepth showempty reportspan ps = concatM
 | 
			
		||||
-- with 0 amount.
 | 
			
		||||
--
 | 
			
		||||
summarisePostingsInDateSpan :: DateSpan -> WhichDate -> Maybe Int -> Bool -> [Posting] -> [SummaryPosting]
 | 
			
		||||
summarisePostingsInDateSpan (DateSpan b e) wd mdepth showempty ps
 | 
			
		||||
summarisePostingsInDateSpan span@(DateSpan b e) wd mdepth showempty ps
 | 
			
		||||
  | null ps && (isNothing b || isNothing e) = []
 | 
			
		||||
  | null ps && showempty = [(summaryp, e')]
 | 
			
		||||
  | null ps && showempty = [(summaryp, dateSpanAsPeriod span)]
 | 
			
		||||
  | otherwise = summarypes
 | 
			
		||||
  where
 | 
			
		||||
    postingdate = if wd == PrimaryDate then postingDate else postingDate2
 | 
			
		||||
    b' = fromMaybe (maybe nulldate postingdate $ headMay ps) b
 | 
			
		||||
    e' = fromMaybe (maybe (addDays 1 nulldate) postingdate $ lastMay ps) e
 | 
			
		||||
    summaryp = nullposting{pdate=Just b'}
 | 
			
		||||
    clippedanames = nub $ map (clipAccountName mdepth) anames
 | 
			
		||||
    summaryps | mdepth == Just 0 = [summaryp{paccount="...",pamount=sumPostings ps}]
 | 
			
		||||
              | otherwise        = [summaryp{paccount=a,pamount=balance a} | a <- clippedanames]
 | 
			
		||||
    summarypes = map (, e') $ (if showempty then id else filter (not . mixedAmountLooksZero . pamount)) summaryps
 | 
			
		||||
    summarypes = map (, dateSpanAsPeriod span) $ (if showempty then id else filter (not . mixedAmountLooksZero . pamount)) summaryps
 | 
			
		||||
    anames = nubSort $ map paccount ps
 | 
			
		||||
    -- aggregate balances by account, like ledgerFromJournal, then do depth-clipping
 | 
			
		||||
    accts = accountsFromPostings ps
 | 
			
		||||
 | 
			
		||||
@ -134,7 +134,7 @@ postingsReportAsText opts items = TB.toLazyText $ foldMap first3 linesWithWidths
 | 
			
		||||
-- Also returns the natural width (without padding) of the amount and balance
 | 
			
		||||
-- fields.
 | 
			
		||||
postingsReportItemAsText :: CliOpts -> Int -> Int -> PostingsReportItem -> (TB.Builder, Int, Int)
 | 
			
		||||
postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, menddate, mdesc, p, b) =
 | 
			
		||||
postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mperiod, mdesc, p, b) =
 | 
			
		||||
    (table <> TB.singleton '\n', thisamtwidth, thisbalwidth)
 | 
			
		||||
  where
 | 
			
		||||
    table = renderRowB def{tableBorders=False, borderSpaces=False} . Group NoLine $ map Header
 | 
			
		||||
@ -154,11 +154,10 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
 | 
			
		||||
      where w = fullwidth - wbWidth amt
 | 
			
		||||
    -- calculate widths
 | 
			
		||||
    (totalwidth,mdescwidth) = registerWidthsFromOpts opts
 | 
			
		||||
    (datewidth, date) = case (mdate,menddate) of
 | 
			
		||||
        (Just _, Just _)   -> (21, showDateSpan (DateSpan mdate menddate))
 | 
			
		||||
        (Nothing, Just _)  -> (21, "")
 | 
			
		||||
        (Just d, Nothing)  -> (10, showDate d)
 | 
			
		||||
        _                  -> (10, "")
 | 
			
		||||
    datewidth = maybe 10 periodTextWidth mperiod
 | 
			
		||||
    date = case mperiod of
 | 
			
		||||
             Just period -> if isJust mdate then showPeriod period else ""
 | 
			
		||||
             Nothing     -> maybe "" showDate mdate
 | 
			
		||||
    (amtwidth, balwidth)
 | 
			
		||||
      | shortfall <= 0 = (preferredamtwidth, preferredbalwidth)
 | 
			
		||||
      | otherwise      = (adjustedamtwidth, adjustedbalwidth)
 | 
			
		||||
@ -172,10 +171,9 @@ postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, mendda
 | 
			
		||||
 | 
			
		||||
    remaining = totalwidth - (datewidth + 1 + 2 + amtwidth + 2 + balwidth)
 | 
			
		||||
    (descwidth, acctwidth)
 | 
			
		||||
      | hasinterval = (0, remaining - 2)
 | 
			
		||||
      | otherwise   = (w, remaining - 2 - w)
 | 
			
		||||
      | isJust mperiod = (0, remaining - 2)
 | 
			
		||||
      | otherwise      = (w, remaining - 2 - w)
 | 
			
		||||
      where
 | 
			
		||||
        hasinterval = isJust menddate
 | 
			
		||||
        w = fromMaybe ((remaining - 2) `div` 2) mdescwidth
 | 
			
		||||
 | 
			
		||||
    -- gather content
 | 
			
		||||
 | 
			
		||||
@ -13,22 +13,22 @@
 | 
			
		||||
# The last report interval option takes precedence.
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --weekly --monthly
 | 
			
		||||
2019-01                 a                                        2             2
 | 
			
		||||
2019-02                 a                                        1             3
 | 
			
		||||
2019-01   a                                                      2             2
 | 
			
		||||
2019-02   a                                                      1             3
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --monthly --weekly
 | 
			
		||||
2018-12-31W01           a                                        2             2
 | 
			
		||||
2019-01-28W05           a                                        1             3
 | 
			
		||||
2018-12-31W01   a                                                2             2
 | 
			
		||||
2019-01-28W05   a                                                1             3
 | 
			
		||||
 | 
			
		||||
# The last report interval option takes precedence.
 | 
			
		||||
# The --period expression is no exception.
 | 
			
		||||
$ hledger -f- register -p 'monthly in 2019' --weekly
 | 
			
		||||
2018-12-31W01           a                                        2             2
 | 
			
		||||
2019-01-28W05           a                                        1             3
 | 
			
		||||
2018-12-31W01   a                                                2             2
 | 
			
		||||
2019-01-28W05   a                                                1             3
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --weekly -p 'monthly in 2019'
 | 
			
		||||
2019-01                 a                                        2             2
 | 
			
		||||
2019-02                 a                                        1             3
 | 
			
		||||
2019-01   a                                                      2             2
 | 
			
		||||
2019-02   a                                                      1             3
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@ -41,13 +41,13 @@ $ hledger -f- register --weekly -p 'monthly in 2019'
 | 
			
		||||
# -p 'monthly in 2019'
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --monthly -p 2019
 | 
			
		||||
2019-01                 a                                        2             2
 | 
			
		||||
2019-02                 a                                        1             3
 | 
			
		||||
2019-01   a                                                      2             2
 | 
			
		||||
2019-02   a                                                      1             3
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register -p 2019 --monthly
 | 
			
		||||
2019-01                 a                                        2             2
 | 
			
		||||
2019-02                 a                                        1             3
 | 
			
		||||
2019-01   a                                                      2             2
 | 
			
		||||
2019-02   a                                                      1             3
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register -p 'monthly in 2019'
 | 
			
		||||
2019-01                 a                                        2             2
 | 
			
		||||
2019-02                 a                                        1             3
 | 
			
		||||
2019-01   a                                                      2             2
 | 
			
		||||
2019-02   a                                                      1             3
 | 
			
		||||
 | 
			
		||||
@ -302,9 +302,9 @@ P 2000/04/01 A  4 B
 | 
			
		||||
  (a)      1 A @ 9 B
 | 
			
		||||
 | 
			
		||||
$ hledger -f- reg --value=cost -M
 | 
			
		||||
2000-01                 a                                     13 B          13 B
 | 
			
		||||
2000-02                 a                                      8 B          21 B
 | 
			
		||||
2000-03                 a                                      9 B          30 B
 | 
			
		||||
2000-01   a                                                   13 B          13 B
 | 
			
		||||
2000-02   a                                                    8 B          21 B
 | 
			
		||||
2000-03   a                                                    9 B          30 B
 | 
			
		||||
 | 
			
		||||
# back to the original test journal:
 | 
			
		||||
<
 | 
			
		||||
@ -326,27 +326,27 @@ P 2000/04/01 B  1 C
 | 
			
		||||
 | 
			
		||||
# 26. periodic register report valued at period end
 | 
			
		||||
$ hledger -f- reg --value=end -M -b 2000
 | 
			
		||||
2000-01                 a                                      5 B           5 B
 | 
			
		||||
2000-02                 a                                      2 B           7 B
 | 
			
		||||
2000-03                 a                                      3 B          10 B
 | 
			
		||||
2000-01   a                                                    5 B           5 B
 | 
			
		||||
2000-02   a                                                    2 B           7 B
 | 
			
		||||
2000-03   a                                                    3 B          10 B
 | 
			
		||||
 | 
			
		||||
# 27. periodic register report valued at specified date
 | 
			
		||||
$ hledger -f- reg --value=2000-01-15 -M -b 2000
 | 
			
		||||
2000-01                 a                                      5 B           5 B
 | 
			
		||||
2000-02                 a                                      5 B          10 B
 | 
			
		||||
2000-03                 a                                      5 B          15 B
 | 
			
		||||
2000-01   a                                                    5 B           5 B
 | 
			
		||||
2000-02   a                                                    5 B          10 B
 | 
			
		||||
2000-03   a                                                    5 B          15 B
 | 
			
		||||
 | 
			
		||||
# 28. periodic register report valued today
 | 
			
		||||
$ hledger -f- reg --value=now -M -b 2000
 | 
			
		||||
2000-01                 a                                      4 B           4 B
 | 
			
		||||
2000-02                 a                                      4 B           8 B
 | 
			
		||||
2000-03                 a                                      4 B          12 B
 | 
			
		||||
2000-01   a                                                    4 B           4 B
 | 
			
		||||
2000-02   a                                                    4 B           8 B
 | 
			
		||||
2000-03   a                                                    4 B          12 B
 | 
			
		||||
 | 
			
		||||
# 29. periodic register report valued at default date (same as --value=end)
 | 
			
		||||
$ hledger -f- reg -V -M -b 2000
 | 
			
		||||
2000-01                 a                                      5 B           5 B
 | 
			
		||||
2000-02                 a                                      2 B           7 B
 | 
			
		||||
2000-03                 a                                      3 B          10 B
 | 
			
		||||
2000-01   a                                                    5 B           5 B
 | 
			
		||||
2000-02   a                                                    2 B           7 B
 | 
			
		||||
2000-03   a                                                    3 B          10 B
 | 
			
		||||
 | 
			
		||||
# balance
 | 
			
		||||
 | 
			
		||||
@ -621,8 +621,8 @@ P 2020-04-01 A 4 B
 | 
			
		||||
   (a)  1 A
 | 
			
		||||
 | 
			
		||||
$ hledger -f- reg --value=then -Q
 | 
			
		||||
2020Q1                  a                                      6 B           6 B
 | 
			
		||||
2020Q2                  a                                      4 B          10 B
 | 
			
		||||
2020Q1   a                                                     6 B           6 B
 | 
			
		||||
2020Q2   a                                                     4 B          10 B
 | 
			
		||||
>=0
 | 
			
		||||
 | 
			
		||||
# 53. print --value should affect all postings, including when there's an implicit transaction price
 | 
			
		||||
 | 
			
		||||
@ -75,8 +75,8 @@ hledger -f- --pivot description reg -M
 | 
			
		||||
    assets:bank account                                   2 EUR  ; date:03/01
 | 
			
		||||
    income:donations                                  -2 EUR
 | 
			
		||||
>>>
 | 
			
		||||
2016-02                 Freifunk                            -2 EUR        -2 EUR
 | 
			
		||||
2016-03                 Freifunk                             2 EUR             0
 | 
			
		||||
2016-02   Freifunk                                          -2 EUR        -2 EUR
 | 
			
		||||
2016-03   Freifunk                                           2 EUR             0
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# pivot for implicit tag code (technical sample)
 | 
			
		||||
@ -86,8 +86,8 @@ hledger -f- --pivot code reg -M
 | 
			
		||||
    assets:bank account                                   2 EUR  ; date:03/01
 | 
			
		||||
    income:donations                                  -2 EUR
 | 
			
		||||
>>>
 | 
			
		||||
2016-02                 Freifunk                            -2 EUR        -2 EUR
 | 
			
		||||
2016-03                 Freifunk                             2 EUR             0
 | 
			
		||||
2016-02   Freifunk                                          -2 EUR        -2 EUR
 | 
			
		||||
2016-03   Freifunk                                           2 EUR             0
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# use of pivot with code-based budgeting
 | 
			
		||||
@ -132,7 +132,7 @@ hledger -f- --pivot payee reg -D ^expense
 | 
			
		||||
    assets:bank account
 | 
			
		||||
    expense:grocery                    30 EUR
 | 
			
		||||
>>>
 | 
			
		||||
2016-02-16              Auchan                              22 EUR        22 EUR
 | 
			
		||||
                        StarBars                             5 EUR        27 EUR
 | 
			
		||||
2016-02-17              Auchan                              30 EUR        57 EUR
 | 
			
		||||
2016-02-16   Auchan                                         22 EUR        22 EUR
 | 
			
		||||
             StarBars                                        5 EUR        27 EUR
 | 
			
		||||
2016-02-17   Auchan                                         30 EUR        57 EUR
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
@ -43,8 +43,8 @@ hledger -f - register aa --depth 1 --daily
 | 
			
		||||
  a:aa      1
 | 
			
		||||
  b:bb:bbb
 | 
			
		||||
>>>
 | 
			
		||||
2010-01-01              a                                        2             2
 | 
			
		||||
2010-01-02              a                                        1             3
 | 
			
		||||
2010-01-01   a                                                   2             2
 | 
			
		||||
2010-01-02   a                                                   1             3
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
# 4. with --cleared
 | 
			
		||||
@ -75,7 +75,7 @@ hledger -f - register --depth 0 --daily a b
 | 
			
		||||
  b:bb      2
 | 
			
		||||
  c:cc
 | 
			
		||||
>>>
 | 
			
		||||
2010-01-01              ...                                      6             6
 | 
			
		||||
2010-01-02              ...                                      3             9
 | 
			
		||||
2010-01-01   ...                                                 6             6
 | 
			
		||||
2010-01-02   ...                                                 3             9
 | 
			
		||||
>>>=0
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@ -5,8 +5,8 @@
 | 
			
		||||
  (a:b)  1
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --period 'monthly'
 | 
			
		||||
2011-02                 a                                        1             1
 | 
			
		||||
                        a:b                                      1             2
 | 
			
		||||
2011-02   a                                                      1             1
 | 
			
		||||
          a:b                                                    1             2
 | 
			
		||||
 | 
			
		||||
# 2. or with a query pattern, just the intervals with matched data:
 | 
			
		||||
<
 | 
			
		||||
@ -17,7 +17,7 @@ $ hledger -f- register --period 'monthly'
 | 
			
		||||
  (b)  1
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --period 'monthly' b
 | 
			
		||||
2011-02                 b                                        1             1
 | 
			
		||||
2011-02   b                                                      1             1
 | 
			
		||||
 | 
			
		||||
<
 | 
			
		||||
2011/1/1
 | 
			
		||||
@ -33,13 +33,13 @@ $ hledger -f- register --period 'monthly' b
 | 
			
		||||
# (unlike current ledger, but more useful)
 | 
			
		||||
$ hledger -f- register --period 'monthly' b --empty
 | 
			
		||||
2011-01                                                          0             0
 | 
			
		||||
2011-02                 b                                        1             1
 | 
			
		||||
2011-02   b                                                      1             1
 | 
			
		||||
2011-03                                                          0             1
 | 
			
		||||
 | 
			
		||||
# 4. any specified begin/end dates limit the intervals reported
 | 
			
		||||
$ hledger -f- register --period 'monthly to 2011/3/1' b --empty
 | 
			
		||||
2011-01                                                          0             0
 | 
			
		||||
2011-02                 b                                        1             1
 | 
			
		||||
2011-02   b                                                      1             1
 | 
			
		||||
 | 
			
		||||
# 5. --date2 should work with intervals
 | 
			
		||||
<
 | 
			
		||||
@ -50,8 +50,8 @@ $ hledger -f- register --period 'monthly to 2011/3/1' b --empty
 | 
			
		||||
  (b)  1
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register --monthly --date2
 | 
			
		||||
2014-01                 a                                        1             1
 | 
			
		||||
                        b                                        1             2
 | 
			
		||||
2014-01   a                                                      1             1
 | 
			
		||||
          b                                                      1             2
 | 
			
		||||
 | 
			
		||||
# 6. All matched postings in the displayed intervals should be reported on.
 | 
			
		||||
<
 | 
			
		||||
@ -65,7 +65,14 @@ $ hledger -f- register --monthly --date2
 | 
			
		||||
 (after)  1
 | 
			
		||||
 | 
			
		||||
$ hledger -f- register -p 'monthly 2014/1/10-2014/2/20'
 | 
			
		||||
2014-01                 before                                   1             1
 | 
			
		||||
2014-02                 after                                    1             2
 | 
			
		||||
                        within                                   1             3
 | 
			
		||||
2014-01   before                                                 1             1
 | 
			
		||||
2014-02   after                                                  1             2
 | 
			
		||||
          within                                                 1             3
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
# 7. Custom ranges should display fully.
 | 
			
		||||
$ hledger -f- register -p 'every tue'
 | 
			
		||||
2013-12-31..2014-01-06   before                                  1             1
 | 
			
		||||
2014-01-28..2014-02-03   within                                  1             2
 | 
			
		||||
2014-02-25..2014-03-03   after                                   1             3
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		Loading…
	
		Reference in New Issue
	
	Block a user