rename historical prices to market prices
Simpler and clearer. We now have "transaction prices" (recorded as part of transaction amounts) and "market prices" (recorded with P directives). Both are matters of historical record, also this avoids confusion with the balance command's "historical balances".
This commit is contained in:
		
							parent
							
								
									49be1f646e
								
							
						
					
					
						commit
						94094252be
					
				| @ -626,10 +626,10 @@ note bottom of Account: An account's name, balance (inclusive &\nexclusive), par | ||||
| Account o-- "*" Account :subaccounts, parent | ||||
| Journal o-- File | ||||
| File o-- "*" File :include | ||||
| Journal *-- "*" HistoricalPrice | ||||
| Journal *-- "*" MarketPrice | ||||
| Journal *-- "*" Transaction | ||||
| HistoricalPrice -- Date | ||||
| HistoricalPrice -- Amount | ||||
| MarketPrice -- Date | ||||
| MarketPrice -- Amount | ||||
| Transaction -- Date | ||||
| Transaction *-- "*" Posting | ||||
| Transaction o-- "*" Tag | ||||
|  | ||||
| @ -492,12 +492,12 @@ Ledger has a different syntax for specifying | ||||
| hledger parses that syntax, and (currently) ignores it. | ||||
| <!-- hledger treats this as an alternate spelling of `@ PRICE`, for greater compatibility with Ledger files. --> | ||||
| 
 | ||||
| ##### Historical prices | ||||
| ##### Market prices | ||||
| 
 | ||||
| hledger also parses, and currently ignores, ledger-style historical price directives: | ||||
| hledger also parses, and currently ignores, ledger-style historical price directives (which we call market prices): | ||||
| <!-- (A time and numeric time zone are allowed but ignored, like ledger.) --> | ||||
| ```journal | ||||
| ; Historical price directives look like: P DATE COMMODITYSYMBOL UNITPRICE | ||||
| ; Market price directives look like: P DATE COMMODITYSYMBOL UNITPRICE | ||||
| ; These say the euro's exchange rate is $1.35 during 2009 and | ||||
| ; $1.40 from 2010/1/1 on. | ||||
| P 2009/1/1 € $1.35 | ||||
|  | ||||
| @ -118,7 +118,7 @@ import Hledger.Data.Commodity | ||||
| import Hledger.Utils | ||||
| 
 | ||||
| 
 | ||||
| deriving instance Show HistoricalPrice | ||||
| deriving instance Show MarketPrice | ||||
| 
 | ||||
| amountstyle = AmountStyle L False 0 (Just '.') Nothing | ||||
| 
 | ||||
|  | ||||
| @ -9,7 +9,7 @@ other data format (see "Hledger.Read"). | ||||
| 
 | ||||
| module Hledger.Data.Journal ( | ||||
|   -- * Parsing helpers | ||||
|   addHistoricalPrice, | ||||
|   addMarketPrice, | ||||
|   addModifierTransaction, | ||||
|   addPeriodicTransaction, | ||||
|   addTimeLogEntry, | ||||
| @ -114,7 +114,7 @@ instance Show Journal where | ||||
| --                      ,show (jmodifiertxns j) | ||||
| --                      ,show (jperiodictxns j) | ||||
| --                      ,show $ open_timelog_entries j | ||||
| --                      ,show $ historical_prices j | ||||
| --                      ,show $ jmarketprices j | ||||
| --                      ,show $ final_comment_lines j | ||||
| --                      ,show $ jContext j | ||||
| --                      ,show $ map fst $ files j | ||||
| @ -125,7 +125,7 @@ nulljournal = Journal { jmodifiertxns = [] | ||||
|                       , jperiodictxns = [] | ||||
|                       , jtxns = [] | ||||
|                       , open_timelog_entries = [] | ||||
|                       , historical_prices = [] | ||||
|                       , jmarketprices = [] | ||||
|                       , final_comment_lines = [] | ||||
|                       , jContext = nullctx | ||||
|                       , files = [] | ||||
| @ -154,8 +154,8 @@ addModifierTransaction mt j = j { jmodifiertxns = mt : jmodifiertxns j } | ||||
| addPeriodicTransaction :: PeriodicTransaction -> Journal -> Journal | ||||
| addPeriodicTransaction pt j = j { jperiodictxns = pt : jperiodictxns j } | ||||
| 
 | ||||
| addHistoricalPrice :: HistoricalPrice -> Journal -> Journal | ||||
| addHistoricalPrice h j = j { historical_prices = h : historical_prices j } | ||||
| addMarketPrice :: MarketPrice -> Journal -> Journal | ||||
| addMarketPrice h j = j { jmarketprices = h : jmarketprices j } | ||||
| 
 | ||||
| addTimeLogEntry :: TimeLogEntry -> Journal -> Journal | ||||
| addTimeLogEntry tle j = j { open_timelog_entries = tle : open_timelog_entries j } | ||||
| @ -411,7 +411,7 @@ journalFinalise tclock tlocal path txt ctx assrt j@Journal{files=fs} = do | ||||
|      , jtxns=reverse $ jtxns j -- NOTE: see addTransaction | ||||
|      , jmodifiertxns=reverse $ jmodifiertxns j -- NOTE: see addModifierTransaction | ||||
|      , jperiodictxns=reverse $ jperiodictxns j -- NOTE: see addPeriodicTransaction | ||||
|      , historical_prices=reverse $ historical_prices j -- NOTE: see addHistoricalPrice | ||||
|      , jmarketprices=reverse $ jmarketprices j -- NOTE: see addMarketPrice | ||||
|      , open_timelog_entries=reverse $ open_timelog_entries j -- NOTE: see addTimeLogEntry | ||||
|      }) | ||||
|   >>= if assrt then journalCheckBalanceAssertions else return | ||||
| @ -493,13 +493,13 @@ journalBalanceTransactions j@Journal{jtxns=ts, jcommoditystyles=ss} = | ||||
| -- will use (a) the display settings of the first, and (b) the | ||||
| -- greatest precision, of the posting amounts in that commodity. | ||||
| journalCanonicaliseAmounts :: Journal -> Journal | ||||
| journalCanonicaliseAmounts j@Journal{jtxns=ts, historical_prices=hps} = j'' | ||||
| journalCanonicaliseAmounts j@Journal{jtxns=ts, jmarketprices=mps} = j'' | ||||
|     where | ||||
|       j'' = j'{jtxns=map fixtransaction ts, historical_prices=map fixhistoricalprice hps} | ||||
|       j'' = j'{jtxns=map fixtransaction ts, jmarketprices=map fixmarketprice mps} | ||||
|       j' = j{jcommoditystyles = canonicalStyles $ dbg8 "journalAmounts" $ journalAmounts j} | ||||
|       fixtransaction t@Transaction{tpostings=ps} = t{tpostings=map fixposting ps} | ||||
|       fixposting p@Posting{pamount=a} = p{pamount=fixmixedamount a} | ||||
|       fixhistoricalprice hp@HistoricalPrice{hamount=a} = hp{hamount=fixamount a} | ||||
|       fixmarketprice mp@MarketPrice{mpamount=a} = mp{mpamount=fixamount a} | ||||
|       fixmixedamount (Mixed as) = Mixed $ map fixamount as | ||||
|       fixamount a@Amount{acommodity=c} = a{astyle=journalCommodityStyle j' c} | ||||
| 
 | ||||
| @ -530,8 +530,8 @@ journalCommodityStyle :: Journal -> Commodity -> AmountStyle | ||||
| journalCommodityStyle j c = M.findWithDefault amountstyle c $ jcommoditystyles j | ||||
| 
 | ||||
| -- -- | Apply this journal's historical price records to unpriced amounts where possible. | ||||
| -- journalApplyHistoricalPrices :: Journal -> Journal | ||||
| -- journalApplyHistoricalPrices j@Journal{jtxns=ts} = j{jtxns=map fixtransaction ts} | ||||
| -- journalApplyMarketPrices :: Journal -> Journal | ||||
| -- journalApplyMarketPrices j@Journal{jtxns=ts} = j{jtxns=map fixtransaction ts} | ||||
| --     where | ||||
| --       fixtransaction t@Transaction{tdate=d, tpostings=ps} = t{tpostings=map fixposting ps} | ||||
| --        where | ||||
| @ -539,14 +539,14 @@ journalCommodityStyle j c = M.findWithDefault amountstyle c $ jcommoditystyles j | ||||
| --         fixmixedamount (Mixed as) = Mixed $ map fixamount as | ||||
| --         fixamount = fixprice | ||||
| --         fixprice a@Amount{price=Just _} = a | ||||
| --         fixprice a@Amount{commodity=c} = a{price=maybe Nothing (Just . UnitPrice) $ journalHistoricalPriceFor j d c} | ||||
| --         fixprice a@Amount{commodity=c} = a{price=maybe Nothing (Just . UnitPrice) $ journalMarketPriceFor j d c} | ||||
| 
 | ||||
| -- -- | Get the price for a commodity on the specified day from the price database, if known. | ||||
| -- -- Does only one lookup step, ie will not look up the price of a price. | ||||
| -- journalHistoricalPriceFor :: Journal -> Day -> Commodity -> Maybe MixedAmount | ||||
| -- journalHistoricalPriceFor j d Commodity{symbol=s} = do | ||||
| --   let ps = reverse $ filter ((<= d).hdate) $ filter ((s==).hsymbol) $ sortBy (comparing hdate) $ historical_prices j | ||||
| --   case ps of (HistoricalPrice{hamount=a}:_) -> Just a | ||||
| -- journalMarketPriceFor :: Journal -> Day -> Commodity -> Maybe MixedAmount | ||||
| -- journalMarketPriceFor j d Commodity{symbol=s} = do | ||||
| --   let ps = reverse $ filter ((<= d).mpdate) $ filter ((s==).hsymbol) $ sortBy (comparing mpdate) $ jmarketprices j | ||||
| --   case ps of (MarketPrice{mpamount=a}:_) -> Just a | ||||
| --              _ -> Nothing | ||||
| 
 | ||||
| -- | Close any open timelog sessions in this journal using the provided current time. | ||||
|  | ||||
| @ -7,7 +7,7 @@ Here is an overview of the hledger data model: | ||||
| > Journal                  -- a journal is read from one or more data files. It contains.. | ||||
| >  [Transaction]           -- journal transactions (aka entries), which have date, cleared status, code, description and.. | ||||
| >   [Posting]              -- multiple account postings, which have account name and amount | ||||
| >  [HistoricalPrice]       -- historical commodity prices | ||||
| >  [MarketPrice]           -- historical market prices for commodities | ||||
| > | ||||
| > Ledger                   -- a ledger is derived from a journal, by applying a filter specification and doing some further processing. It contains.. | ||||
| >  Journal                 -- a filtered copy of the original journal, containing only the transactions and postings we are interested in | ||||
| @ -176,10 +176,10 @@ data TimeLogEntry = TimeLogEntry { | ||||
|       tldescription :: String | ||||
|     } deriving (Eq,Ord,Typeable,Data) | ||||
| 
 | ||||
| data HistoricalPrice = HistoricalPrice { | ||||
|       hdate :: Day, | ||||
|       hcommodity :: Commodity, | ||||
|       hamount :: Amount | ||||
| data MarketPrice = MarketPrice { | ||||
|       mpdate :: Day, | ||||
|       mpcommodity :: Commodity, | ||||
|       mpamount :: Amount | ||||
|     } deriving (Eq,Ord,Typeable,Data) -- & Show (in Amount.hs) | ||||
| 
 | ||||
| type Year = Integer | ||||
| @ -205,7 +205,7 @@ data Journal = Journal { | ||||
|       jperiodictxns :: [PeriodicTransaction], | ||||
|       jtxns :: [Transaction], | ||||
|       open_timelog_entries :: [TimeLogEntry], | ||||
|       historical_prices :: [HistoricalPrice], | ||||
|       jmarketprices :: [MarketPrice], | ||||
|       final_comment_lines :: String,        -- ^ any trailing comments from the journal file | ||||
|       jContext :: JournalContext,           -- ^ the context (parse state) at the end of parsing | ||||
|       files :: [(FilePath, String)],        -- ^ the file path and raw text of the main and | ||||
|  | ||||
| @ -26,7 +26,7 @@ module Hledger.Read.JournalReader ( | ||||
|   journal, | ||||
|   directive, | ||||
|   defaultyeardirective, | ||||
|   historicalpricedirective, | ||||
|   marketpricedirective, | ||||
|   datetimep, | ||||
|   codep, | ||||
|   accountnamep, | ||||
| @ -170,7 +170,7 @@ journal = do | ||||
|                            , liftM (return . addTransaction) transaction | ||||
|                            , liftM (return . addModifierTransaction) modifiertransaction | ||||
|                            , liftM (return . addPeriodicTransaction) periodictransaction | ||||
|                            , liftM (return . addHistoricalPrice) historicalpricedirective | ||||
|                            , liftM (return . addMarketPrice) marketpricedirective | ||||
|                            , emptyorcommentlinep >> return (return id) | ||||
|                            , multilinecommentp >> return (return id) | ||||
|                            ] <?> "journal transaction or directive" | ||||
| @ -314,9 +314,9 @@ defaultcommoditydirective = do | ||||
|   restofline | ||||
|   return $ return id | ||||
| 
 | ||||
| historicalpricedirective :: ParsecT [Char] JournalContext (ExceptT String IO) HistoricalPrice | ||||
| historicalpricedirective = do | ||||
|   char 'P' <?> "historical price" | ||||
| marketpricedirective :: ParsecT [Char] JournalContext (ExceptT String IO) MarketPrice | ||||
| marketpricedirective = do | ||||
|   char 'P' <?> "market price" | ||||
|   many spacenonewline | ||||
|   date <- try (do {LocalTime d _ <- datetimep; return d}) <|> datep -- a time is ignored | ||||
|   many1 spacenonewline | ||||
| @ -324,7 +324,7 @@ historicalpricedirective = do | ||||
|   many spacenonewline | ||||
|   price <- amountp | ||||
|   restofline | ||||
|   return $ HistoricalPrice date symbol price | ||||
|   return $ MarketPrice date symbol price | ||||
| 
 | ||||
| ignoredpricecommoditydirective :: ParsecT [Char] JournalContext (ExceptT String IO) JournalUpdate | ||||
| ignoredpricecommoditydirective = do | ||||
| @ -1084,8 +1084,8 @@ tests_Hledger_Read_JournalReader = TestList $ concat [ | ||||
|      assertParse (parseWithCtx nullctx defaultyeardirective "Y 2010\n") | ||||
|      assertParse (parseWithCtx nullctx defaultyeardirective "Y 10001\n") | ||||
| 
 | ||||
|   ,"historicalpricedirective" ~: | ||||
|     assertParseEqual (parseWithCtx nullctx historicalpricedirective "P 2004/05/01 XYZ $55.00\n") (HistoricalPrice (parsedate "2004/05/01") "XYZ" $ usd 55) | ||||
|   ,"marketpricedirective" ~: | ||||
|     assertParseEqual (parseWithCtx nullctx marketpricedirective "P 2004/05/01 XYZ $55.00\n") (MarketPrice (parsedate "2004/05/01") "XYZ" $ usd 55) | ||||
| 
 | ||||
|   ,"ignoredpricecommoditydirective" ~: do | ||||
|      assertParse (parseWithCtx nullctx ignoredpricecommoditydirective "N $\n") | ||||
|  | ||||
| @ -60,7 +60,7 @@ import System.FilePath | ||||
| import Hledger.Data | ||||
| -- XXX too much reuse ? | ||||
| import Hledger.Read.JournalReader ( | ||||
|   directive, historicalpricedirective, defaultyeardirective, emptyorcommentlinep, datetimep, | ||||
|   directive, marketpricedirective, defaultyeardirective, emptyorcommentlinep, datetimep, | ||||
|   parseJournalWith, modifiedaccountname | ||||
|   ) | ||||
| import Hledger.Utils | ||||
| @ -94,7 +94,7 @@ timelogFile = do items <- many timelogItem | ||||
|       -- character, excepting transactions versus empty (blank or | ||||
|       -- comment-only) lines, can use choice w/o try | ||||
|       timelogItem = choice [ directive | ||||
|                           , liftM (return . addHistoricalPrice) historicalpricedirective | ||||
|                           , liftM (return . addMarketPrice) marketpricedirective | ||||
|                           , defaultyeardirective | ||||
|                           , emptyorcommentlinep >> return (return id) | ||||
|                           , liftM (return . addTimeLogEntry)  timelogentry | ||||
|  | ||||
| @ -347,9 +347,9 @@ amountValue j d a = | ||||
| commodityValue :: Journal -> Day -> Commodity -> Maybe Amount | ||||
| commodityValue j d c | ||||
|     | null applicableprices = Nothing | ||||
|     | otherwise             = Just $ hamount $ last applicableprices | ||||
|     | otherwise             = Just $ mpamount $ last applicableprices | ||||
|   where | ||||
|     applicableprices = [p | p <- sort $ historical_prices j, hcommodity p == c, hdate p <= d] | ||||
|     applicableprices = [p | p <- sort $ jmarketprices j, mpcommodity p == c, mpdate p <= d] | ||||
| 
 | ||||
| -- | Find the best commodity to convert to when asked to show the | ||||
| -- market value of this commodity on the given date. That is, the one | ||||
| @ -357,7 +357,7 @@ commodityValue j d c | ||||
| -- mentioned in the most recent applicable historical price directive | ||||
| -- before this date. | ||||
| -- defaultValuationCommodity :: Journal -> Day -> Commodity -> Maybe Commodity | ||||
| -- defaultValuationCommodity j d c = hamount <$> commodityValue j d c | ||||
| -- defaultValuationCommodity j d c = mpamount <$> commodityValue j d c | ||||
| 
 | ||||
| -- | Render a single-column balance report as CSV. | ||||
| balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user