Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-hledger-lib for openSUSE:Factory 
checked in at 2021-01-20 18:26:00
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-hledger-lib (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-hledger-lib.new.28504 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-hledger-lib"

Wed Jan 20 18:26:00 2021 rev:9 rq:864457 version:1.20.3

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-hledger-lib/ghc-hledger-lib.changes  
2021-01-08 17:40:00.912996961 +0100
+++ 
/work/SRC/openSUSE:Factory/.ghc-hledger-lib.new.28504/ghc-hledger-lib.changes   
    2021-01-20 18:26:21.435456887 +0100
@@ -1,0 +2,8 @@
+Fri Jan 15 08:56:01 UTC 2021 - [email protected]
+
+- Update hledger-lib to version 1.20.3.
+  # 1.20.3 2021-01-14
+
+  - See hledger.
+
+-------------------------------------------------------------------

Old:
----
  hledger-lib-1.20.2.tar.gz

New:
----
  hledger-lib-1.20.3.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-hledger-lib.spec ++++++
--- /var/tmp/diff_new_pack.AkT3KZ/_old  2021-01-20 18:26:22.363457771 +0100
+++ /var/tmp/diff_new_pack.AkT3KZ/_new  2021-01-20 18:26:22.367457775 +0100
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-hledger-lib
 #
-# Copyright (c) 2020 SUSE LLC
+# Copyright (c) 2021 SUSE LLC
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -19,7 +19,7 @@
 %global pkg_name hledger-lib
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        1.20.2
+Version:        1.20.3
 Release:        0
 Summary:        A reusable library providing the core functionality of hledger
 License:        GPL-3.0-or-later

++++++ hledger-lib-1.20.2.tar.gz -> hledger-lib-1.20.3.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/CHANGES.md 
new/hledger-lib-1.20.3/CHANGES.md
--- old/hledger-lib-1.20.2/CHANGES.md   2020-12-29 02:37:44.000000000 +0100
+++ new/hledger-lib-1.20.3/CHANGES.md   2021-01-14 15:30:14.000000000 +0100
@@ -1,6 +1,10 @@
 Internal/api/developer-ish changes in the hledger-lib (and hledger) packages.
 For user-visible changes, see the hledger package changelog.
 
+# 1.20.3 2021-01-14
+
+- See hledger.
+
 # 1.20.2 2020-12-28
 
 - Fix the info manuals' node structure.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/Hledger/Data/Commodity.hs 
new/hledger-lib-1.20.3/Hledger/Data/Commodity.hs
--- old/hledger-lib-1.20.2/Hledger/Data/Commodity.hs    2020-11-18 
01:27:47.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Data/Commodity.hs    2021-01-13 
19:36:26.000000000 +0100
@@ -25,6 +25,8 @@
 import Hledger.Data.Types
 import Hledger.Utils
 
+-- Show space-containing commodity symbols quoted, as they are in a journal.
+showCommoditySymbol = textQuoteIfNeeded
 
 -- characters that may not be used in a non-quoted commodity symbol
 isNonsimpleCommodityChar :: Char -> Bool
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/Hledger/Data/Valuation.hs 
new/hledger-lib-1.20.3/Hledger/Data/Valuation.hs
--- old/hledger-lib-1.20.2/Hledger/Data/Valuation.hs    2020-12-29 
00:24:17.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Data/Valuation.hs    2021-01-14 
14:49:35.000000000 +0100
@@ -5,6 +5,7 @@
 
 -}
 
+{-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE RecordWildCards #-}
@@ -28,9 +29,8 @@
 where
 
 import Control.Applicative ((<|>))
-import Data.Foldable (asum)
 import Data.Function ((&), on)
-import Data.List ( (\\), sortBy )
+import Data.List (partition, intercalate, sortBy)
 import Data.List.Extra (nubSortBy)
 import qualified Data.Map as M
 import qualified Data.Set as S
@@ -39,12 +39,13 @@
 import Data.Time.Calendar (Day, fromGregorian)
 import Data.MemoUgly (memo)
 import GHC.Generics (Generic)
-import Safe (lastMay)
+import Safe (headMay, lastMay)
 
 import Hledger.Utils
 import Hledger.Data.Types
 import Hledger.Data.Amount
 import Hledger.Data.Dates (nulldate)
+import Hledger.Data.Commodity (showCommoditySymbol)
 
 
 ------------------------------------------------------------------------------
@@ -219,9 +220,13 @@
       Just to            ->
         -- We have a commodity to convert to. Find the most direct price 
available,
         -- according to the rules described in makePriceGraph.
-        case 
-          pricesShortestPath forwardprices from to <|> 
-          pricesShortestPath allprices     from to 
+        let msg = "seeking " ++ pshowedge' "" from to ++ " price"
+        in case 
+          (traceAt 2 (msg++" using forward prices") $ 
+            pricesShortestPath from to forwardprices)
+          <|> 
+          (traceAt 2 (msg++" using forward and reverse prices") $ 
+            pricesShortestPath from to allprices)
         of
           Nothing -> Nothing
           Just [] -> Nothing
@@ -246,6 +251,7 @@
 
 ------------------------------------------------------------------------------
 -- Market price graph
+-- built directly with MarketPrices for now, probably space-inefficient
 
 type Edge = MarketPrice
 type Path = [Edge]
@@ -277,33 +283,55 @@
 -- form the edges of a directed graph. There should be at most one edge
 -- between each directed pair of commodities, eg there can be one
 -- USD->EUR price and one EUR->USD price.
-pricesShortestPath :: [Edge] -> CommoditySymbol -> CommoditySymbol -> Maybe 
Path
-pricesShortestPath edges start end =
-  dbg1 ("shortest price path for "++T.unpack start++" -> "++T.unpack end) $ 
-  asum $ map (findPath end edgesremaining) initialpaths
+pricesShortestPath :: CommoditySymbol -> CommoditySymbol -> [Edge] -> Maybe 
Path
+pricesShortestPath start end edges =
+  dbg2 ("shortest "++pshowedge' "" start end++" price path") $
+  find [([],edges)]
   where
-    initialpaths = dbg9 "initial price paths" $ [[p] | p <- edges, mpfrom p == 
start]
-    edgesremaining = dbg9 "initial edges remaining" $ edges \\ concat 
initialpaths
-
--- Helper: breadth-first search for a continuation of the given path
--- using zero or more of the given edges, to the specified end commodity.
--- Returns the first & shortest complete path found, or Nothing.
-findPath :: CommoditySymbol -> [Edge] -> Path -> Maybe Path
-findPath end _ path | mpathend == Just end = Just path  -- path is complete
-  where 
-    mpathend = mpto <$> lastMay path
-findPath _ [] _ = Nothing   -- no more edges are available
-findPath end edgesremaining path =   -- try continuing with all the remaining 
edges
-  asum [ 
-      findPath end edgesremaining' path'
-    | e <- nextedges
-    , let path' = path++[e]
-    , let edgesremaining' = filter (/=e) edgesremaining
-    ]
-  where
-    nextedges = [ e | e <- edgesremaining, Just (mpfrom e) == mpathend ]
-      where
-        mpathend = mpto <$> lastMay path
+    -- Find the first and shortest complete path using a breadth-first search.
+    find :: [(Path,[Edge])] -> Maybe Path
+    find paths =
+      case concatMap extend paths of
+        [] -> Nothing 
+        _ | iteration > maxiterations -> 
+          trace ("gave up searching for a price chain after "++show 
maxiterations++" iterations, please report a bug")
+          Nothing
+          where 
+            iteration = 1 + maybe 0 (length . fst) (headMay paths)
+            maxiterations = 1000
+        paths' -> 
+          case completepaths of
+                p:_ -> Just p  -- the left-most complete path at this length
+                []  -> find paths'
+          where completepaths = [p | (p,_) <- paths', (mpto <$> lastMay p) == 
Just end]
+
+    -- Use all applicable edges from those provided to extend this path by one 
step,
+    -- returning zero or more new (path, remaining edges) pairs.
+    extend :: (Path,[Edge]) -> [(Path,[Edge])]
+    extend (path,unusededges) =
+      let
+        pathnodes = start : map mpto path
+        pathend = fromMaybe start $ mpto <$> lastMay path
+        (nextedges,remainingedges) = partition ((==pathend).mpfrom) unusededges
+      in
+        [ (path', remainingedges')
+        | e <- nextedges
+        , let path' = dbgpath "trying" $ path ++ [e]  -- PERF prepend ?
+        , let pathnodes' = mpto e : pathnodes
+        , let remainingedges' = [r | r <- remainingedges, not $ mpto r `elem` 
pathnodes' ]
+        ]
+
+-- debug helpers
+dbgpath  label = dbg2With (pshowpath label)
+-- dbgedges label = dbg2With (pshowedges label)
+pshowpath label = \case
+  []      -> prefix label ""
+  p@(e:_) -> prefix label $ pshownode (mpfrom e) ++ ">" ++ intercalate ">" 
(map (pshownode . mpto) p)
+-- pshowedges label = prefix label . intercalate ", " . map (pshowedge "")
+-- pshowedge label MarketPrice{..} = pshowedge' label mpfrom mpto
+pshowedge' label from to = prefix label $ pshownode from ++ ">" ++ pshownode to
+pshownode = T.unpack . showCommoditySymbol
+prefix l = if null l then (""++) else ((l++": ")++)
 
 -- | A snapshot of the known exchange rates between commodity pairs at a given 
date.
 -- This is a home-made version, more tailored to our needs.
@@ -367,12 +395,12 @@
     }
   where
     -- prices in effect on date d, either declared or inferred
-    visibledeclaredprices = dbg2 "visibledeclaredprices" $ filter 
((<=d).mpdate) alldeclaredprices
-    visibleinferredprices = dbg2 "visibleinferredprices" $ filter 
((<=d).mpdate) allinferredprices
+    visibledeclaredprices = dbg9 "visibledeclaredprices" $ filter 
((<=d).mpdate) alldeclaredprices
+    visibleinferredprices = dbg9 "visibleinferredprices" $ filter 
((<=d).mpdate) allinferredprices
     forwardprices = effectiveMarketPrices visibledeclaredprices 
visibleinferredprices
 
     -- infer any additional reverse prices not already declared or inferred
-    reverseprices = dbg2 "additional reverse prices" $
+    reverseprices = dbg9 "additional reverse prices" $
       [p | p@MarketPrice{..} <- map marketPriceReverse forwardprices
          , not $ (mpfrom,mpto) `S.member` forwardpairs
       ]
@@ -384,7 +412,7 @@
     -- somewhat but not quite like effectiveMarketPrices
     defaultdests = M.fromList [(mpfrom,mpto) | MarketPrice{..} <- 
pricesfordefaultcomms]
       where
-        pricesfordefaultcomms = dbg2 "prices for choosing default valuation 
commodities, by date then parse order" $
+        pricesfordefaultcomms = dbg9 "prices for choosing default valuation 
commodities, by date then parse order" $
           ps
           & zip [1..]  -- label items with their parse order
           & sortBy (compare `on` 
(\(parseorder,MarketPrice{..})->(mpdate,parseorder)))  -- sort by increasing 
date then increasing parse order
@@ -407,7 +435,7 @@
     declaredprices' = [(1, i, p) | (i,p) <- zip [1..] declaredprices]
     inferredprices' = [(0, i, p) | (i,p) <- zip [1..] inferredprices]
   in
-    dbg2 "effective forward prices" $
+    dbg9 "effective forward prices" $
     -- combine
     declaredprices' ++ inferredprices'
     -- sort by decreasing date then decreasing precedence then decreasing 
parse order
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/Hledger/Read/Common.hs 
new/hledger-lib-1.20.3/Hledger/Read/Common.hs
--- old/hledger-lib-1.20.2/Hledger/Read/Common.hs       2020-12-28 
21:45:25.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Read/Common.hs       2021-01-14 
14:49:35.000000000 +0100
@@ -401,7 +401,7 @@
         mfirstundeclaredcomm = 
           headMay $ filter (not . (`elem` cs)) $ catMaybes $
           (acommodity . baamount <$> pbalanceassertion) :
-          (map (Just . acommodity) $ amounts pamount)
+          (map (Just . acommodity) . filter (/= missingamt) $ amounts pamount)
         cs = journalCommoditiesDeclared j
 
 setYear :: Year -> JournalParser m ()
@@ -788,9 +788,12 @@
         return $ nullamt{acommodity=c, aquantity=sign q, aismultiplier=mult, 
astyle=s, aprice=Nothing}
       -- no symbol amount
       Nothing -> do
-        mdecmarkStyle <- getDecimalMarkStyle
-        mcommodityStyle <- getDefaultAmountStyle
-        let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle
+        -- look for a number style to use when parsing, based on
+        -- these things we've already parsed, in this order of preference:
+        mdecmarkStyle   <- getDecimalMarkStyle   -- a decimal-mark CSV rule
+        mcommodityStyle <- getAmountStyle ""     -- a commodity directive for 
the no-symbol commodity
+        mdefaultStyle   <- getDefaultAmountStyle -- a D default commodity 
directive
+        let msuggestedStyle = mdecmarkStyle <|> mcommodityStyle <|> 
mdefaultStyle
         (q,prec,mdec,mgrps) <- lift $ interpretNumber numRegion 
msuggestedStyle ambiguousRawNum mExponent
         -- if a default commodity has been set, apply it and its style to this 
amount
         -- (unless it's a multiplier in an automated posting)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/Hledger/Reports/BudgetReport.hs 
new/hledger-lib-1.20.3/Hledger/Reports/BudgetReport.hs
--- old/hledger-lib-1.20.2/Hledger/Reports/BudgetReport.hs      2020-12-29 
00:24:17.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Reports/BudgetReport.hs      2021-01-14 
14:49:35.000000000 +0100
@@ -21,6 +21,7 @@
   budgetReportAsCsv,
   -- * Helpers
   reportPeriodName,
+  combineBudgetAndActual,
   -- * Tests
   tests_BudgetReport
 )
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/hledger-lib-1.20.2/Hledger/Reports/MultiBalanceReport.hs 
new/hledger-lib-1.20.3/Hledger/Reports/MultiBalanceReport.hs
--- old/hledger-lib-1.20.2/Hledger/Reports/MultiBalanceReport.hs        
2020-12-29 00:24:17.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Reports/MultiBalanceReport.hs        
2021-01-14 14:49:35.000000000 +0100
@@ -51,7 +51,7 @@
 #endif
 import Data.Semigroup (sconcat)
 import Data.Time.Calendar (Day, addDays, fromGregorian)
-import Safe (headMay, lastDef, lastMay, minimumMay)
+import Safe (headMay, lastDef, lastMay)
 
 import Hledger.Data
 import Hledger.Query
@@ -358,39 +358,20 @@
         HistoricalBalance -> historical
       where
         historical = cumulativeSum startingBalance
-        cumulative | fixedValuationDate = cumulativeSum nullacct
-                   | otherwise          = fmap (`subtractAcct` valuedStart) 
historical
-        changeamts | fixedValuationDate = M.mapWithKey valueAcct changes
-                   | otherwise          = M.fromDistinctAscList . zip dates $
-                                            zipWith subtractAcct histamts 
(valuedStart:histamts)
-          where (dates, histamts) = unzip $ M.toAscList historical
+        cumulative = cumulativeSum nullacct
+        changeamts = M.mapWithKey valueAcct changes
 
         cumulativeSum start = snd $ M.mapAccumWithKey accumValued start changes
           where accumValued startAmt date newAmt = (s, valueAcct date s)
                   where s = sumAcct startAmt newAmt
 
-        -- Whether the market price is measured at the same date for all report
-        -- periods, and we can therefore use the simpler calculations for
-        -- cumulative and change reports.
-        fixedValuationDate = case value_ ropts of
-            Just (AtCost (Just _)) -> singleperiod
-            Just (AtEnd  _)        -> singleperiod
-            Just (AtDefault _)     -> singleperiod
-            _                      -> True
-          where singleperiod = interval_ ropts == NoInterval
-
         startingBalance = HM.lookupDefault nullacct name startbals
-        valuedStart = valueAcct (DateSpan Nothing historicalDate) 
startingBalance
 
     -- Add the values of two accounts. Should be right-biased, since it's used
     -- in scanl, so other properties (such as anumpostings) stay in the right 
place
     sumAcct Account{aibalance=i1,aebalance=e1} 
a@Account{aibalance=i2,aebalance=e2} =
         a{aibalance = i1 + i2, aebalance = e1 + e2}
 
-    -- Subtract the values in one account from another. Should be left-biased.
-    subtractAcct a@Account{aibalance=i1,aebalance=e1} 
Account{aibalance=i2,aebalance=e2} =
-        a{aibalance = i1 - i2, aebalance = e1 - e2}
-
     -- We may be converting amounts to value, per hledger_options.m4.md 
"Effect of --value on reports".
     valueAcct (DateSpan _ (Just end)) acct =
         acct{aibalance = value (aibalance acct), aebalance = value (aebalance 
acct)}
@@ -398,8 +379,6 @@
     valueAcct _ _ = error "multiBalanceReport: expected all spans to have an 
end date"  -- XXX should not happen
 
     zeros = M.fromList [(span, nullacct) | span <- colspans]
-    historicalDate = minimumMay $ mapMaybe spanStart colspans
-
 
 -- | Lay out a set of postings grouped by date span into a regular matrix with 
rows
 -- given by AccountName and columns by DateSpan, then generate a 
MultiBalanceReport
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/Hledger/Reports/PostingsReport.hs 
new/hledger-lib-1.20.3/Hledger/Reports/PostingsReport.hs
--- old/hledger-lib-1.20.2/Hledger/Reports/PostingsReport.hs    2020-12-29 
00:24:17.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Reports/PostingsReport.hs    2021-01-14 
14:49:35.000000000 +0100
@@ -81,15 +81,15 @@
 
       -- Postings, or summary postings with their subperiod's end date, to be 
displayed.
       displayps :: [(Posting, Maybe Day)]
-        | multiperiod =
-            let summaryps = summarisePostingsByInterval interval_ whichdate 
mdepth showempty reportspan reportps
-            in [(pvalue p lastday, Just periodend) | (p, periodend) <- 
summaryps, let lastday = addDays (-1) periodend]
-        | otherwise =
-            [(pvalue p reportorjournallast, Nothing) | p <- reportps]
+        | multiperiod && changingValuation ropts = [(pvalue lastday p, Just 
periodend) | (p, periodend) <- summariseps reportps, let lastday = addDays (-1) 
periodend]
+        | multiperiod                            = [(p, Just periodend) | (p, 
periodend) <- summariseps valuedps]
+        | otherwise                              = [(p, Nothing)        | p <- 
valuedps]
         where
+          summariseps = summarisePostingsByInterval interval_ whichdate mdepth 
showempty reportspan
+          valuedps = map (pvalue reportorjournallast) reportps
           showempty = empty_ || average_
           -- We may be converting posting amounts to value, per 
hledger_options.m4.md "Effect of --value on reports".
-          pvalue p periodlast = maybe p (postingApplyValuation priceoracle 
styles periodlast mreportlast (rsToday rspec) multiperiod p) value_
+          pvalue periodlast p = maybe p (postingApplyValuation priceoracle 
styles periodlast mreportlast (rsToday rspec) multiperiod p) value_
             where
               mreportlast = reportPeriodLastDay rspec
           reportorjournallast =
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/Hledger/Reports/ReportOptions.hs 
new/hledger-lib-1.20.3/Hledger/Reports/ReportOptions.hs
--- old/hledger-lib-1.20.2/Hledger/Reports/ReportOptions.hs     2020-12-29 
00:24:17.000000000 +0100
+++ new/hledger-lib-1.20.3/Hledger/Reports/ReportOptions.hs     2021-01-14 
14:49:35.000000000 +0100
@@ -23,6 +23,7 @@
   rawOptsToReportSpec,
   flat_,
   tree_,
+  changingValuation,
   reportOptsToggleStatus,
   simplifyStatuses,
   whichDateFromOpts,
@@ -485,6 +486,15 @@
     consIf f b = if b then (f True:) else id
     consJust f = maybe id ((:) . f)
 
+-- | Whether the market price for postings might change when reported in
+-- different report periods.
+changingValuation :: ReportOpts -> Bool
+changingValuation ropts = case value_ ropts of
+    Just (AtCost (Just _)) -> True
+    Just (AtEnd  _)        -> True
+    Just (AtDefault _)     -> interval_ ropts /= NoInterval
+    _                      -> False
+
 -- Report dates.
 
 -- | The effective report span is the start and end dates specified by
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger-lib.cabal 
new/hledger-lib-1.20.3/hledger-lib.cabal
--- old/hledger-lib-1.20.2/hledger-lib.cabal    2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger-lib.cabal    2021-01-14 14:50:04.000000000 
+0100
@@ -4,10 +4,10 @@
 --
 -- see: https://github.com/sol/hpack
 --
--- hash: f99ed8ff188d98ffb43ea739b382591b37b4e66b2adbabc5345e75d4e8e69a56
+-- hash: 84b9a4a7bf3049275178ede9a44418e46548ddce8bdbd182d32caccb5cb51f3f
 
 name:           hledger-lib
-version:        1.20.2
+version:        1.20.3
 synopsis:       A reusable library providing the core functionality of hledger
 description:    A reusable library containing hledger's core functionality.
                 This is used by most hledger* packages so that they support 
the same
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_csv.5 
new/hledger-lib-1.20.3/hledger_csv.5
--- old/hledger-lib-1.20.2/hledger_csv.5        2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_csv.5        2021-01-14 14:51:09.000000000 
+0100
@@ -1,6 +1,6 @@
 .\"t
 
-.TH "HLEDGER_CSV" "5" "December 2020" "hledger-lib-1.20.1 " "hledger User 
Manuals"
+.TH "HLEDGER_CSV" "5" "December 2020" "hledger-lib-1.20.3 " "hledger User 
Manuals"
 
 
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_csv.txt 
new/hledger-lib-1.20.3/hledger_csv.txt
--- old/hledger-lib-1.20.2/hledger_csv.txt      2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_csv.txt      2021-01-14 14:51:17.000000000 
+0100
@@ -958,4 +958,4 @@
 
 
 
-hledger-lib-1.20.1               December 2020                  HLEDGER_CSV(5)
+hledger-lib-1.20.3               December 2020                  HLEDGER_CSV(5)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_journal.5 
new/hledger-lib-1.20.3/hledger_journal.5
--- old/hledger-lib-1.20.2/hledger_journal.5    2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_journal.5    2021-01-14 14:51:09.000000000 
+0100
@@ -1,6 +1,6 @@
 .\"t
 
-.TH "HLEDGER_JOURNAL" "5" "December 2020" "hledger-lib-1.20.1 " "hledger User 
Manuals"
+.TH "HLEDGER_JOURNAL" "5" "December 2020" "hledger-lib-1.20.3 " "hledger User 
Manuals"
 
 
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_journal.txt 
new/hledger-lib-1.20.3/hledger_journal.txt
--- old/hledger-lib-1.20.2/hledger_journal.txt  2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_journal.txt  2021-01-14 14:51:17.000000000 
+0100
@@ -1575,4 +1575,4 @@
 
 
 
-hledger-lib-1.20.1               December 2020              HLEDGER_JOURNAL(5)
+hledger-lib-1.20.3               December 2020              HLEDGER_JOURNAL(5)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_timeclock.5 
new/hledger-lib-1.20.3/hledger_timeclock.5
--- old/hledger-lib-1.20.2/hledger_timeclock.5  2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_timeclock.5  2021-01-14 14:51:08.000000000 
+0100
@@ -1,5 +1,5 @@
 
-.TH "HLEDGER_TIMECLOCK" "5" "December 2020" "hledger-lib-1.20.1 " "hledger 
User Manuals"
+.TH "HLEDGER_TIMECLOCK" "5" "December 2020" "hledger-lib-1.20.3 " "hledger 
User Manuals"
 
 
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_timeclock.txt 
new/hledger-lib-1.20.3/hledger_timeclock.txt
--- old/hledger-lib-1.20.2/hledger_timeclock.txt        2020-12-29 
02:22:19.000000000 +0100
+++ new/hledger-lib-1.20.3/hledger_timeclock.txt        2021-01-14 
14:51:17.000000000 +0100
@@ -77,4 +77,4 @@
 
 
 
-hledger-lib-1.20.1               December 2020            HLEDGER_TIMECLOCK(5)
+hledger-lib-1.20.3               December 2020            HLEDGER_TIMECLOCK(5)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_timedot.5 
new/hledger-lib-1.20.3/hledger_timedot.5
--- old/hledger-lib-1.20.2/hledger_timedot.5    2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_timedot.5    2021-01-14 14:51:08.000000000 
+0100
@@ -1,5 +1,5 @@
 
-.TH "HLEDGER_TIMEDOT" "5" "December 2020" "hledger-lib-1.20.1 " "hledger User 
Manuals"
+.TH "HLEDGER_TIMEDOT" "5" "December 2020" "hledger-lib-1.20.3 " "hledger User 
Manuals"
 
 
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hledger-lib-1.20.2/hledger_timedot.txt 
new/hledger-lib-1.20.3/hledger_timedot.txt
--- old/hledger-lib-1.20.2/hledger_timedot.txt  2020-12-29 02:22:19.000000000 
+0100
+++ new/hledger-lib-1.20.3/hledger_timedot.txt  2021-01-14 14:51:17.000000000 
+0100
@@ -160,4 +160,4 @@
 
 
 
-hledger-lib-1.20.1               December 2020              HLEDGER_TIMEDOT(5)
+hledger-lib-1.20.3               December 2020              HLEDGER_TIMEDOT(5)

Reply via email to