"This implements Tier 1 of #1353 (https://github.com/simonmichael/hledger/issues/1353#issuecomment-762623077), minus the mockups of the documentation for Tier 1.1."
This commit is contained in:
		
						commit
						3429601750
					
				| @ -615,7 +615,7 @@ mapMixedAmount f (Mixed as) = Mixed $ map f as | |||||||
| -- | Convert all component amounts to cost/selling price where | -- | Convert all component amounts to cost/selling price where | ||||||
| -- possible (see amountCost). | -- possible (see amountCost). | ||||||
| mixedAmountCost :: MixedAmount -> MixedAmount | mixedAmountCost :: MixedAmount -> MixedAmount | ||||||
| mixedAmountCost (Mixed as) = Mixed $ map amountCost as | mixedAmountCost = mapMixedAmount amountCost | ||||||
| 
 | 
 | ||||||
| -- | Divide a mixed amount's quantities by a constant. | -- | Divide a mixed amount's quantities by a constant. | ||||||
| divideMixedAmount :: Quantity -> MixedAmount -> MixedAmount | divideMixedAmount :: Quantity -> MixedAmount -> MixedAmount | ||||||
| @ -671,7 +671,7 @@ mixedAmountIsZero = all amountIsZero . amounts . normaliseMixedAmountSquashPrice | |||||||
| -- | Given a map of standard commodity display styles, apply the | -- | Given a map of standard commodity display styles, apply the | ||||||
| -- appropriate one to each individual amount. | -- appropriate one to each individual amount. | ||||||
| styleMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount | styleMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount | ||||||
| styleMixedAmount styles (Mixed as) = Mixed $ map (styleAmount styles) as | styleMixedAmount styles = mapMixedAmount (styleAmount styles) | ||||||
| 
 | 
 | ||||||
| -- | Reset each individual amount's display style to the default. | -- | Reset each individual amount's display style to the default. | ||||||
| mixedAmountUnstyled :: MixedAmount -> MixedAmount | mixedAmountUnstyled :: MixedAmount -> MixedAmount | ||||||
| @ -842,20 +842,20 @@ ltraceamount s = traceWith (((s ++ ": ") ++).showMixedAmount) | |||||||
| 
 | 
 | ||||||
| -- | Set the display precision in the amount's commodities. | -- | Set the display precision in the amount's commodities. | ||||||
| setMixedAmountPrecision :: AmountPrecision -> MixedAmount -> MixedAmount | setMixedAmountPrecision :: AmountPrecision -> MixedAmount -> MixedAmount | ||||||
| setMixedAmountPrecision p (Mixed as) = Mixed $ map (setAmountPrecision p) as | setMixedAmountPrecision p = mapMixedAmount (setAmountPrecision p) | ||||||
| 
 | 
 | ||||||
| mixedAmountStripPrices :: MixedAmount -> MixedAmount | mixedAmountStripPrices :: MixedAmount -> MixedAmount | ||||||
| mixedAmountStripPrices (Mixed as) = Mixed $ map (\a -> a{aprice=Nothing}) as | mixedAmountStripPrices = mapMixedAmount (\a -> a{aprice=Nothing}) | ||||||
| 
 | 
 | ||||||
| -- | Canonicalise a mixed amount's display styles using the provided commodity style map. | -- | Canonicalise a mixed amount's display styles using the provided commodity style map. | ||||||
| canonicaliseMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount | canonicaliseMixedAmount :: M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount | ||||||
| canonicaliseMixedAmount styles (Mixed as) = Mixed $ map (canonicaliseAmount styles) as | canonicaliseMixedAmount styles = mapMixedAmount (canonicaliseAmount styles) | ||||||
| 
 | 
 | ||||||
| -- | Replace each component amount's TotalPrice, if it has one, with an equivalent UnitPrice. | -- | Replace each component amount's TotalPrice, if it has one, with an equivalent UnitPrice. | ||||||
| -- Has no effect on amounts without one. | -- Has no effect on amounts without one. | ||||||
| -- Does Decimal division, might be some rounding/irrational number issues. | -- Does Decimal division, might be some rounding/irrational number issues. | ||||||
| mixedAmountTotalPriceToUnitPrice :: MixedAmount -> MixedAmount | mixedAmountTotalPriceToUnitPrice :: MixedAmount -> MixedAmount | ||||||
| mixedAmountTotalPriceToUnitPrice (Mixed as) = Mixed $ map amountTotalPriceToUnitPrice as | mixedAmountTotalPriceToUnitPrice = mapMixedAmount amountTotalPriceToUnitPrice | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| ------------------------------------------------------------------------------- | ------------------------------------------------------------------------------- | ||||||
|  | |||||||
| @ -64,6 +64,7 @@ module Hledger.Data.Posting ( | |||||||
|   -- * misc. |   -- * misc. | ||||||
|   showComment, |   showComment, | ||||||
|   postingTransformAmount, |   postingTransformAmount, | ||||||
|  |   postingApplyCostValuation, | ||||||
|   postingApplyValuation, |   postingApplyValuation, | ||||||
|   postingToCost, |   postingToCost, | ||||||
|   tests_Posting |   tests_Posting | ||||||
| @ -330,17 +331,24 @@ aliasReplace (BasicAlias old new) a | |||||||
| aliasReplace (RegexAlias re repl) a = | aliasReplace (RegexAlias re repl) a = | ||||||
|   fmap T.pack . regexReplace re repl $ T.unpack a -- XXX |   fmap T.pack . regexReplace re repl $ T.unpack a -- XXX | ||||||
| 
 | 
 | ||||||
|  | -- | Apply a specified costing and valuation to this posting's amount, | ||||||
|  | -- using the provided price oracle, commodity styles, and reference dates. | ||||||
|  | -- Costing is done first if requested, and after that any valuation. | ||||||
|  | -- See amountApplyValuation and amountCost. | ||||||
|  | postingApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Costing -> Maybe ValuationType -> Posting -> Posting | ||||||
|  | postingApplyCostValuation priceoracle styles periodlast today cost v p = | ||||||
|  |     postingTransformAmount (mixedAmountApplyCostValuation priceoracle styles periodlast today (postingDate p) cost v) p | ||||||
|  | 
 | ||||||
| -- | Apply a specified valuation to this posting's amount, using the | -- | Apply a specified valuation to this posting's amount, using the | ||||||
| -- provided price oracle, commodity styles, reference dates, and | -- provided price oracle, commodity styles, and reference dates. | ||||||
| -- whether this is for a multiperiod report or not. See | -- See amountApplyValuation. | ||||||
| -- amountApplyValuation. |  | ||||||
| postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting | postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting | ||||||
| postingApplyValuation priceoracle styles periodlast today v p = | postingApplyValuation priceoracle styles periodlast today v p = | ||||||
|     postingTransformAmount (mixedAmountApplyValuation priceoracle styles periodlast today (postingDate p) v) p |     postingTransformAmount (mixedAmountApplyValuation priceoracle styles periodlast today (postingDate p) v) p | ||||||
| 
 | 
 | ||||||
| -- | Convert this posting's amount to cost, and apply the appropriate amount styles. | -- | Convert this posting's amount to cost, and apply the appropriate amount styles. | ||||||
| postingToCost :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting | postingToCost :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting | ||||||
| postingToCost styles p@Posting{pamount=a} = p{pamount=styleMixedAmount styles $ mixedAmountCost a} | postingToCost styles = postingTransformAmount (styleMixedAmount styles . mixedAmountCost) | ||||||
| 
 | 
 | ||||||
| -- | Apply a transform function to this posting's amount. | -- | Apply a transform function to this posting's amount. | ||||||
| postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting | postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting | ||||||
|  | |||||||
| @ -32,6 +32,7 @@ module Hledger.Data.Transaction ( | |||||||
|   balanceTransaction, |   balanceTransaction, | ||||||
|   balanceTransactionHelper, |   balanceTransactionHelper, | ||||||
|   transactionTransformPostings, |   transactionTransformPostings, | ||||||
|  |   transactionApplyCostValuation, | ||||||
|   transactionApplyValuation, |   transactionApplyValuation, | ||||||
|   transactionToCost, |   transactionToCost, | ||||||
|   transactionApplyAliases, |   transactionApplyAliases, | ||||||
| @ -590,10 +591,16 @@ postingSetTransaction t p = p{ptransaction=Just t} | |||||||
| transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction | transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction | ||||||
| transactionTransformPostings f t@Transaction{tpostings=ps} = t{tpostings=map f ps} | transactionTransformPostings f t@Transaction{tpostings=ps} = t{tpostings=map f ps} | ||||||
| 
 | 
 | ||||||
|  | -- | Apply a specified costing and valuation to this transaction's amounts, | ||||||
|  | -- using the provided price oracle, commodity styles, and reference dates. | ||||||
|  | -- See amountApplyValuation and amountCost. | ||||||
|  | transactionApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Costing -> Maybe ValuationType -> Transaction -> Transaction | ||||||
|  | transactionApplyCostValuation priceoracle styles periodlast today cost v = | ||||||
|  |   transactionTransformPostings (postingApplyCostValuation priceoracle styles periodlast today cost v) | ||||||
|  | 
 | ||||||
| -- | Apply a specified valuation to this transaction's amounts, using | -- | Apply a specified valuation to this transaction's amounts, using | ||||||
| -- the provided price oracle, commodity styles, reference dates, and | -- the provided price oracle, commodity styles, and reference dates. | ||||||
| -- whether this is for a multiperiod report or not. See | -- See amountApplyValuation. | ||||||
| -- amountApplyValuation. |  | ||||||
| transactionApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Transaction -> Transaction | transactionApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Transaction -> Transaction | ||||||
| transactionApplyValuation priceoracle styles periodlast today v = | transactionApplyValuation priceoracle styles periodlast today v = | ||||||
|   transactionTransformPostings (postingApplyValuation priceoracle styles periodlast today v) |   transactionTransformPostings (postingApplyValuation priceoracle styles periodlast today v) | ||||||
|  | |||||||
| @ -13,11 +13,13 @@ looking up historical market prices (exchange rates) between commodities. | |||||||
| {-# LANGUAGE DeriveGeneric #-} | {-# LANGUAGE DeriveGeneric #-} | ||||||
| 
 | 
 | ||||||
| module Hledger.Data.Valuation ( | module Hledger.Data.Valuation ( | ||||||
|    ValuationType(..) |    Costing(..) | ||||||
|  |   ,ValuationType(..) | ||||||
|   ,PriceOracle |   ,PriceOracle | ||||||
|   ,journalPriceOracle |   ,journalPriceOracle | ||||||
|   -- ,amountApplyValuation |   -- ,amountApplyValuation | ||||||
|   -- ,amountValueAtDate |   -- ,amountValueAtDate | ||||||
|  |   ,mixedAmountApplyCostValuation | ||||||
|   ,mixedAmountApplyValuation |   ,mixedAmountApplyValuation | ||||||
|   ,mixedAmountValueAtDate |   ,mixedAmountValueAtDate | ||||||
|   ,marketPriceReverse |   ,marketPriceReverse | ||||||
| @ -51,11 +53,14 @@ import Text.Printf (printf) | |||||||
| ------------------------------------------------------------------------------ | ------------------------------------------------------------------------------ | ||||||
| -- Types | -- Types | ||||||
| 
 | 
 | ||||||
|  | -- | Whether to convert amounts to cost. | ||||||
|  | data Costing = Cost | NoCost | ||||||
|  |   deriving (Show,Eq) | ||||||
|  | 
 | ||||||
| -- | What kind of value conversion should be done on amounts ? | -- | What kind of value conversion should be done on amounts ? | ||||||
| -- CLI: --value=cost|then|end|now|DATE[,COMM] | -- CLI: --value=then|end|now|DATE[,COMM] | ||||||
| data ValuationType = | data ValuationType = | ||||||
|     AtCost     (Maybe CommoditySymbol)  -- ^ convert to cost commodity using transaction prices, then optionally to given commodity using market prices at posting date |     AtThen     (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using market prices at each posting's date | ||||||
|   | AtThen     (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using market prices at each posting's date |  | ||||||
|   | AtEnd      (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using market prices at period end(s) |   | AtEnd      (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using market prices at period end(s) | ||||||
|   | AtNow      (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using current market prices |   | AtNow      (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using current market prices | ||||||
|   | AtDate Day (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using market prices on some date |   | AtDate Day (Maybe CommoditySymbol)  -- ^ convert to default or given valuation commodity, using market prices on some date | ||||||
| @ -94,9 +99,21 @@ priceDirectiveToMarketPrice PriceDirective{..} = | |||||||
| ------------------------------------------------------------------------------ | ------------------------------------------------------------------------------ | ||||||
| -- Converting things to value | -- Converting things to value | ||||||
| 
 | 
 | ||||||
|  | -- | Apply a specified costing and valuation to this mixed amount, | ||||||
|  | -- using the provided price oracle, commodity styles, and reference dates. | ||||||
|  | -- Costing is done first if requested, and after that any valuation. | ||||||
|  | -- See amountApplyValuation and amountCost. | ||||||
|  | mixedAmountApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> Costing -> Maybe ValuationType -> MixedAmount -> MixedAmount | ||||||
|  | mixedAmountApplyCostValuation priceoracle styles periodlast today postingdate cost v = | ||||||
|  |     valuation . costing | ||||||
|  |   where | ||||||
|  |     valuation = maybe id (mixedAmountApplyValuation priceoracle styles periodlast today postingdate) v | ||||||
|  |     costing = case cost of | ||||||
|  |         Cost   -> styleMixedAmount styles . mixedAmountCost | ||||||
|  |         NoCost -> id | ||||||
|  | 
 | ||||||
| -- | Apply a specified valuation to this mixed amount, using the | -- | Apply a specified valuation to this mixed amount, using the | ||||||
| -- provided price oracle, commodity styles, reference dates, and | -- provided price oracle, commodity styles, and reference dates. | ||||||
| -- whether this is for a multiperiod report or not. |  | ||||||
| -- See amountApplyValuation. | -- See amountApplyValuation. | ||||||
| mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount | mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount | ||||||
| mixedAmountApplyValuation priceoracle styles periodlast today postingdate v = | mixedAmountApplyValuation priceoracle styles periodlast today postingdate v = | ||||||
| @ -114,7 +131,7 @@ mixedAmountApplyValuation priceoracle styles periodlast today postingdate v = | |||||||
| -- | -- | ||||||
| -- - a fixed date specified by the ValuationType itself | -- - a fixed date specified by the ValuationType itself | ||||||
| --   (--value=DATE). | --   (--value=DATE). | ||||||
| --  | -- | ||||||
| -- - the provided "period end" date - this is typically the last day | -- - the provided "period end" date - this is typically the last day | ||||||
| --   of a subperiod (--value=end with a multi-period report), or of | --   of a subperiod (--value=end with a multi-period report), or of | ||||||
| --   the specified report period or the journal (--value=end with a | --   the specified report period or the journal (--value=end with a | ||||||
| @ -133,8 +150,6 @@ mixedAmountApplyValuation priceoracle styles periodlast today postingdate v = | |||||||
| amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> Amount -> Amount | amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> Amount -> Amount | ||||||
| amountApplyValuation priceoracle styles periodlast today postingdate v a = | amountApplyValuation priceoracle styles periodlast today postingdate v a = | ||||||
|   case v of |   case v of | ||||||
|     AtCost    Nothing -> styleAmount styles $ amountCost a |  | ||||||
|     AtCost    mc      -> amountValueAtDate priceoracle styles mc periodlast . styleAmount styles $ amountCost a |  | ||||||
|     AtThen    mc      -> amountValueAtDate priceoracle styles mc postingdate a |     AtThen    mc      -> amountValueAtDate priceoracle styles mc postingdate a | ||||||
|     AtEnd     mc      -> amountValueAtDate priceoracle styles mc periodlast a |     AtEnd     mc      -> amountValueAtDate priceoracle styles mc periodlast a | ||||||
|     AtNow     mc      -> amountValueAtDate priceoracle styles mc today a |     AtNow     mc      -> amountValueAtDate priceoracle styles mc today a | ||||||
|  | |||||||
| @ -111,7 +111,7 @@ accountTransactionsReport rspec@ReportSpec{rsOpts=ropts} j reportq thisacctq = i | |||||||
|     periodlast = |     periodlast = | ||||||
|       fromMaybe (error' "journalApplyValuation: expected a non-empty journal") $ -- XXX shouldn't happen |       fromMaybe (error' "journalApplyValuation: expected a non-empty journal") $ -- XXX shouldn't happen | ||||||
|       reportPeriodOrJournalLastDay rspec j |       reportPeriodOrJournalLastDay rspec j | ||||||
|     tval = maybe id (transactionApplyValuation prices styles periodlast (rsToday rspec)) $ value_ ropts |     tval = transactionApplyCostValuation prices styles periodlast (rsToday rspec) (cost_ ropts) $ value_ ropts | ||||||
|     ts4 = |     ts4 = | ||||||
|       ptraceAtWith 5 (("ts4:\n"++).pshowTransactions) $ |       ptraceAtWith 5 (("ts4:\n"++).pshowTransactions) $ | ||||||
|       map tval ts3 |       map tval ts3 | ||||||
|  | |||||||
| @ -226,8 +226,10 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $ | |||||||
|         (textCell TopLeft) (textCell TopRight) (uncurry showcell) displayTableWithWidths |         (textCell TopLeft) (textCell TopRight) (uncurry showcell) displayTableWithWidths | ||||||
|   where |   where | ||||||
|     title = "Budget performance in " <> showDateSpan (periodicReportSpan budgetr) |     title = "Budget performance in " <> showDateSpan (periodicReportSpan budgetr) | ||||||
|  |            <> (case cost_ of | ||||||
|  |                  Cost   -> ", converted to cost" | ||||||
|  |                  NoCost -> "") | ||||||
|            <> (case value_ of |            <> (case value_ of | ||||||
|                  Just (AtCost _mc)   -> ", valued at cost" |  | ||||||
|                  Just (AtThen _mc)   -> ", valued at posting date" |                  Just (AtThen _mc)   -> ", valued at posting date" | ||||||
|                  Just (AtEnd _mc)    -> ", valued at period ends" |                  Just (AtEnd _mc)    -> ", valued at period ends" | ||||||
|                  Just (AtNow _mc)    -> ", current value" |                  Just (AtNow _mc)    -> ", current value" | ||||||
| @ -284,9 +286,9 @@ budgetReportAsText ropts@ReportOpts{..} budgetr = TB.toLazyText $ | |||||||
|         _   -> -- trace (pshow $ (maybecost actual, maybecost budget))  -- debug missing percentage |         _   -> -- trace (pshow $ (maybecost actual, maybecost budget))  -- debug missing percentage | ||||||
|                Nothing |                Nothing | ||||||
|       where |       where | ||||||
|         maybecost = case value_ of |         maybecost = case cost_ of | ||||||
|             Just (AtCost _) -> mixedAmountCost |             Cost   -> mixedAmountCost | ||||||
|             _               -> id |             NoCost -> id | ||||||
| 
 | 
 | ||||||
|     maybetranspose | transpose_ = \(Table rh ch vals) -> Table ch rh (transpose vals) |     maybetranspose | transpose_ = \(Table rh ch vals) -> Table ch rh (transpose vals) | ||||||
|                    | otherwise  = id |                    | otherwise  = id | ||||||
|  | |||||||
| @ -40,11 +40,8 @@ entriesReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j@Journal{..} = | |||||||
|     -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". |     -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". | ||||||
|     tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings} |     tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings} | ||||||
|       where |       where | ||||||
|         pvalue = maybe id |         pvalue = postingApplyCostValuation (journalPriceOracle infer_value_ j) (journalCommodityStyles j) periodlast (rsToday rspec) cost_ value_ | ||||||
|           (postingApplyValuation (journalPriceOracle infer_value_ j) (journalCommodityStyles j) periodlast (rsToday rspec)) |           where periodlast  = fromMaybe (rsToday rspec) $ reportPeriodOrJournalLastDay rspec j | ||||||
|           value_ |  | ||||||
|           where |  | ||||||
|             periodlast  = fromMaybe (rsToday rspec) $ reportPeriodOrJournalLastDay rspec j |  | ||||||
| 
 | 
 | ||||||
| tests_EntriesReport = tests "EntriesReport" [ | tests_EntriesReport = tests "EntriesReport" [ | ||||||
|   tests "entriesReport" [ |   tests "entriesReport" [ | ||||||
|  | |||||||
| @ -50,7 +50,7 @@ import Data.Semigroup ((<>)) | |||||||
| #endif | #endif | ||||||
| import Data.Semigroup (sconcat) | import Data.Semigroup (sconcat) | ||||||
| import Data.Time.Calendar (Day, addDays, fromGregorian) | import Data.Time.Calendar (Day, addDays, fromGregorian) | ||||||
| import Safe (headMay, lastDef, lastMay, minimumMay) | import Safe (headMay, lastDef, lastMay) | ||||||
| 
 | 
 | ||||||
| import Hledger.Data | import Hledger.Data | ||||||
| import Hledger.Query | import Hledger.Query | ||||||
| @ -317,14 +317,13 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col | |||||||
|         CumulativeChange  -> cumulative |         CumulativeChange  -> cumulative | ||||||
|         HistoricalBalance -> historical |         HistoricalBalance -> historical | ||||||
|       where |       where | ||||||
|         historical                           = cumulativeSum avalue startingBalance changes |         historical = cumulativeSum avalue startingBalance changes | ||||||
|         cumulative | changingValuation ropts = fmap (`subtractAcct` valuedStart) historical |         cumulative = cumulativeSum avalue nullacct changes | ||||||
|                    | otherwise               = cumulativeSum avalue nullacct changes |         changeamts = if changingValuation ropts | ||||||
|         changeamts | changingValuation ropts = periodChanges valuedStart historical |                         then periodChanges nullacct cumulative | ||||||
|                    | otherwise               = changes |                         else changes | ||||||
| 
 | 
 | ||||||
|         startingBalance = HM.lookupDefault nullacct name startbals |         startingBalance = HM.lookupDefault nullacct name startbals | ||||||
|         valuedStart = avalue (DateSpan Nothing historicalDate) startingBalance |  | ||||||
| 
 | 
 | ||||||
|     -- Transpose to get each account's balance changes across all columns, then |     -- Transpose to get each account's balance changes across all columns, then | ||||||
|     -- pad with zeros |     -- pad with zeros | ||||||
| @ -335,7 +334,6 @@ calculateReportMatrix rspec@ReportSpec{rsOpts=ropts} j priceoracle startbals col | |||||||
| 
 | 
 | ||||||
|     (pvalue, avalue) = postingAndAccountValuations rspec j priceoracle |     (pvalue, avalue) = postingAndAccountValuations rspec j priceoracle | ||||||
|     addElided = if queryDepth (rsQuery rspec) == Just 0 then HM.insert "..." zeros else id |     addElided = if queryDepth (rsQuery rspec) == Just 0 then HM.insert "..." zeros else id | ||||||
|     historicalDate = minimumMay $ mapMaybe spanStart colspans |  | ||||||
|     zeros = M.fromList [(span, nullacct) | span <- colspans] |     zeros = M.fromList [(span, nullacct) | span <- colspans] | ||||||
|     colspans = M.keys colps |     colspans = M.keys colps | ||||||
| 
 | 
 | ||||||
| @ -576,14 +574,13 @@ cumulativeSum value start = snd . M.mapAccumWithKey accumValued start | |||||||
| -- MultiBalanceReport. | -- MultiBalanceReport. | ||||||
| postingAndAccountValuations :: ReportSpec -> Journal -> PriceOracle | postingAndAccountValuations :: ReportSpec -> Journal -> PriceOracle | ||||||
|                             -> (DateSpan -> Posting -> Posting, DateSpan -> Account -> Account) |                             -> (DateSpan -> Posting -> Posting, DateSpan -> Account -> Account) | ||||||
| postingAndAccountValuations rspec@ReportSpec{rsOpts=ropts} j priceoracle = | postingAndAccountValuations rspec@ReportSpec{rsOpts=ropts} j priceoracle | ||||||
|   case value_ ropts of |     | changingValuation ropts = (const id, avalue' (cost_ ropts) (value_ ropts)) | ||||||
|     Nothing -> (const id, const id) |     | otherwise               = (pvalue' (cost_ ropts) (value_ ropts), const id) | ||||||
|     Just v  -> if changingValuation ropts then (const id, avalue' v) else (pvalue' v, const id) |  | ||||||
|   where |   where | ||||||
|     avalue' v span a = a{aibalance = value (aibalance a), aebalance = value (aebalance a)} |     avalue' c v span a = a{aibalance = value (aibalance a), aebalance = value (aebalance a)} | ||||||
|       where value = mixedAmountApplyValuation priceoracle styles (end span) (rsToday rspec) (error "multiBalanceReport: did not expect amount valuation to be called ") v  -- PARTIAL: should not happen |       where value = mixedAmountApplyCostValuation priceoracle styles (end span) (rsToday rspec) (error "multiBalanceReport: did not expect amount valuation to be called ") c v  -- PARTIAL: should not happen | ||||||
|     pvalue' v span = postingApplyValuation priceoracle styles (end span) (rsToday rspec) v |     pvalue' c v span = postingApplyCostValuation priceoracle styles (end span) (rsToday rspec) c v | ||||||
|     end = fromMaybe (error "multiBalanceReport: expected all spans to have an end date")  -- XXX should not happen |     end = fromMaybe (error "multiBalanceReport: expected all spans to have an end date")  -- XXX should not happen | ||||||
|         . fmap (addDays (-1)) . spanEnd |         . fmap (addDays (-1)) . spanEnd | ||||||
|     styles = journalCommodityStyles j |     styles = journalCommodityStyles j | ||||||
|  | |||||||
| @ -76,7 +76,7 @@ postingsReport rspec@ReportSpec{rsOpts=ropts@ReportOpts{..}} j = items | |||||||
|       (precedingps, reportps) = matchedPostingsBeforeAndDuring rspec j reportspan |       (precedingps, reportps) = matchedPostingsBeforeAndDuring rspec j reportspan | ||||||
| 
 | 
 | ||||||
|       -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". |       -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". | ||||||
|       pvalue periodlast = maybe id (postingApplyValuation priceoracle styles periodlast (rsToday rspec)) value_ |       pvalue periodlast = postingApplyCostValuation priceoracle styles periodlast (rsToday rspec) cost_ value_ | ||||||
| 
 | 
 | ||||||
|       -- Postings, or summary postings with their subperiod's end date, to be displayed. |       -- Postings, or summary postings with their subperiod's end date, to be displayed. | ||||||
|       displayps :: [(Posting, Maybe Day)] |       displayps :: [(Posting, Maybe Day)] | ||||||
|  | |||||||
| @ -45,7 +45,7 @@ where | |||||||
| 
 | 
 | ||||||
| import Control.Applicative ((<|>)) | import Control.Applicative ((<|>)) | ||||||
| import Data.List.Extra (nubSort) | import Data.List.Extra (nubSort) | ||||||
| import Data.Maybe (fromMaybe, isJust) | import Data.Maybe (fromMaybe, isJust, mapMaybe) | ||||||
| import qualified Data.Text as T | import qualified Data.Text as T | ||||||
| import Data.Time.Calendar (Day, addDays) | import Data.Time.Calendar (Day, addDays) | ||||||
| import Data.Default (Default(..)) | import Data.Default (Default(..)) | ||||||
| @ -85,6 +85,7 @@ data ReportOpts = ReportOpts { | |||||||
|      period_         :: Period |      period_         :: Period | ||||||
|     ,interval_       :: Interval |     ,interval_       :: Interval | ||||||
|     ,statuses_       :: [Status]  -- ^ Zero, one, or two statuses to be matched |     ,statuses_       :: [Status]  -- ^ Zero, one, or two statuses to be matched | ||||||
|  |     ,cost_           :: Costing  -- ^ Should we convert amounts to cost, when present? | ||||||
|     ,value_          :: Maybe ValuationType  -- ^ What value should amounts be converted to ? |     ,value_          :: Maybe ValuationType  -- ^ What value should amounts be converted to ? | ||||||
|     ,infer_value_    :: Bool      -- ^ Infer market prices from transactions ? |     ,infer_value_    :: Bool      -- ^ Infer market prices from transactions ? | ||||||
|     ,depth_          :: Maybe Int |     ,depth_          :: Maybe Int | ||||||
| @ -134,6 +135,7 @@ defreportopts = ReportOpts | |||||||
|     { period_          = PeriodAll |     { period_          = PeriodAll | ||||||
|     , interval_        = NoInterval |     , interval_        = NoInterval | ||||||
|     , statuses_        = [] |     , statuses_        = [] | ||||||
|  |     , cost_            = NoCost | ||||||
|     , value_           = Nothing |     , value_           = Nothing | ||||||
|     , infer_value_     = False |     , infer_value_     = False | ||||||
|     , depth_           = Nothing |     , depth_           = Nothing | ||||||
| @ -170,6 +172,7 @@ rawOptsToReportOpts rawopts = do | |||||||
|     let colorflag    = stringopt "color" rawopts |     let colorflag    = stringopt "color" rawopts | ||||||
|         formatstring = T.pack <$> maybestringopt "format" rawopts |         formatstring = T.pack <$> maybestringopt "format" rawopts | ||||||
|         querystring  = map T.pack $ listofstringopt "args" rawopts  -- doesn't handle an arg like "" right |         querystring  = map T.pack $ listofstringopt "args" rawopts  -- doesn't handle an arg like "" right | ||||||
|  |         (costing, valuation) = valuationTypeFromRawOpts rawopts | ||||||
| 
 | 
 | ||||||
|     format <- case parseStringFormat <$> formatstring of |     format <- case parseStringFormat <$> formatstring of | ||||||
|         Nothing         -> return defaultBalanceLineFormat |         Nothing         -> return defaultBalanceLineFormat | ||||||
| @ -180,7 +183,8 @@ rawOptsToReportOpts rawopts = do | |||||||
|           {period_      = periodFromRawOpts d rawopts |           {period_      = periodFromRawOpts d rawopts | ||||||
|           ,interval_    = intervalFromRawOpts rawopts |           ,interval_    = intervalFromRawOpts rawopts | ||||||
|           ,statuses_    = statusesFromRawOpts rawopts |           ,statuses_    = statusesFromRawOpts rawopts | ||||||
|           ,value_       = valuationTypeFromRawOpts rawopts |           ,cost_        = costing | ||||||
|  |           ,value_       = valuation | ||||||
|           ,infer_value_ = boolopt "infer-value" rawopts |           ,infer_value_ = boolopt "infer-value" rawopts | ||||||
|           ,depth_       = maybeposintopt "depth" rawopts |           ,depth_       = maybeposintopt "depth" rawopts | ||||||
|           ,date2_       = boolopt "date2" rawopts |           ,date2_       = boolopt "date2" rawopts | ||||||
| @ -400,27 +404,29 @@ reportOptsToggleStatus s ropts@ReportOpts{statuses_=ss} | |||||||
|   | s `elem` ss = ropts{statuses_=filter (/= s) ss} |   | s `elem` ss = ropts{statuses_=filter (/= s) ss} | ||||||
|   | otherwise   = ropts{statuses_=simplifyStatuses (s:ss)} |   | otherwise   = ropts{statuses_=simplifyStatuses (s:ss)} | ||||||
| 
 | 
 | ||||||
| -- | Parse the type of valuation to be performed, if any, specified by | -- | Parse the type of valuation and costing to be performed, if any, | ||||||
| -- -B/--cost, -V, -X/--exchange, or --value flags. If there's more | -- specified by -B/--cost, -V, -X/--exchange, or --value flags. It is | ||||||
| -- than one of these, the rightmost flag wins. | -- allowed to combine -B/--cost with any other valuation type. If | ||||||
| valuationTypeFromRawOpts :: RawOpts -> Maybe ValuationType | -- there's more than one valuation type, the rightmost flag wins. | ||||||
| valuationTypeFromRawOpts = lastMay . collectopts valuationfromrawopt | valuationTypeFromRawOpts :: RawOpts -> (Costing, Maybe ValuationType) | ||||||
|  | valuationTypeFromRawOpts rawopts = (costing, lastMay $ mapMaybe snd valuationopts) | ||||||
|   where |   where | ||||||
|  |     costing = if (any ((Cost==) . fst) valuationopts) then Cost else NoCost | ||||||
|  |     valuationopts = collectopts valuationfromrawopt rawopts | ||||||
|     valuationfromrawopt (n,v)  -- option name, value |     valuationfromrawopt (n,v)  -- option name, value | ||||||
|       | n == "B"     = Just $ AtCost Nothing |       | n == "B"     = Just (Cost,   Nothing) | ||||||
|       | n == "V"     = Just $ AtEnd Nothing |       | n == "V"     = Just (NoCost, Just $ AtEnd Nothing) | ||||||
|       | n == "X"     = Just $ AtEnd (Just $ T.pack v) |       | n == "X"     = Just (NoCost, Just $ AtEnd (Just $ T.pack v)) | ||||||
|       | n == "value" = Just $ valuation v |       | n == "value" = Just $ valuation v | ||||||
|       | otherwise    = Nothing |       | otherwise    = Nothing | ||||||
|     valuation v |     valuation v | ||||||
|       | t `elem` ["cost","c"]  = AtCost mc |       | t `elem` ["cost","c"]  = (Cost, usageError "--value=cost,COMM is no longer supported, please specify valuation explicitly, e.g. --cost --value=then,COMM" <$ mc) | ||||||
|       | t `elem` ["then" ,"t"] = AtThen  mc |       | t `elem` ["then" ,"t"] = (NoCost, Just $ AtThen mc) | ||||||
|       | t `elem` ["end" ,"e"]  = AtEnd  mc |       | t `elem` ["end" ,"e"]  = (NoCost, Just $ AtEnd  mc) | ||||||
|       | t `elem` ["now" ,"n"]  = AtNow  mc |       | t `elem` ["now" ,"n"]  = (NoCost, Just $ AtNow  mc) | ||||||
|       | otherwise = |       | otherwise = case parsedateM t of | ||||||
|           case parsedateM t of |             Just d  -> (NoCost, Just $ AtDate d mc) | ||||||
|             Just d  -> AtDate d mc |             Nothing -> usageError $ "could not parse \""++t++"\" as valuation type, should be: then|end|now|t|e|n|YYYY-MM-DD" | ||||||
|             Nothing -> usageError $ "could not parse \""++t++"\" as valuation type, should be: cost|then|end|now|c|t|e|n|YYYY-MM-DD" |  | ||||||
|       where |       where | ||||||
|         -- parse --value's value: TYPE[,COMM] |         -- parse --value's value: TYPE[,COMM] | ||||||
|         (t,c') = break (==',') v |         (t,c') = break (==',') v | ||||||
| @ -452,13 +458,12 @@ flat_ = not . tree_ | |||||||
| -- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts) | -- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts) | ||||||
| 
 | 
 | ||||||
| -- | Convert this journal's postings' amounts to cost using their | -- | Convert this journal's postings' amounts to cost using their | ||||||
| -- transaction prices, if specified by options (-B/--value=cost). | -- transaction prices, if specified by options (-B/--cost). | ||||||
| -- Maybe soon superseded by newer valuation code. | -- Maybe soon superseded by newer valuation code. | ||||||
| journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal | journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal | ||||||
| journalSelectingAmountFromOpts opts = | journalSelectingAmountFromOpts opts = case cost_ opts of | ||||||
|   case value_ opts of |     Cost   -> journalToCost | ||||||
|     Just (AtCost _) -> journalToCost |     NoCost -> id | ||||||
|     _               -> id |  | ||||||
| 
 | 
 | ||||||
| -- | Convert report options to a query, ignoring any non-flag command line arguments. | -- | Convert report options to a query, ignoring any non-flag command line arguments. | ||||||
| queryFromFlags :: ReportOpts -> Query | queryFromFlags :: ReportOpts -> Query | ||||||
| @ -476,7 +481,6 @@ queryFromFlags ReportOpts{..} = simplifyQuery $ And flagsq | |||||||
| -- different report periods. | -- different report periods. | ||||||
| changingValuation :: ReportOpts -> Bool | changingValuation :: ReportOpts -> Bool | ||||||
| changingValuation ropts = case value_ ropts of | changingValuation ropts = case value_ ropts of | ||||||
|     Just (AtCost (Just _)) -> True |  | ||||||
|     Just (AtEnd  _)        -> True |     Just (AtEnd  _)        -> True | ||||||
|     _                      -> False |     _                      -> False | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -81,7 +81,7 @@ tsDraw UIState{aopts=UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{ | |||||||
| 
 | 
 | ||||||
|       render . defaultLayout toplabel bottomlabel . str |       render . defaultLayout toplabel bottomlabel . str | ||||||
|         . T.unpack . showTransactionOneLineAmounts |         . T.unpack . showTransactionOneLineAmounts | ||||||
|         $ maybe id (transactionApplyValuation prices styles periodlast (rsToday rspec)) (value_ ropts) t |         $ transactionApplyCostValuation prices styles periodlast (rsToday rspec) (cost_ ropts) (value_ ropts) t | ||||||
|         -- (if real_ ropts then filterTransactionPostings (Real True) else id) -- filter postings by --real |         -- (if real_ ropts then filterTransactionPostings (Real True) else id) -- filter postings by --real | ||||||
|       where |       where | ||||||
|         toplabel = |         toplabel = | ||||||
|  | |||||||
| @ -113,7 +113,10 @@ clearCostValue ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_= | |||||||
| -- | Toggle between showing the primary amounts or costs. | -- | Toggle between showing the primary amounts or costs. | ||||||
| toggleCost :: UIState -> UIState | toggleCost :: UIState -> UIState | ||||||
| toggleCost ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} = | toggleCost ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rspec@ReportSpec{rsOpts=ropts}}}} = | ||||||
|   ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{value_ = valuationToggleCost $ value_ ropts}}}}} |     ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{cost_ = toggle $ cost_ ropts}}}}} | ||||||
|  |   where | ||||||
|  |     toggle Cost   = NoCost | ||||||
|  |     toggle NoCost = Cost | ||||||
| 
 | 
 | ||||||
| -- | Toggle between showing primary amounts or default valuation. | -- | Toggle between showing primary amounts or default valuation. | ||||||
| toggleValue :: UIState -> UIState | toggleValue :: UIState -> UIState | ||||||
| @ -121,11 +124,6 @@ toggleValue ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportspec_=rsp | |||||||
|   ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{ |   ui{aopts=uopts{cliopts_=copts{reportspec_=rspec{rsOpts=ropts{ | ||||||
|     value_ = plog "toggling value mode to" $ valuationToggleValue $ value_ ropts}}}}} |     value_ = plog "toggling value mode to" $ valuationToggleValue $ value_ ropts}}}}} | ||||||
| 
 | 
 | ||||||
| -- | Basic toggling of -B/cost, for hledger-ui. |  | ||||||
| valuationToggleCost :: Maybe ValuationType -> Maybe ValuationType |  | ||||||
| valuationToggleCost (Just (AtCost _)) = Nothing |  | ||||||
| valuationToggleCost _                 = Just $ AtCost Nothing |  | ||||||
| 
 |  | ||||||
| -- | Basic toggling of -V, for hledger-ui. | -- | Basic toggling of -V, for hledger-ui. | ||||||
| valuationToggleValue :: Maybe ValuationType -> Maybe ValuationType | valuationToggleValue :: Maybe ValuationType -> Maybe ValuationType | ||||||
| valuationToggleValue (Just (AtEnd _)) = Nothing | valuationToggleValue (Just (AtEnd _)) = Nothing | ||||||
|  | |||||||
| @ -156,7 +156,7 @@ reportflags = [ | |||||||
| 
 | 
 | ||||||
|   -- valuation |   -- valuation | ||||||
|  ,flagNone ["B","cost"]      (setboolopt "B") |  ,flagNone ["B","cost"]      (setboolopt "B") | ||||||
|    "show amounts converted to their cost/selling amount, using the transaction price. Equivalent to --value=cost." |    "show amounts converted to their cost/selling amount, using the transaction price." | ||||||
|  ,flagNone ["V","market"]    (setboolopt "V") |  ,flagNone ["V","market"]    (setboolopt "V") | ||||||
|    (unwords |    (unwords | ||||||
|      ["show amounts converted to period-end market value in their default valuation commodity." |      ["show amounts converted to period-end market value in their default valuation commodity." | ||||||
| @ -166,12 +166,11 @@ reportflags = [ | |||||||
|    (unwords |    (unwords | ||||||
|      ["show amounts converted to current (single period reports)" |      ["show amounts converted to current (single period reports)" | ||||||
|      ,"or period-end (multiperiod reports) market value in the specified commodity." |      ,"or period-end (multiperiod reports) market value in the specified commodity." | ||||||
|      ,"Equivalent to --value=now,COMM / --value=end,COMM." |      ,"Equivalent to --value=end,COMM." | ||||||
|      ]) |      ]) | ||||||
|  ,flagReq  ["value"]         (\s opts -> Right $ setopt "value" s opts) "TYPE[,COMM]" |  ,flagReq  ["value"]         (\s opts -> Right $ setopt "value" s opts) "TYPE[,COMM]" | ||||||
|    (unlines |    (unlines | ||||||
|      ["show amounts converted with valuation TYPE, and optionally to specified commodity COMM. TYPE can be:" |      ["show amounts converted with valuation TYPE, and optionally to specified commodity COMM. TYPE can be:" | ||||||
|      ,"'cost': convert to cost using transaction prices, then optionally to COMM using period-end market prices" |  | ||||||
|      ,"'then': convert to contemporaneous market value, in default valuation commodity or COMM (print & register commands only)" |      ,"'then': convert to contemporaneous market value, in default valuation commodity or COMM (print & register commands only)" | ||||||
|      ,"'end':  convert to period-end market value, in default valuation commodity or COMM" |      ,"'end':  convert to period-end market value, in default valuation commodity or COMM" | ||||||
|      ,"'now':  convert to current market value, in default valuation commodity or COMM" |      ,"'now':  convert to current market value, in default valuation commodity or COMM" | ||||||
|  | |||||||
| @ -598,14 +598,17 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $ | |||||||
|         PeriodChange                     -> "Balance changes" |         PeriodChange                     -> "Balance changes" | ||||||
|         CumulativeChange                 -> "Ending balances (cumulative)" |         CumulativeChange                 -> "Ending balances (cumulative)" | ||||||
|         HistoricalBalance                -> "Ending balances (historical)" |         HistoricalBalance                -> "Ending balances (historical)" | ||||||
|     valuationdesc = case value_ of |     valuationdesc = | ||||||
|         Just (AtCost _mc)    -> ", valued at cost" |         (case cost_ of | ||||||
|         Just (AtThen _mc)    -> ", valued at posting date" |             Cost   -> ", converted to cost" | ||||||
|         Just (AtEnd _mc) | changingValuation -> "" |             NoCost -> "") | ||||||
|         Just (AtEnd _mc)     -> ", valued at period ends" |         <> (case value_ of | ||||||
|         Just (AtNow _mc)     -> ", current value" |             Just (AtThen _mc)    -> ", valued at posting date" | ||||||
|         Just (AtDate d _mc)  -> ", valued at " <> showDate d |             Just (AtEnd _mc) | changingValuation -> "" | ||||||
|         Nothing              -> "" |             Just (AtEnd _mc)     -> ", valued at period ends" | ||||||
|  |             Just (AtNow _mc)     -> ", current value" | ||||||
|  |             Just (AtDate d _mc)  -> ", valued at " <> showDate d | ||||||
|  |             Nothing              -> "") | ||||||
| 
 | 
 | ||||||
|     changingValuation = case (balancetype_, value_) of |     changingValuation = case (balancetype_, value_) of | ||||||
|         (PeriodChange, Just (AtEnd _)) -> interval_ /= NoInterval |         (PeriodChange, Just (AtEnd _)) -> interval_ /= NoInterval | ||||||
|  | |||||||
| @ -61,13 +61,8 @@ roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{rsOpts=ReportOpts{..} | |||||||
|   d <- getCurrentDay |   d <- getCurrentDay | ||||||
|   -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". |   -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". | ||||||
|   let |   let | ||||||
|     tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings} |     tvalue = transactionApplyCostValuation (journalPriceOracle infer_value_ j) (journalCommodityStyles j) periodlast (rsToday rspec) cost_ value_ | ||||||
|       where |       where periodlast = fromMaybe (rsToday rspec) $ reportPeriodOrJournalLastDay rspec j | ||||||
|         pvalue = maybe id |  | ||||||
|           (postingApplyValuation (journalPriceOracle infer_value_ j) (journalCommodityStyles j) periodlast (rsToday rspec)) |  | ||||||
|           value_ |  | ||||||
|           where |  | ||||||
|             periodlast  = fromMaybe (rsToday rspec) $ reportPeriodOrJournalLastDay rspec j |  | ||||||
|   let |   let | ||||||
|     ropts = rsOpts rspec |     ropts = rsOpts rspec | ||||||
|     showCashFlow = boolopt "cashflow" rawopts |     showCashFlow = boolopt "cashflow" rawopts | ||||||
| @ -278,7 +273,7 @@ unMix a = | |||||||
|     Just a -> aquantity a |     Just a -> aquantity a | ||||||
|     Nothing -> error' $ "Amounts could not be converted to a single cost basis: " ++ show (map showAmount $ amounts a) ++ |     Nothing -> error' $ "Amounts could not be converted to a single cost basis: " ++ show (map showAmount $ amounts a) ++ | ||||||
|                "\nConsider using --value to force all costs to be in a single commodity." ++ |                "\nConsider using --value to force all costs to be in a single commodity." ++ | ||||||
|                "\nFor example, \"--value cost,<commodity> --infer-value\", where commodity is the one that was used to pay for the investment." |                "\nFor example, \"--cost --value=end,<commodity> --infer-value\", where commodity is the one that was used to pay for the investment." | ||||||
| 
 | 
 | ||||||
| -- Show Decimal rounded to two decimal places, unless it has less places already. This ensures that "2" won't be shown as "2.00" | -- Show Decimal rounded to two decimal places, unless it has less places already. This ensures that "2" won't be shown as "2.00" | ||||||
| showDecimal :: Decimal -> String | showDecimal :: Decimal -> String | ||||||
|  | |||||||
| @ -139,14 +139,17 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r | |||||||
|             CumulativeChange                 -> "(Cumulative Ending Balances)" |             CumulativeChange                 -> "(Cumulative Ending Balances)" | ||||||
|             HistoricalBalance                -> "(Historical Ending Balances)" |             HistoricalBalance                -> "(Historical Ending Balances)" | ||||||
| 
 | 
 | ||||||
|         valuationdesc = case value_ of |         valuationdesc = | ||||||
|           Just (AtCost _mc)       -> ", valued at cost" |           (case cost_ of | ||||||
|           Just (AtThen _mc)       -> ", valued at posting date" |                Cost   -> ", converted to cost" | ||||||
|           Just (AtEnd _mc) | changingValuation -> "" |                NoCost -> "") | ||||||
|           Just (AtEnd _mc)        -> ", valued at period ends" |           <> (case value_ of | ||||||
|           Just (AtNow _mc)        -> ", current value" |                Just (AtThen _mc)       -> ", valued at posting date" | ||||||
|           Just (AtDate today _mc) -> ", valued at " <> showDate today |                Just (AtEnd _mc) | changingValuation -> "" | ||||||
|           Nothing                 -> "" |                Just (AtEnd _mc)        -> ", valued at period ends" | ||||||
|  |                Just (AtNow _mc)        -> ", current value" | ||||||
|  |                Just (AtDate today _mc) -> ", valued at " <> showDate today | ||||||
|  |                Nothing                 -> "") | ||||||
| 
 | 
 | ||||||
|         changingValuation = case (balancetype_, value_) of |         changingValuation = case (balancetype_, value_) of | ||||||
|             (PeriodChange, Just (AtEnd _)) -> interval_ /= NoInterval |             (PeriodChange, Just (AtEnd _)) -> interval_ /= NoInterval | ||||||
|  | |||||||
| @ -716,26 +716,28 @@ Some of these can also be expressed as command-line options (eg `depth:2` is equ | |||||||
| Generally you can mix options and query arguments, and the resulting query will be their intersection | Generally you can mix options and query arguments, and the resulting query will be their intersection | ||||||
| (perhaps excluding the `-p/--period` option). | (perhaps excluding the `-p/--period` option). | ||||||
| 
 | 
 | ||||||
|  | # COSTING | ||||||
|  | 
 | ||||||
|  | The `-B/--cost` flag converts amounts to their cost or sale amount at transaction time, | ||||||
|  | if they have a [transaction price](hledger.html#transaction-prices) specified. | ||||||
|  | If this flag is supplied, hledger will perform cost conversion first, and will apply | ||||||
|  | any market price valuations (if requested) afterwards. | ||||||
|  | 
 | ||||||
| # VALUATION | # VALUATION | ||||||
| 
 | 
 | ||||||
| Instead of reporting amounts in their original commodity, | Instead of reporting amounts in their original commodity, | ||||||
| hledger can convert them to | hledger can convert them to | ||||||
| cost/sale amount (using the conversion rate recorded in the transaction), | cost/sale amount (using the conversion rate recorded in the transaction), | ||||||
| or to market value (using some market price on a certain date). | and/or to market value (using some market price on a certain date). | ||||||
| This is controlled by the `--value=TYPE[,COMMODITY]` option, | This is controlled by the `--cost` and `--value=TYPE[,COMMODITY]` options, | ||||||
| but we also provide the simpler `-B`/`-V`/`-X` flags, | but we also provide the simpler `-V`/`-X` flags, | ||||||
| and usually one of those is all you need. | and usually one of those is all you need. | ||||||
| 
 | 
 | ||||||
| ## -B: Cost |  | ||||||
| 
 |  | ||||||
| The `-B/--cost` flag converts amounts to their cost or sale amount at transaction time, |  | ||||||
| if they have a [transaction price](hledger.html#transaction-prices) specified. |  | ||||||
| 
 |  | ||||||
| ## -V: Value | ## -V: Value | ||||||
| 
 | 
 | ||||||
| The `-V/--market` flag converts amounts to market value in their | The `-V/--market` flag converts amounts to market value in their | ||||||
| default *valuation commodity*, using the | default *valuation commodity*, using the | ||||||
| [market prices](#market-prices) in effect on the *valuation date(s)*, if any.  | [market prices](#market-prices) in effect on the *valuation date(s)*, if any. | ||||||
| More on these in a minute. | More on these in a minute. | ||||||
| 
 | 
 | ||||||
| ## -X: Value in specified commodity | ## -X: Value in specified commodity | ||||||
| @ -885,12 +887,11 @@ $ hledger -f t.j bal -N euros -V | |||||||
| 
 | 
 | ||||||
| ## --value: Flexible valuation | ## --value: Flexible valuation | ||||||
| 
 | 
 | ||||||
| `-B`, `-V` and `-X` are special cases of the more general `--value` option: | `-V` and `-X` are special cases of the more general `--value` option: | ||||||
| 
 | 
 | ||||||
|      --value=TYPE[,COMM]  TYPE is cost, then, end, now or YYYY-MM-DD. |      --value=TYPE[,COMM]  TYPE is then, end, now or YYYY-MM-DD. | ||||||
|                           COMM is an optional commodity symbol. |                           COMM is an optional commodity symbol. | ||||||
|                           Shows amounts converted to: |                           Shows amounts converted to: | ||||||
|                           - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) |  | ||||||
|                           - default valuation commodity (or COMM) using market prices at posting dates |                           - default valuation commodity (or COMM) using market prices at posting dates | ||||||
|                           - default valuation commodity (or COMM) using market prices at period end(s) |                           - default valuation commodity (or COMM) using market prices at period end(s) | ||||||
|                           - default valuation commodity (or COMM) using current market prices |                           - default valuation commodity (or COMM) using current market prices | ||||||
| @ -898,9 +899,6 @@ $ hledger -f t.j bal -N euros -V | |||||||
| 
 | 
 | ||||||
| The TYPE part selects cost or value and valuation date: | The TYPE part selects cost or value and valuation date: | ||||||
| 
 | 
 | ||||||
| `--value=cost` |  | ||||||
| : Convert amounts to cost, using the prices recorded in transactions. |  | ||||||
| 
 |  | ||||||
| `--value=then` | `--value=then` | ||||||
| : Convert amounts to their value in the [default valuation commodity](#valuation-commodity), | : Convert amounts to their value in the [default valuation commodity](#valuation-commodity), | ||||||
|   using market prices on each posting's date. |   using market prices on each posting's date. | ||||||
| @ -945,7 +943,7 @@ P 2000-04-01 A  4 B | |||||||
| 
 | 
 | ||||||
| Show the cost of each posting: | Show the cost of each posting: | ||||||
| ```shell | ```shell | ||||||
| $ hledger -f- print --value=cost | $ hledger -f- print --cost | ||||||
| 2000-01-01 | 2000-01-01 | ||||||
|     (a)             5 B |     (a)             5 B | ||||||
| 
 | 
 | ||||||
| @ -1056,7 +1054,7 @@ Related: | |||||||
| [#329](https://github.com/simonmichael/hledger/issues/329), | [#329](https://github.com/simonmichael/hledger/issues/329), | ||||||
| [#1083](https://github.com/simonmichael/hledger/issues/1083). | [#1083](https://github.com/simonmichael/hledger/issues/1083). | ||||||
| 
 | 
 | ||||||
| | Report type                                         | `-B`, `--value=cost`                                             | `-V`, `-X`                                                        | `--value=then`                                                                                 | `--value=end`                                                     | `--value=DATE`, `--value=now`           | | | Report type                                         | `-B`, `--cost`                                                   | `-V`, `-X`                                                        | `--value=then`                                                                                 | `--value=end`                                                     | `--value=DATE`, `--value=now`           | | ||||||
| |-----------------------------------------------------|------------------------------------------------------------------|-------------------------------------------------------------------|------------------------------------------------------------------------------------------------|-------------------------------------------------------------------|-----------------------------------------| | |-----------------------------------------------------|------------------------------------------------------------------|-------------------------------------------------------------------|------------------------------------------------------------------------------------------------|-------------------------------------------------------------------|-----------------------------------------| | ||||||
| | **print**                                           |                                                                  |                                                                   |                                                                                                |                                                                   |                                         | | | **print**                                           |                                                                  |                                                                   |                                                                                                |                                                                   |                                         | | ||||||
| | posting amounts                                     | cost                                                             | value at report end or today                                      | value at posting date                                                                          | value at report or journal end                                    | value at DATE/today                     | | | posting amounts                                     | cost                                                             | value at report end or today                                      | value at posting date                                                                          | value at report or journal end                                    | value at DATE/today                     | | ||||||
|  | |||||||
| @ -219,7 +219,7 @@ $ hledger -f- reg --value=cost | |||||||
| 2000-01-01                      (a)                            6 B           6 B | 2000-01-01                      (a)                            6 B           6 B | ||||||
| 2000-02-01                      (a)                            7 B          13 B | 2000-02-01                      (a)                            7 B          13 B | ||||||
| 2000-03-01                      (a)                            8 B          21 B | 2000-03-01                      (a)                            8 B          21 B | ||||||
|   | 
 | ||||||
| # 16. register report valued at posting dates | # 16. register report valued at posting dates | ||||||
| $ hledger -f- reg --value=then | $ hledger -f- reg --value=then | ||||||
| 2000-01-01                      (a)                            1 B           1 B | 2000-01-01                      (a)                            1 B           1 B | ||||||
| @ -303,12 +303,16 @@ $ hledger -f- reg --value=cost -M | |||||||
| 
 | 
 | ||||||
| # back to the original test journal: | # back to the original test journal: | ||||||
| < | < | ||||||
|  | P 1999/01/01 A  10 B | ||||||
| P 2000/01/01 A  1 B | P 2000/01/01 A  1 B | ||||||
| P 2000/01/15 A  5 B | P 2000/01/15 A  5 B | ||||||
| P 2000/02/01 A  2 B | P 2000/02/01 A  2 B | ||||||
| P 2000/03/01 A  3 B | P 2000/03/01 A  3 B | ||||||
| P 2000/04/01 A  4 B | P 2000/04/01 A  4 B | ||||||
| 
 | 
 | ||||||
|  | 1999/01/01 | ||||||
|  |   (a)      2 A @ 4 B | ||||||
|  | 
 | ||||||
| 2000/01/01 | 2000/01/01 | ||||||
|   (a)      1 A @ 6 B |   (a)      1 A @ 6 B | ||||||
| 
 | 
 | ||||||
| @ -319,25 +323,25 @@ P 2000/04/01 A  4 B | |||||||
|   (a)      1 A @ 8 B |   (a)      1 A @ 8 B | ||||||
| 
 | 
 | ||||||
| # 25. periodic register report valued at period end | # 25. periodic register report valued at period end | ||||||
| $ hledger -f- reg --value=end -M | $ hledger -f- reg --value=end -M -b 2000 | ||||||
| 2000-01                 a                                      5 B           5 B | 2000-01                 a                                      5 B           5 B | ||||||
| 2000-02                 a                                      2 B           7 B | 2000-02                 a                                      2 B           7 B | ||||||
| 2000-03                 a                                      3 B          10 B | 2000-03                 a                                      3 B          10 B | ||||||
| 
 | 
 | ||||||
| # 26. periodic register report valued at specified date | # 26. periodic register report valued at specified date | ||||||
| $ hledger -f- reg --value=2000-01-15 -M | $ hledger -f- reg --value=2000-01-15 -M -b 2000 | ||||||
| 2000-01                 a                                      5 B           5 B | 2000-01                 a                                      5 B           5 B | ||||||
| 2000-02                 a                                      5 B          10 B | 2000-02                 a                                      5 B          10 B | ||||||
| 2000-03                 a                                      5 B          15 B | 2000-03                 a                                      5 B          15 B | ||||||
| 
 | 
 | ||||||
| # 27. periodic register report valued today | # 27. periodic register report valued today | ||||||
| $ hledger -f- reg --value=now -M | $ hledger -f- reg --value=now -M -b 2000 | ||||||
| 2000-01                 a                                      4 B           4 B | 2000-01                 a                                      4 B           4 B | ||||||
| 2000-02                 a                                      4 B           8 B | 2000-02                 a                                      4 B           8 B | ||||||
| 2000-03                 a                                      4 B          12 B | 2000-03                 a                                      4 B          12 B | ||||||
| 
 | 
 | ||||||
| # 28. periodic register report valued at default date (same as --value=end) | # 28. periodic register report valued at default date (same as --value=end) | ||||||
| $ hledger -f- reg -V -M | $ hledger -f- reg -V -M -b 2000 | ||||||
| 2000-01                 a                                      5 B           5 B | 2000-01                 a                                      5 B           5 B | ||||||
| 2000-02                 a                                      2 B           7 B | 2000-02                 a                                      2 B           7 B | ||||||
| 2000-03                 a                                      3 B          10 B | 2000-03                 a                                      3 B          10 B | ||||||
| @ -345,30 +349,30 @@ $ hledger -f- reg -V -M | |||||||
| # balance | # balance | ||||||
| 
 | 
 | ||||||
| # 29. single column balance report valued at cost | # 29. single column balance report valued at cost | ||||||
| $ hledger -f- bal -N --value=cost | $ hledger -f- bal -N --value=cost -b 2000 | ||||||
|                 21 B  a |                 21 B  a | ||||||
| 
 | 
 | ||||||
| # 30. single column balance report valued at period end (which includes market price declarations, see #1405) | # 30. single column balance report valued at period end (which includes market price declarations, see #1405) | ||||||
| $ hledger -f- bal -N --value=end | $ hledger -f- bal -N --value=end -b 2000 | ||||||
|                 12 B  a |                 12 B  a | ||||||
| 
 | 
 | ||||||
| # 31. single column balance report valued at specified date | # 31. single column balance report valued at specified date | ||||||
| $ hledger -f- bal -N --value=2000-01-15 | $ hledger -f- bal -N --value=2000-01-15 -b 2000 | ||||||
|                 15 B  a |                 15 B  a | ||||||
| 
 | 
 | ||||||
| # 32. single column balance report valued today | # 32. single column balance report valued today | ||||||
| $ hledger -f- bal -N --value=now | $ hledger -f- bal -N --value=now -b 2000 | ||||||
|                 12 B  a |                 12 B  a | ||||||
| 
 | 
 | ||||||
| # 33. single column balance report valued at default date (same as --value=end) | # 33. single column balance report valued at default date (same as --value=end) | ||||||
| $ hledger -f- bal -N -V | $ hledger -f- bal -N -V -b 2000 | ||||||
|                 12 B  a |                 12 B  a | ||||||
| 
 | 
 | ||||||
| # balance, periodic | # balance, periodic | ||||||
| 
 | 
 | ||||||
| # 34. multicolumn balance report valued at cost | # 34. multicolumn balance report valued at cost | ||||||
| $ hledger -f- bal -MTA --value=cost | $ hledger -f- bal -MTA --value=cost -b 2000 | ||||||
| Balance changes in 2000-01-01..2000-04-30, valued at cost: | Balance changes in 2000-01-01..2000-04-30, converted to cost: | ||||||
| 
 | 
 | ||||||
|    || Jan  Feb  Mar  Apr    Total  Average  |    || Jan  Feb  Mar  Apr    Total  Average  | ||||||
| ===++====================================== | ===++====================================== | ||||||
| @ -377,7 +381,7 @@ Balance changes in 2000-01-01..2000-04-30, valued at cost: | |||||||
|    || 6 B  7 B  8 B    0     21 B      5 B  |    || 6 B  7 B  8 B    0     21 B      5 B  | ||||||
| 
 | 
 | ||||||
| # 35. multicolumn balance report valued at posting date | # 35. multicolumn balance report valued at posting date | ||||||
| $ hledger -f- bal -M --value=then | $ hledger -f- bal -M --value=then -b 2000 | ||||||
| Balance changes in 2000-01-01..2000-04-30, valued at posting date: | Balance changes in 2000-01-01..2000-04-30, valued at posting date: | ||||||
| 
 | 
 | ||||||
|    || Jan  Feb  Mar  Apr  |    || Jan  Feb  Mar  Apr  | ||||||
| @ -387,7 +391,7 @@ Balance changes in 2000-01-01..2000-04-30, valued at posting date: | |||||||
|    || 1 B  2 B  3 B    0  |    || 1 B  2 B  3 B    0  | ||||||
| 
 | 
 | ||||||
| # 36. multicolumn balance report showing changes in period-end values | # 36. multicolumn balance report showing changes in period-end values | ||||||
| $ hledger -f- bal -M --value=end | $ hledger -f- bal -M --value=end -b 2000 | ||||||
| Period-end value changes in 2000-01-01..2000-04-30: | Period-end value changes in 2000-01-01..2000-04-30: | ||||||
| 
 | 
 | ||||||
|    || Jan   Feb  Mar  Apr  |    || Jan   Feb  Mar  Apr  | ||||||
| @ -397,7 +401,7 @@ Period-end value changes in 2000-01-01..2000-04-30: | |||||||
|    || 5 B  -1 B  5 B  3 B  |    || 5 B  -1 B  5 B  3 B  | ||||||
| 
 | 
 | ||||||
| # 37. multicolumn balance report showing changes in period-end values with -T or -A | # 37. multicolumn balance report showing changes in period-end values with -T or -A | ||||||
| $ hledger -f- bal -MTA --value=end | $ hledger -f- bal -MTA --value=end -b 2000 | ||||||
| Period-end value changes in 2000-01-01..2000-04-30: | Period-end value changes in 2000-01-01..2000-04-30: | ||||||
| 
 | 
 | ||||||
|    || Jan   Feb  Mar  Apr    Total  Average  |    || Jan   Feb  Mar  Apr    Total  Average  | ||||||
| @ -407,7 +411,7 @@ Period-end value changes in 2000-01-01..2000-04-30: | |||||||
|    || 5 B  -1 B  5 B  3 B     12 B      3 B  |    || 5 B  -1 B  5 B  3 B     12 B      3 B  | ||||||
| 
 | 
 | ||||||
| # 38. multicolumn balance report valued at other date | # 38. multicolumn balance report valued at other date | ||||||
| $ hledger -f- bal -MTA --value=2000-01-15 | $ hledger -f- bal -MTA --value=2000-01-15 -b 2000 | ||||||
| Balance changes in 2000-01-01..2000-04-30, valued at 2000-01-15: | Balance changes in 2000-01-01..2000-04-30, valued at 2000-01-15: | ||||||
| 
 | 
 | ||||||
|    || Jan  Feb  Mar  Apr    Total  Average  |    || Jan  Feb  Mar  Apr    Total  Average  | ||||||
| @ -417,7 +421,7 @@ Balance changes in 2000-01-01..2000-04-30, valued at 2000-01-15: | |||||||
|    || 5 B  5 B  5 B    0     15 B      4 B  |    || 5 B  5 B  5 B    0     15 B      4 B  | ||||||
| 
 | 
 | ||||||
| # 39. multicolumn balance report valued today (with today >= 2000-04-01) | # 39. multicolumn balance report valued today (with today >= 2000-04-01) | ||||||
| $ hledger -f- bal -M --value=now | $ hledger -f- bal -M --value=now -b 2000 | ||||||
| Balance changes in 2000-01-01..2000-04-30, current value: | Balance changes in 2000-01-01..2000-04-30, current value: | ||||||
| 
 | 
 | ||||||
|    || Jan  Feb  Mar  Apr  |    || Jan  Feb  Mar  Apr  | ||||||
| @ -427,7 +431,7 @@ Balance changes in 2000-01-01..2000-04-30, current value: | |||||||
|    || 4 B  4 B  4 B    0  |    || 4 B  4 B  4 B    0  | ||||||
| 
 | 
 | ||||||
| # 40. multicolumn balance report showing changes in period-end values (same as --value=end) | # 40. multicolumn balance report showing changes in period-end values (same as --value=end) | ||||||
| $ hledger -f- bal -M -V | $ hledger -f- bal -M -V -b 2000 | ||||||
| Period-end value changes in 2000-01-01..2000-04-30: | Period-end value changes in 2000-01-01..2000-04-30: | ||||||
| 
 | 
 | ||||||
|    || Jan   Feb  Mar  Apr  |    || Jan   Feb  Mar  Apr  | ||||||
| @ -439,42 +443,42 @@ Period-end value changes in 2000-01-01..2000-04-30: | |||||||
| # balance, periodic, with -H (starting balance and accumulating across periods) | # balance, periodic, with -H (starting balance and accumulating across periods) | ||||||
| 
 | 
 | ||||||
| # 41. multicolumn balance report with -H, valued at cost. | # 41. multicolumn balance report with -H, valued at cost. | ||||||
| # The starting balance on 2000/01/01 is 6 B (cost of the first 2 A). | # The starting balance on 2000/01/01 is 14 B (cost of the first 8A). | ||||||
| # February adds 1 A costing 7 B, making 13 B. | # February adds 1 A costing 7 B, making 21 B. | ||||||
| # March adds 1 A costing 8 B, making 21 B. | # March adds 1 A costing 8 B, making 29 B. | ||||||
| $ hledger -f- bal -M -H -b 200002 --value=cost | $ hledger -f- bal -M -H -b 200002 --value=cost | ||||||
| Ending balances (historical) in 2000-02-01..2000-04-30, valued at cost: | Ending balances (historical) in 2000-02-01..2000-04-30, converted to cost: | ||||||
| 
 | 
 | ||||||
|    || 2000-02-29  2000-03-31  2000-04-30  |    || 2000-02-29  2000-03-31  2000-04-30  | ||||||
| ===++==================================== | ===++==================================== | ||||||
|  a ||       13 B        21 B        21 B  |  a ||       21 B        29 B        29 B  | ||||||
| ---++------------------------------------ | ---++------------------------------------ | ||||||
|    ||       13 B        21 B        21 B  |    ||       21 B        29 B        29 B  | ||||||
| 
 | 
 | ||||||
| # 42. multicolumn balance report with -H valued at period end. | # 42. multicolumn balance report with -H valued at period end. | ||||||
| # The starting balance is 1 A. | # The starting balance is 3 A. | ||||||
| # February adds 1 A making 2 A, which is valued at 2000/02/29 as 4 B. | # February adds 1 A making 4 A, which is valued at 2000/02/29 as 8 B. | ||||||
| # March adds 1 A making 3 A, which is valued at 2000/03/31 as 9 B. | # March adds 1 A making 5 A, which is valued at 2000/03/31 as 15 B. | ||||||
| # April adds 0 A making 3 A, which is valued at 2000/04/31 as 12 B. | # April adds 0 A making 5 A, which is valued at 2000/04/31 as 20 B. | ||||||
| $ hledger -f- bal -MA -H -b 200002 --value=end | $ hledger -f- bal -MA -H -b 200002 --value=end | ||||||
| Ending balances (historical) in 2000-02-01..2000-04-30, valued at period ends: | Ending balances (historical) in 2000-02-01..2000-04-30, valued at period ends: | ||||||
| 
 | 
 | ||||||
|    || 2000-02-29  2000-03-31  2000-04-30  Average  |    || 2000-02-29  2000-03-31  2000-04-30  Average  | ||||||
| ===++============================================= | ===++============================================= | ||||||
|  a ||        4 B         9 B        12 B      8 B  |  a ||        8 B        15 B        20 B     14 B  | ||||||
| ---++--------------------------------------------- | ---++--------------------------------------------- | ||||||
|    ||        4 B         9 B        12 B      8 B  |    ||        8 B        15 B        20 B     14 B  | ||||||
| 
 | 
 | ||||||
| # 43. multicolumn balance report with -H valued at other date. | # 43. multicolumn balance report with -H valued at other date. | ||||||
| # The starting balance is 5 B (1 A valued at 2000/1/15). | # The starting balance is 15 B (3 A valued at 2000/1/15). | ||||||
| $ hledger -f- bal -M -H -b 200002 --value=2000-01-15 | $ hledger -f- bal -M -H -b 200002 --value=2000-01-15 | ||||||
| Ending balances (historical) in 2000-02-01..2000-04-30, valued at 2000-01-15: | Ending balances (historical) in 2000-02-01..2000-04-30, valued at 2000-01-15: | ||||||
| 
 | 
 | ||||||
|    || 2000-02-29  2000-03-31  2000-04-30  |    || 2000-02-29  2000-03-31  2000-04-30  | ||||||
| ===++==================================== | ===++==================================== | ||||||
|  a ||       10 B        15 B        15 B  |  a ||       20 B        25 B        25 B  | ||||||
| ---++------------------------------------ | ---++------------------------------------ | ||||||
|    ||       10 B        15 B        15 B  |    ||       20 B        25 B        25 B  | ||||||
| 
 | 
 | ||||||
| # 44. multicolumn balance report with -H, valuing each period's carried-over balances at cost. | # 44. multicolumn balance report with -H, valuing each period's carried-over balances at cost. | ||||||
| < | < | ||||||
| @ -488,7 +492,7 @@ P 2000/04/01 A  4 B | |||||||
|   (a)      1 A @ 6 B |   (a)      1 A @ 6 B | ||||||
| 
 | 
 | ||||||
| $ hledger -f- bal -ME -H -p200001-200004 --value=c | $ hledger -f- bal -ME -H -p200001-200004 --value=c | ||||||
| Ending balances (historical) in 2000Q1, valued at cost: | Ending balances (historical) in 2000Q1, converted to cost: | ||||||
| 
 | 
 | ||||||
|    || 2000-01-31  2000-02-29  2000-03-31  |    || 2000-01-31  2000-02-29  2000-03-31  | ||||||
| ===++==================================== | ===++==================================== | ||||||
| @ -551,7 +555,7 @@ Budget performance in 2000-01-01..2000-04-30: | |||||||
| 
 | 
 | ||||||
| # 48. budget report, valued at cost. | # 48. budget report, valued at cost. | ||||||
| $ hledger -f- bal -MTA --budget --value=c | $ hledger -f- bal -MTA --budget --value=c | ||||||
| Budget performance in 2000-01-01..2000-04-30, valued at cost: | Budget performance in 2000-01-01..2000-04-30, converted to cost: | ||||||
| 
 | 
 | ||||||
|    ||               Jan                Feb                Mar            Apr               Total            Average  |    ||               Jan                Feb                Mar            Apr               Total            Average  | ||||||
| ===++=============================================================================================================== | ===++=============================================================================================================== | ||||||
|  | |||||||
| @ -134,11 +134,11 @@ $ hledger -f- print -B | |||||||
| 
 | 
 | ||||||
| >=0 | >=0 | ||||||
| 
 | 
 | ||||||
| # 12. Note the -XZ nullifies the -B here, because both are forms of --value | # 12. Note the -XZ does not nullify the -B here. | ||||||
| # (-B -XZ is equivalent to --value=cost --value=end,Z), and the rightmost wins. | # (-B -XZ is equivalent to --cost --value=end,Z). | ||||||
| $ hledger -f- print -B -XZ | $ hledger -f- print -B -XZ | ||||||
| 2000-01-01 | 2000-01-01 | ||||||
|     a        -1A @ 1B |     a             -1B | ||||||
|     b              1B |     b              1B | ||||||
| 
 | 
 | ||||||
| >=0 | >=0 | ||||||
| @ -176,10 +176,10 @@ $ hledger -f- print -B | |||||||
| >=0 | >=0 | ||||||
| 
 | 
 | ||||||
| # 16.  | # 16.  | ||||||
| $ hledger -f- print -B -XZ | $ hledger -f- print -B -XA | ||||||
| 2000-01-01 | 2000-01-01 | ||||||
|     a        -1A @ 1B |     a             -1A | ||||||
|     b              1B |     b              1A | ||||||
| 
 | 
 | ||||||
| >=0 | >=0 | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -240,11 +240,11 @@ hledger -f- roi -p 2019-11 --inv Investment --pnl PnL | |||||||
| >>>2 | >>>2 | ||||||
| hledger: Amounts could not be converted to a single cost basis: ["10 B","-10 B @@ 100 A"] | hledger: Amounts could not be converted to a single cost basis: ["10 B","-10 B @@ 100 A"] | ||||||
| Consider using --value to force all costs to be in a single commodity. | Consider using --value to force all costs to be in a single commodity. | ||||||
| For example, "--value cost,<commodity> --infer-value", where commodity is the one that was used to pay for the investment. | For example, "--cost --value=end,<commodity> --infer-value", where commodity is the one that was used to pay for the investment. | ||||||
| >>>=1 | >>>=1 | ||||||
| 
 | 
 | ||||||
| # 10. Forcing valuation via --value | # 10. Forcing valuation via --value | ||||||
| hledger -f- roi -p 2019-11 --inv Investment --pnl PnL --value cost,A --infer-value | hledger -f- roi -p 2019-11 --inv Investment --pnl PnL --cost --value=then,A --infer-value | ||||||
| <<< | <<< | ||||||
| 2019/11/01 Example | 2019/11/01 Example | ||||||
|   Assets:Checking  -100 A |   Assets:Checking  -100 A | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user