diff --git a/Hledger/Cli/Commands/Register.hs b/Hledger/Cli/Commands/Register.hs index a921d7909..7a67000eb 100644 --- a/Hledger/Cli/Commands/Register.hs +++ b/Hledger/Cli/Commands/Register.hs @@ -51,12 +51,6 @@ summarisePostings interval depth empty filterspan ps = concatMap summarisespan $ reportspan | empty = filterspan `orDatesFrom` dataspan | otherwise = dataspan --- | Combine two datespans, filling any unspecified dates in the first --- with dates from the second. -orDatesFrom (DateSpan a1 b1) (DateSpan a2 b2) = DateSpan a b - where a = if isJust a1 then a1 else a2 - b = if isJust b1 then b1 else b2 - -- | Date-sort and split a list of postings into three spans - postings matched -- by the given display expression, and the preceding and following postings. postingsMatchingDisplayExpr :: Maybe String -> [Posting] -> ([Posting],[Posting],[Posting]) diff --git a/hledger-lib/Hledger/Data/Commodity.hs b/hledger-lib/Hledger/Data/Commodity.hs index b92e21eee..d2cd07bda 100644 --- a/hledger-lib/Hledger/Data/Commodity.hs +++ b/hledger-lib/Hledger/Data/Commodity.hs @@ -10,6 +10,8 @@ module Hledger.Data.Commodity where import Hledger.Data.Utils import Hledger.Data.Types +import qualified Data.Map as Map +import Data.Map ((!)) nonsimplecommoditychars = "0123456789-.@;\n \"" @@ -39,3 +41,16 @@ comm sym = fromMaybe conversionRate :: Commodity -> Commodity -> Double conversionRate _ _ = 1 +-- | Convert a list of commodities to a map from commodity symbols to +-- unique, display-preference-canonicalised commodities. +canonicaliseCommodities :: [Commodity] -> Map.Map String Commodity +canonicaliseCommodities cs = + Map.fromList [(s,firstc{precision=maxp}) | s <- symbols, + let cs = commoditymap ! s, + let firstc = head cs, + let maxp = maximum $ map precision cs + ] + where + commoditymap = Map.fromList [(s, commoditieswithsymbol s) | s <- symbols] + commoditieswithsymbol s = filter ((s==) . symbol) cs + symbols = nub $ map symbol cs diff --git a/hledger-lib/Hledger/Data/Dates.hs b/hledger-lib/Hledger/Data/Dates.hs index 78b5411f5..54cb8f15c 100644 --- a/hledger-lib/Hledger/Data/Dates.hs +++ b/hledger-lib/Hledger/Data/Dates.hs @@ -71,7 +71,20 @@ splitspan start next span@(DateSpan (Just b) (Just e)) daysInSpan :: DateSpan -> Maybe Integer daysInSpan (DateSpan (Just d1) (Just d2)) = Just $ diffDays d2 d1 daysInSpan _ = Nothing + +-- | Does the span include the given date ? +spanContainsDate :: DateSpan -> Day -> Bool +spanContainsDate (DateSpan Nothing Nothing) _ = True +spanContainsDate (DateSpan Nothing (Just e)) d = d < e +spanContainsDate (DateSpan (Just b) Nothing) d = d >= b +spanContainsDate (DateSpan (Just b) (Just e)) d = d >= b && d < e +-- | Combine two datespans, filling any unspecified dates in the first +-- with dates from the second. +orDatesFrom (DateSpan a1 b1) (DateSpan a2 b2) = DateSpan a b + where a = if isJust a1 then a1 else a2 + b = if isJust b1 then b1 else b2 + -- | Parse a period expression to an Interval and overall DateSpan using -- the provided reference date, or raise an error. parsePeriodExpr :: Day -> String -> (Interval, DateSpan) diff --git a/hledger-lib/Hledger/Data/Journal.hs b/hledger-lib/Hledger/Data/Journal.hs index cde7db1db..7818bd4c5 100644 --- a/hledger-lib/Hledger/Data/Journal.hs +++ b/hledger-lib/Hledger/Data/Journal.hs @@ -15,6 +15,7 @@ import Hledger.Data.Utils import Hledger.Data.Types import Hledger.Data.AccountName import Hledger.Data.Amount +import Hledger.Data.Commodity (canonicaliseCommodities) import Hledger.Data.Dates (nulldatespan) import Hledger.Data.Transaction (journalTransactionWithDate) import Hledger.Data.Posting @@ -268,17 +269,7 @@ journalConvertAmountsToCost j@Journal{jtxns=ts} = j{jtxns=map fixtransaction ts} -- | Get this journal's unique, display-preference-canonicalised commodities, by symbol. journalCanonicalCommodities :: Journal -> Map.Map String Commodity -journalCanonicalCommodities j = - Map.fromList [(s,firstc{precision=maxp}) | s <- commoditysymbols, - let cs = commoditymap ! s, - let firstc = head cs, - let maxp = maximum $ map precision cs - ] - where - commoditymap = Map.fromList [(s,commoditieswithsymbol s) | s <- commoditysymbols] - commoditieswithsymbol s = filter ((s==) . symbol) commodities - commoditysymbols = nub $ map symbol commodities - commodities = journalAmountAndPriceCommodities j +journalCanonicalCommodities j = canonicaliseCommodities $ journalAmountAndPriceCommodities j -- | Get all this journal's amounts' commodities, in the order parsed. journalAmountCommodities :: Journal -> [Commodity] diff --git a/hledger-lib/Hledger/Data/Posting.hs b/hledger-lib/Hledger/Data/Posting.hs index 1343ceab9..5577a9163 100644 --- a/hledger-lib/Hledger/Data/Posting.hs +++ b/hledger-lib/Hledger/Data/Posting.hs @@ -14,7 +14,7 @@ import Hledger.Data.Utils import Hledger.Data.Types import Hledger.Data.Amount import Hledger.Data.AccountName -import Hledger.Data.Dates (nulldate) +import Hledger.Data.Dates (nulldate, spanContainsDate) instance Show Posting where show = showPosting @@ -79,10 +79,7 @@ postingCleared p = maybe False tstatus $ ptransaction p -- | Does this posting fall within the given date span ? isPostingInDateSpan :: DateSpan -> Posting -> Bool -isPostingInDateSpan (DateSpan Nothing Nothing) _ = True -isPostingInDateSpan (DateSpan Nothing (Just e)) p = postingDate p < e -isPostingInDateSpan (DateSpan (Just b) Nothing) p = postingDate p >= b -isPostingInDateSpan (DateSpan (Just b) (Just e)) p = d >= b && d < e where d = postingDate p +isPostingInDateSpan s = spanContainsDate s . postingDate isEmptyPosting :: Posting -> Bool isEmptyPosting = isZeroMixedAmount . pamount