fix: cost: Add inferred equity postings during journal finalisation, so
they can be matched by queries.
This commit is contained in:
		
							parent
							
								
									f7a3f510be
								
							
						
					
					
						commit
						57d055b643
					
				| @ -24,6 +24,7 @@ module Hledger.Data.Journal ( | ||||
|   commodityStylesFromAmounts, | ||||
|   journalCommodityStyles, | ||||
|   journalToCost, | ||||
|   journalAddInferredEquityPostings, | ||||
|   journalReverse, | ||||
|   journalSetLastReadTime, | ||||
|   journalPivot, | ||||
| @ -881,11 +882,16 @@ postingInferredmarketPrice p@Posting{pamount} = | ||||
| -- | Convert all this journal's amounts to cost using the transaction prices, if any. | ||||
| -- The journal's commodity styles are applied to the resulting amounts. | ||||
| journalToCost :: ConversionOp -> Journal -> Journal | ||||
| journalToCost cost j@Journal{jtxns=ts} = | ||||
|     j{jtxns=map (transactionToCost (journalConversionAccount j) styles cost) ts} | ||||
| journalToCost cost j@Journal{jtxns=ts} = j{jtxns=map (transactionToCost styles cost) ts} | ||||
|   where | ||||
|     styles = journalCommodityStyles j | ||||
| 
 | ||||
| -- | Add inferred equity postings to a 'Journal' using transaction prices. | ||||
| journalAddInferredEquityPostings :: Journal -> Journal | ||||
| journalAddInferredEquityPostings j = journalMapTransactions (transactionAddInferredEquityPostings equityAcct) j | ||||
|   where | ||||
|     equityAcct = journalConversionAccount j | ||||
| 
 | ||||
| -- -- | Get this journal's unique, display-preference-canonicalised commodities, by symbol. | ||||
| -- journalCanonicalCommodities :: Journal -> M.Map String CommoditySymbol | ||||
| -- journalCanonicalCommodities j = canonicaliseCommodities $ journalAmountCommodities j | ||||
|  | ||||
| @ -71,6 +71,7 @@ module Hledger.Data.Posting ( | ||||
|   postingTransformAmount, | ||||
|   postingApplyValuation, | ||||
|   postingToCost, | ||||
|   postingAddInferredEquityPostings, | ||||
|   tests_Posting | ||||
| ) | ||||
| where | ||||
| @ -481,12 +482,14 @@ postingApplyValuation priceoracle styles periodlast today v p = | ||||
|     postingTransformAmount (mixedAmountApplyValuation priceoracle styles periodlast today (postingDate p) v) p | ||||
| 
 | ||||
| -- | Maybe convert this 'Posting's amount to cost, and apply apply appropriate | ||||
| -- amount styles; or, in --infer-equity mode, remove its cost price and add an | ||||
| -- appropriate pair of equity postings. | ||||
| postingToCost :: Text -> M.Map CommoditySymbol AmountStyle -> ConversionOp -> Posting -> [Posting] | ||||
| postingToCost _          _      NoConversionOp p = [p] | ||||
| postingToCost _          styles ToCost         p = [postingTransformAmount (styleMixedAmount styles . mixedAmountCost) p] | ||||
| postingToCost equityAcct styles InferEquity    p = taggedPosting : concatMap conversionPostings priceAmounts | ||||
| -- amount styles. | ||||
| postingToCost :: M.Map CommoditySymbol AmountStyle -> ConversionOp -> Posting -> Posting | ||||
| postingToCost _      NoConversionOp p = p | ||||
| postingToCost styles ToCost         p = postingTransformAmount (styleMixedAmount styles . mixedAmountCost) p | ||||
| 
 | ||||
| -- | Generate inferred equity postings from a 'Posting' using transaction prices. | ||||
| postingAddInferredEquityPostings :: Text -> Posting -> [Posting] | ||||
| postingAddInferredEquityPostings equityAcct p = taggedPosting : concatMap conversionPostings priceAmounts | ||||
|   where | ||||
|     taggedPosting | ||||
|       | null priceAmounts = p | ||||
| @ -499,7 +502,7 @@ postingToCost equityAcct styles InferEquity    p = taggedPosting : concatMap con | ||||
|                        , pamount = mixedAmount . negate $ amountStripPrices amt | ||||
|                        } | ||||
|                    , cp{ paccount = accountPrefix <> costCommodity | ||||
|                        , pamount = styleMixedAmount styles $ mixedAmount cost | ||||
|                        , pamount = mixedAmount cost | ||||
|                        } | ||||
|                    ] | ||||
|       where | ||||
|  | ||||
| @ -27,6 +27,7 @@ module Hledger.Data.Transaction | ||||
| , transactionTransformPostings | ||||
| , transactionApplyValuation | ||||
| , transactionToCost | ||||
| , transactionAddInferredEquityPostings | ||||
| , transactionApplyAliases | ||||
| , transactionMapPostings | ||||
| , transactionMapPostingAmounts | ||||
| @ -203,10 +204,14 @@ transactionApplyValuation priceoracle styles periodlast today v = | ||||
|   transactionTransformPostings (postingApplyValuation priceoracle styles periodlast today v) | ||||
| 
 | ||||
| -- | Maybe convert this 'Transaction's amounts to cost and apply the | ||||
| -- appropriate amount styles; or in --infer-equity mode, replace any | ||||
| -- transaction prices by a pair of equity postings. | ||||
| transactionToCost :: Text -> M.Map CommoditySymbol AmountStyle -> ConversionOp -> Transaction -> Transaction | ||||
| transactionToCost equityAcct styles cost t = t{tpostings=concatMap (postingToCost equityAcct styles cost) $ tpostings t} | ||||
| -- appropriate amount styles. | ||||
| transactionToCost :: M.Map CommoditySymbol AmountStyle -> ConversionOp -> Transaction -> Transaction | ||||
| transactionToCost styles cost = transactionMapPostings (postingToCost styles cost) | ||||
| 
 | ||||
| -- | Add inferred equity postings to a 'Transaction' using transaction prices. | ||||
| transactionAddInferredEquityPostings :: AccountName -> Transaction -> Transaction | ||||
| transactionAddInferredEquityPostings equityAcct t = | ||||
|     t{tpostings=concatMap (postingAddInferredEquityPostings equityAcct) $ tpostings t} | ||||
| 
 | ||||
| -- | Apply some account aliases to all posting account names in the transaction, as described by accountNameApplyAliases. | ||||
| -- This can fail due to a bad replacement pattern in a regular expression alias. | ||||
|  | ||||
| @ -52,7 +52,7 @@ import Text.Printf (printf) | ||||
| -- Types | ||||
| 
 | ||||
| -- | Which operation to perform on conversion transactions. | ||||
| data ConversionOp = NoConversionOp | InferEquity | ToCost | ||||
| data ConversionOp = NoConversionOp | ToCost | ||||
|   deriving (Show,Eq) | ||||
| 
 | ||||
| -- | What kind of value conversion should be done on amounts ? | ||||
| @ -111,7 +111,6 @@ mixedAmountApplyValuation priceoracle styles periodlast today postingdate v = | ||||
| -- | Convert an Amount to its cost if requested, and style it appropriately. | ||||
| amountToCost :: M.Map CommoditySymbol AmountStyle -> ConversionOp -> Amount -> Amount | ||||
| amountToCost styles ToCost         = styleAmount styles . amountCost | ||||
| amountToCost _      InferEquity    = amountStripPrices | ||||
| amountToCost _      NoConversionOp = id | ||||
| 
 | ||||
| -- | Apply a specified valuation to this amount, using the provided | ||||
|  | ||||
| @ -213,6 +213,7 @@ rawOptsToInputOpts day rawopts = | ||||
|       ,forecast_          = forecastPeriodFromRawOpts day rawopts | ||||
|       ,reportspan_        = DateSpan (queryStartDate False datequery) (queryEndDate False datequery) | ||||
|       ,auto_              = boolopt "auto" rawopts | ||||
|       ,infer_equity_      = boolopt "infer-equity" rawopts && not (conversionop_ ropts == Just ToCost) | ||||
|       ,balancingopts_     = defbalancingopts{ | ||||
|                                  ignore_assertions_ = boolopt "ignore-assertions" rawopts | ||||
|                                , infer_transaction_prices_ = not noinferprice | ||||
| @ -302,7 +303,7 @@ parseAndFinaliseJournal' parser iopts f txt = do | ||||
| -- - infer transaction-implied market prices from transaction prices | ||||
| -- | ||||
| journalFinalise :: InputOpts -> FilePath -> Text -> ParsedJournal -> ExceptT String IO Journal | ||||
| journalFinalise iopts@InputOpts{auto_,balancingopts_,strict_} f txt pj = do | ||||
| journalFinalise iopts@InputOpts{auto_,infer_equity_,balancingopts_,strict_} f txt pj = do | ||||
|     t <- liftIO getPOSIXTime | ||||
|     -- Infer and apply canonical styles for each commodity (or throw an error). | ||||
|     -- This affects transaction balancing/assertions/assignments, so needs to be done early. | ||||
| @ -325,6 +326,8 @@ journalFinalise iopts@InputOpts{auto_,balancingopts_,strict_} f txt pj = do | ||||
|           & (if auto_ && not (null $ jtxnmodifiers j) then journalAddAutoPostings d balancingopts_ else pure) | ||||
|         -- Balance all transactions and maybe check balance assertions. | ||||
|           >>= journalBalanceTransactions balancingopts_ | ||||
|         -- Add inferred equity postings, after balancing transactions and generating auto postings | ||||
|           <&> (if infer_equity_ then journalAddInferredEquityPostings else id) | ||||
|         -- infer market prices from commodity-exchanging transactions | ||||
|           <&> journalInferMarketPricesFromTransactions | ||||
| 
 | ||||
|  | ||||
| @ -36,6 +36,7 @@ data InputOpts = InputOpts { | ||||
|     ,forecast_          :: Maybe DateSpan       -- ^ span in which to generate forecast transactions | ||||
|     ,reportspan_        :: DateSpan             -- ^ a dirty hack keeping the query dates in InputOpts. This rightfully lives in ReportSpec, but is duplicated here. | ||||
|     ,auto_              :: Bool                 -- ^ generate automatic postings when journal is parsed | ||||
|     ,infer_equity_      :: Bool                 -- ^ generate automatic equity postings from transaction prices | ||||
|     ,balancingopts_     :: BalancingOpts        -- ^ options for balancing transactions | ||||
|     ,strict_            :: Bool                 -- ^ do extra error checking (eg, all posted accounts are declared, no prices are inferred) | ||||
|     ,_ioDay             :: Day                  -- ^ today's date, for use with forecast transactions  XXX this duplicates _rsDay, and should eventually be removed when it's not needed anymore. | ||||
| @ -53,6 +54,7 @@ definputopts = InputOpts | ||||
|     , forecast_          = Nothing | ||||
|     , reportspan_        = nulldatespan | ||||
|     , auto_              = False | ||||
|     , infer_equity_      = False | ||||
|     , balancingopts_     = defbalancingopts | ||||
|     , strict_            = False | ||||
|     , _ioDay             = nulldate | ||||
|  | ||||
| @ -515,7 +515,6 @@ valuationTypeFromRawOpts rawopts = case (balancecalcopt rawopts, directval) of | ||||
| conversionOpFromRawOpts :: RawOpts -> Maybe ConversionOp | ||||
| conversionOpFromRawOpts rawopts | ||||
|     | isJust costFlag && balancecalcopt rawopts == CalcGain = usageError "--gain cannot be combined with --cost" | ||||
|     | boolopt "infer-equity" rawopts = costFlag <|> Just InferEquity | ||||
|     | otherwise = costFlag | ||||
|   where | ||||
|     costFlag = lastMay $ collectopts conversionopfromrawopt rawopts | ||||
| @ -619,7 +618,6 @@ mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle = | ||||
|     gain mc span = mixedAmountGainAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span) | ||||
|     costing = case fromMaybe NoConversionOp $ conversionop_ ropts of | ||||
|         NoConversionOp -> id | ||||
|         InferEquity    -> mixedAmountStripPrices | ||||
|         ToCost         -> styleMixedAmount styles . mixedAmountCost | ||||
|     styles = journalCommodityStyles j | ||||
|     err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date" | ||||
|  | ||||
| @ -65,7 +65,7 @@ showTxn :: ReportOpts -> ReportSpec -> Journal -> Transaction -> T.Text | ||||
| showTxn ropts rspec j t = | ||||
|       showTransactionOneLineAmounts | ||||
|     $ maybe id (transactionApplyValuation prices styles periodlast (_rsDay rspec)) (value_ ropts) | ||||
|     $ maybe id (transactionToCost (journalConversionAccount j) styles) (conversionop_ ropts) t | ||||
|     $ maybe id (transactionToCost styles) (conversionop_ ropts) t | ||||
|     -- (if real_ ropts then filterTransactionPostings (Real True) else id) -- filter postings by --real | ||||
|   where | ||||
|     prices = journalPriceOracle (infer_prices_ ropts) j | ||||
|  | ||||
| @ -102,7 +102,6 @@ toggleConversionOp = over conversionop toggleCostMode | ||||
|   where | ||||
|     toggleCostMode Nothing               = Just ToCost | ||||
|     toggleCostMode (Just NoConversionOp) = Just ToCost | ||||
|     toggleCostMode (Just InferEquity)    = Just ToCost | ||||
|     toggleCostMode (Just ToCost)         = Just NoConversionOp | ||||
| 
 | ||||
| -- | Toggle between showing primary amounts or default valuation. | ||||
|  | ||||
| @ -72,7 +72,7 @@ close CliOpts{rawopts_=rawopts, reportspec_=rspec'} j = do | ||||
|         (Nothing, Nothing) -> (T.pack defclosingacct, T.pack defopeningacct) | ||||
| 
 | ||||
|     ropts = (_rsReportOpts rspec'){balanceaccum_=Historical, accountlistmode_=ALFlat} | ||||
|     rspec = setDefaultConversionOp (if show_costs then NoConversionOp else InferEquity) rspec'{_rsReportOpts=ropts} | ||||
|     rspec = setDefaultConversionOp NoConversionOp rspec'{_rsReportOpts=ropts} | ||||
| 
 | ||||
|     -- dates of the closing and opening transactions | ||||
|     -- | ||||
|  | ||||
| @ -89,7 +89,7 @@ entriesReportAsText opts = | ||||
|       | otherwise = originalTransaction | ||||
|     maybeStripPrices | ||||
|       -- Strip prices when inferring equity, unless the show-costs option is set | ||||
|       | opts ^. conversionop == Just InferEquity && not (boolopt "show-costs" $ rawopts_ opts) = | ||||
|       | opts ^. infer_equity && not (boolopt "show-costs" $ rawopts_ opts) = | ||||
|           transactionTransformPostings postingStripPrices | ||||
|       | otherwise = id | ||||
| 
 | ||||
|  | ||||
| @ -343,6 +343,18 @@ account  equity:trades   V | ||||
| 
 | ||||
| >>>=0 | ||||
| 
 | ||||
| # 28. Inferred equity postings are generated early enough to match filters | ||||
| hledger -f- areg --infer-equity equity:conversion | ||||
| <<< | ||||
| 2011/01/01 | ||||
|     expenses:foreign currency       €100 @ $1.35 | ||||
|     assets | ||||
| >>> | ||||
| Transactions in equity:conversion and subaccounts: | ||||
| 2011-01-01                      ex:foreign currenc..       $135.00       $135.00 | ||||
|                                                              €-100         €-100 | ||||
| >>>=0 | ||||
| 
 | ||||
| # # when the *cost-basis* balance has exactly two commodities, both | ||||
| # # unpriced, infer an implicit conversion price for the first one in terms | ||||
| # # of the second. | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user