imp: lib,cli: Implement gain report for balance reports.
A gain report will report on unrealised gains by looking at the difference between the valuation of an amount (by default, --value=end), and the valuation of the cost of the amount.
This commit is contained in:
parent
90612c1444
commit
ddba9f6ce4
@ -20,6 +20,8 @@ module Hledger.Data.Valuation (
|
|||||||
,mixedAmountToCost
|
,mixedAmountToCost
|
||||||
,mixedAmountApplyValuation
|
,mixedAmountApplyValuation
|
||||||
,mixedAmountValueAtDate
|
,mixedAmountValueAtDate
|
||||||
|
,mixedAmountApplyGain
|
||||||
|
,mixedAmountGainAtDate
|
||||||
,marketPriceReverse
|
,marketPriceReverse
|
||||||
,priceDirectiveToMarketPrice
|
,priceDirectiveToMarketPrice
|
||||||
-- ,priceLookup
|
-- ,priceLookup
|
||||||
@ -114,28 +116,24 @@ amountToCost NoCost _ = id
|
|||||||
amountToCost Cost styles = styleAmount styles . amountCost
|
amountToCost Cost styles = styleAmount styles . amountCost
|
||||||
|
|
||||||
-- | Apply a specified valuation to this amount, using the provided
|
-- | Apply a specified valuation to this amount, using the provided
|
||||||
-- price oracle, reference dates, and whether this is for a
|
-- price oracle, and reference dates. Also fix up its display style
|
||||||
-- multiperiod report or not. Also fix up its display style using the
|
-- using the provided commodity styles.
|
||||||
-- provided commodity styles.
|
|
||||||
--
|
--
|
||||||
-- When the valuation requires converting to another commodity, a
|
-- When the valuation requires converting to another commodity, a
|
||||||
-- valuation (conversion) date is chosen based on the valuation type,
|
-- valuation (conversion) date is chosen based on the valuation type
|
||||||
-- the provided reference dates, and whether this is for a
|
-- and the provided reference dates. It will be one of:
|
||||||
-- single-period or multi-period report. It will be one of:
|
|
||||||
--
|
--
|
||||||
-- - a fixed date specified by the ValuationType itself
|
-- - the date of the posting itself (--value=then)
|
||||||
-- (--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
|
||||||
-- single-period report).
|
-- single-period report).
|
||||||
--
|
--
|
||||||
-- - the provided "report end" date - the last day of the specified
|
-- - the provided "today" date (--value=now).
|
||||||
-- report period, if any (-V/-X with a report end date).
|
|
||||||
--
|
--
|
||||||
-- - the provided "today" date - (--value=now, or -V/X with no report
|
-- - a fixed date specified by the ValuationType itself
|
||||||
-- end date).
|
-- (--value=DATE).
|
||||||
--
|
--
|
||||||
-- This is all a bit complicated. See the reference doc at
|
-- This is all a bit complicated. See the reference doc at
|
||||||
-- https://hledger.org/hledger.html#effect-of-valuation-on-reports
|
-- https://hledger.org/hledger.html#effect-of-valuation-on-reports
|
||||||
@ -180,6 +178,29 @@ amountValueAtDate priceoracle styles mto d a =
|
|||||||
styleAmount styles
|
styleAmount styles
|
||||||
amount{acommodity=comm, aquantity=rate * aquantity a}
|
amount{acommodity=comm, aquantity=rate * aquantity a}
|
||||||
|
|
||||||
|
-- | Calculate the gain of each component amount, that is the difference
|
||||||
|
-- between the valued amount and the value of the cost basis (see
|
||||||
|
-- mixedAmountApplyValuation).
|
||||||
|
--
|
||||||
|
-- If the commodity we are valuing in is not the same as the commodity of the
|
||||||
|
-- cost, this will value the cost at the same date as the primary amount. This
|
||||||
|
-- may not be what you want; for example you may want the cost valued at the
|
||||||
|
-- posting date. If so, let us know and we can change this behaviour.
|
||||||
|
mixedAmountApplyGain :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount
|
||||||
|
mixedAmountApplyGain priceoracle styles periodlast today postingdate v ma =
|
||||||
|
mixedAmountApplyValuation priceoracle styles periodlast today postingdate v $ ma `maMinus` mixedAmountCost ma
|
||||||
|
|
||||||
|
-- | Calculate the gain of each component amount, that is the
|
||||||
|
-- difference between the valued amount and the value of the cost basis.
|
||||||
|
--
|
||||||
|
-- If the commodity we are valuing in is not the same as the commodity of the
|
||||||
|
-- cost, this will value the cost at the same date as the primary amount. This
|
||||||
|
-- may not be what you want; for example you may want the cost valued at the
|
||||||
|
-- posting date. If so, let us know and we can change this behaviour.
|
||||||
|
mixedAmountGainAtDate :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
|
||||||
|
mixedAmountGainAtDate priceoracle styles mto d ma =
|
||||||
|
mixedAmountValueAtDate priceoracle styles mto d $ ma `maMinus` mixedAmountCost ma
|
||||||
|
|
||||||
------------------------------------------------------------------------------
|
------------------------------------------------------------------------------
|
||||||
-- Market price lookup
|
-- Market price lookup
|
||||||
|
|
||||||
|
|||||||
@ -303,6 +303,7 @@ calculateReportMatrix rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle startb
|
|||||||
CalcChange -> M.mapWithKey avalue changes
|
CalcChange -> M.mapWithKey avalue changes
|
||||||
CalcBudget -> M.mapWithKey avalue changes
|
CalcBudget -> M.mapWithKey avalue changes
|
||||||
CalcValueChange -> periodChanges valuedStart historical
|
CalcValueChange -> periodChanges valuedStart historical
|
||||||
|
CalcGain -> periodChanges valuedStart historical
|
||||||
cumulative = cumulativeSum avalue nullacct changeamts
|
cumulative = cumulativeSum avalue nullacct changeamts
|
||||||
historical = cumulativeSum avalue startingBalance changes
|
historical = cumulativeSum avalue startingBalance changes
|
||||||
startingBalance = HM.lookupDefault nullacct name startbals
|
startingBalance = HM.lookupDefault nullacct name startbals
|
||||||
|
|||||||
@ -82,6 +82,7 @@ data BalanceCalculation =
|
|||||||
CalcChange -- ^ Sum of posting amounts in the period.
|
CalcChange -- ^ Sum of posting amounts in the period.
|
||||||
| CalcBudget -- ^ Sum of posting amounts and the goal for the period.
|
| CalcBudget -- ^ Sum of posting amounts and the goal for the period.
|
||||||
| CalcValueChange -- ^ Change from previous period's historical end value to this period's historical end value.
|
| CalcValueChange -- ^ Change from previous period's historical end value to this period's historical end value.
|
||||||
|
| CalcGain -- ^ Change from previous period's gain, i.e. valuation minus cost basis.
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Default BalanceCalculation where def = CalcChange
|
instance Default BalanceCalculation where def = CalcChange
|
||||||
@ -319,6 +320,7 @@ balancecalcopt =
|
|||||||
parse = \case
|
parse = \case
|
||||||
"sum" -> Just CalcChange
|
"sum" -> Just CalcChange
|
||||||
"valuechange" -> Just CalcValueChange
|
"valuechange" -> Just CalcValueChange
|
||||||
|
"gain" -> Just CalcGain
|
||||||
"budget" -> Just CalcBudget
|
"budget" -> Just CalcBudget
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
@ -454,16 +456,16 @@ reportOptsToggleStatus s ropts@ReportOpts{statuses_=ss}
|
|||||||
-- to --value, or if --valuechange is called with a valuation type
|
-- to --value, or if --valuechange is called with a valuation type
|
||||||
-- other than -V/--value=end.
|
-- other than -V/--value=end.
|
||||||
valuationTypeFromRawOpts :: RawOpts -> (Costing, Maybe ValuationType)
|
valuationTypeFromRawOpts :: RawOpts -> (Costing, Maybe ValuationType)
|
||||||
valuationTypeFromRawOpts rawopts = (costing, valuation)
|
valuationTypeFromRawOpts rawopts = case (balancecalcopt rawopts, directcost, directval) of
|
||||||
|
(CalcValueChange, _, Nothing ) -> (directcost, Just $ AtEnd Nothing) -- If no valuation requested for valuechange, use AtEnd
|
||||||
|
(CalcValueChange, _, Just (AtEnd _)) -> (directcost, directval) -- If AtEnd valuation requested, use it
|
||||||
|
(CalcValueChange, _, _ ) -> usageError "--valuechange only produces sensible results with --value=end"
|
||||||
|
(CalcGain, Cost, _ ) -> usageError "--gain cannot be combined with --cost"
|
||||||
|
(CalcGain, NoCost, Nothing ) -> (directcost, Just $ AtEnd Nothing) -- If no valuation requested for gain, use AtEnd
|
||||||
|
(_, _, _ ) -> (directcost, directval) -- Otherwise, use requested valuation
|
||||||
where
|
where
|
||||||
costing = if (any ((Cost==) . fst) valuationopts) then Cost else NoCost
|
directcost = if any (== Cost) (map fst valuationopts) then Cost else NoCost
|
||||||
valuation = case balancecalcopt rawopts of
|
directval = lastMay $ mapMaybe snd valuationopts
|
||||||
CalcValueChange -> case directval of
|
|
||||||
Nothing -> Just $ AtEnd Nothing -- If no valuation requested for valuechange, use AtEnd
|
|
||||||
Just (AtEnd _) -> directval -- If AtEnd valuation requested, use it
|
|
||||||
Just _ -> usageError "--valuechange only produces sensible results with --value=end"
|
|
||||||
_ -> directval -- Otherwise, use requested valuation
|
|
||||||
where directval = lastMay $ mapMaybe snd valuationopts
|
|
||||||
|
|
||||||
valuationopts = collectopts valuationfromrawopt rawopts
|
valuationopts = collectopts valuationfromrawopt rawopts
|
||||||
valuationfromrawopt (n,v) -- option name, value
|
valuationfromrawopt (n,v) -- option name, value
|
||||||
@ -524,9 +526,12 @@ journalApplyValuationFromOpts rspec j =
|
|||||||
-- | Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.
|
-- | Like journalApplyValuationFromOpts, but takes PriceOracle as an argument.
|
||||||
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
|
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
|
||||||
journalApplyValuationFromOptsWith rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle =
|
journalApplyValuationFromOptsWith rspec@ReportSpec{_rsReportOpts=ropts} j priceoracle =
|
||||||
journalMapPostings valuation $ costing j
|
case balancecalc_ ropts of
|
||||||
|
CalcGain -> journalMapPostings (\p -> postingTransformAmount (gain p) p) j
|
||||||
|
_ -> journalMapPostings (\p -> postingTransformAmount (valuation p) p) $ costing j
|
||||||
where
|
where
|
||||||
valuation p = maybe id (postingApplyValuation priceoracle styles (periodEnd p) (_rsDay rspec)) (value_ ropts) p
|
valuation p = maybe id (mixedAmountApplyValuation priceoracle styles (periodEnd p) (_rsDay rspec) (postingDate p)) (value_ ropts)
|
||||||
|
gain p = maybe id (mixedAmountApplyGain priceoracle styles (periodEnd p) (_rsDay rspec) (postingDate p)) (value_ ropts)
|
||||||
costing = case cost_ ropts of
|
costing = case cost_ ropts of
|
||||||
Cost -> journalToCost
|
Cost -> journalToCost
|
||||||
NoCost -> id
|
NoCost -> id
|
||||||
@ -545,24 +550,29 @@ mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceO
|
|||||||
-> (DateSpan -> MixedAmount -> MixedAmount)
|
-> (DateSpan -> MixedAmount -> MixedAmount)
|
||||||
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
||||||
case valuationAfterSum ropts of
|
case valuationAfterSum ropts of
|
||||||
Just mc -> \span -> valuation mc span . costing
|
Just mc -> case balancecalc_ ropts of
|
||||||
Nothing -> const id
|
CalcGain -> \span -> gain mc span
|
||||||
|
_ -> \span -> valuation mc span . costing
|
||||||
|
Nothing -> \_span -> id
|
||||||
where
|
where
|
||||||
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
||||||
where err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
|
gain mc span = mixedAmountGainAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
||||||
costing = case cost_ ropts of
|
costing = case cost_ ropts of
|
||||||
Cost -> styleMixedAmount styles . mixedAmountCost
|
Cost -> styleMixedAmount styles . mixedAmountCost
|
||||||
NoCost -> id
|
NoCost -> id
|
||||||
styles = journalCommodityStyles j
|
styles = journalCommodityStyles j
|
||||||
|
err = error "mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
|
||||||
|
|
||||||
-- | If the ReportOpts specify that we are performing valuation after summing amounts,
|
-- | If the ReportOpts specify that we are performing valuation after summing amounts,
|
||||||
-- return Just the commodity symbol we're converting to, otherwise return Nothing.
|
-- return Just of the commodity symbol we're converting to, Just Nothing for the default,
|
||||||
|
-- and otherwise return Nothing.
|
||||||
-- Used for example with historical reports with --value=end.
|
-- Used for example with historical reports with --value=end.
|
||||||
valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
|
valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
|
||||||
valuationAfterSum ropts = case value_ ropts of
|
valuationAfterSum ropts = case value_ ropts of
|
||||||
Just (AtEnd mc) | valueAfterSum -> Just mc
|
Just (AtEnd mc) | valueAfterSum -> Just mc
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
where valueAfterSum = balancecalc_ ropts == CalcValueChange
|
where valueAfterSum = balancecalc_ ropts == CalcValueChange
|
||||||
|
|| balancecalc_ ropts == CalcGain
|
||||||
|| balanceaccum_ ropts /= PerPeriod
|
|| balanceaccum_ ropts /= PerPeriod
|
||||||
|
|
||||||
|
|
||||||
|
|||||||
@ -290,7 +290,9 @@ balancemode = hledgerCommandMode
|
|||||||
, "(case insensitive substring match)."
|
, "(case insensitive substring match)."
|
||||||
])
|
])
|
||||||
,flagNone ["valuechange"] (setboolopt "valuechange")
|
,flagNone ["valuechange"] (setboolopt "valuechange")
|
||||||
"show change of value of period-end historical balances"
|
"show total change of value of period-end historical balances (caused by deposits, withdrawals, market price fluctuations)"
|
||||||
|
,flagNone ["gain"] (setboolopt "gain")
|
||||||
|
"show unrealised capital gain/loss (historical balance value minus cost basis)"
|
||||||
,flagNone ["change"] (setboolopt "change")
|
,flagNone ["change"] (setboolopt "change")
|
||||||
"accumulate amounts from column start to column end (in multicolumn reports, default)"
|
"accumulate amounts from column start to column end (in multicolumn reports, default)"
|
||||||
,flagNone ["cumulative"] (setboolopt "cumulative")
|
,flagNone ["cumulative"] (setboolopt "cumulative")
|
||||||
@ -639,6 +641,9 @@ multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $
|
|||||||
mtitle = case (balancecalc_, balanceaccum_) of
|
mtitle = case (balancecalc_, balanceaccum_) of
|
||||||
(CalcValueChange, PerPeriod ) -> "Period-end value changes"
|
(CalcValueChange, PerPeriod ) -> "Period-end value changes"
|
||||||
(CalcValueChange, Cumulative ) -> "Cumulative period-end value changes"
|
(CalcValueChange, Cumulative ) -> "Cumulative period-end value changes"
|
||||||
|
(CalcGain, PerPeriod ) -> "Incremental gain"
|
||||||
|
(CalcGain, Cumulative ) -> "Cumulative gain"
|
||||||
|
(CalcGain, Historical ) -> "Historical gain"
|
||||||
(_, PerPeriod ) -> "Balance changes"
|
(_, PerPeriod ) -> "Balance changes"
|
||||||
(_, Cumulative ) -> "Ending balances (cumulative)"
|
(_, Cumulative ) -> "Ending balances (cumulative)"
|
||||||
(_, Historical) -> "Ending balances (historical)"
|
(_, Historical) -> "Ending balances (historical)"
|
||||||
|
|||||||
@ -35,6 +35,7 @@ Many of these work with the higher-level commands as well.
|
|||||||
- or actual and planned balance changes ([`--budget`](#budget-report))
|
- or actual and planned balance changes ([`--budget`](#budget-report))
|
||||||
- or value of balance changes ([`-V`](#valuation-type))
|
- or value of balance changes ([`-V`](#valuation-type))
|
||||||
- or change of balance values ([`--valuechange`](#balance-report-types))
|
- or change of balance values ([`--valuechange`](#balance-report-types))
|
||||||
|
- or unrealised capital gain/loss ([`--gain`](#balance-report-types))
|
||||||
|
|
||||||
..in..
|
..in..
|
||||||
|
|
||||||
@ -419,7 +420,9 @@ It is one of:
|
|||||||
- `--sum` : sum the posting amounts (**default**)
|
- `--sum` : sum the posting amounts (**default**)
|
||||||
- `--budget` : like --sum but also show a goal amount
|
- `--budget` : like --sum but also show a goal amount
|
||||||
- `--valuechange` : show the change in period-end historical balance values
|
- `--valuechange` : show the change in period-end historical balance values
|
||||||
<!-- - `--gain` : show the change in period-end historical balances values caused by market price fluctuations -->
|
(caused by deposits, withdrawals, and/or market price fluctuations)
|
||||||
|
- `--gain` : show the unrealised capital gain/loss, (the current valued balance
|
||||||
|
minus each amount's original cost)
|
||||||
|
|
||||||
**Accumulation type:**\
|
**Accumulation type:**\
|
||||||
Which postings should be included in each cell's calculation.
|
Which postings should be included in each cell's calculation.
|
||||||
@ -445,7 +448,7 @@ It is one of:
|
|||||||
- no valuation, show amounts in their original commodities (**default**)
|
- no valuation, show amounts in their original commodities (**default**)
|
||||||
- `--value=cost[,COMM]` : no valuation, show amounts converted to cost
|
- `--value=cost[,COMM]` : no valuation, show amounts converted to cost
|
||||||
- `--value=then[,COMM]` : show value at transaction dates
|
- `--value=then[,COMM]` : show value at transaction dates
|
||||||
- `--value=end[,COMM]` : show value at period end date(s) (**default with `--valuechange`**)
|
- `--value=end[,COMM]` : show value at period end date(s) (**default with `--valuechange`, `--gain`**)
|
||||||
- `--value=now[,COMM]` : show value at today's date
|
- `--value=now[,COMM]` : show value at today's date
|
||||||
- `--value=YYYY-MM-DD[,COMM]` : show value at another date
|
- `--value=YYYY-MM-DD[,COMM]` : show value at another date
|
||||||
|
|
||||||
|
|||||||
@ -60,7 +60,9 @@ compoundBalanceCommandMode CompoundBalanceCommandSpec{..} =
|
|||||||
([flagNone ["sum"] (setboolopt "sum")
|
([flagNone ["sum"] (setboolopt "sum")
|
||||||
"show sum of posting amounts (default)"
|
"show sum of posting amounts (default)"
|
||||||
,flagNone ["valuechange"] (setboolopt "valuechange")
|
,flagNone ["valuechange"] (setboolopt "valuechange")
|
||||||
"show change of value of period-end historical balances"
|
"show total change of period-end historical balance value (caused by deposits, withdrawals, market price fluctuations)"
|
||||||
|
,flagNone ["gain"] (setboolopt "gain")
|
||||||
|
"show unrealised capital gain/loss (historical balance value minus cost basis)"
|
||||||
,flagNone ["budget"] (setboolopt "budget")
|
,flagNone ["budget"] (setboolopt "budget")
|
||||||
"show sum of posting amounts compared to budget goals defined by periodic transactions\n "
|
"show sum of posting amounts compared to budget goals defined by periodic transactions\n "
|
||||||
|
|
||||||
@ -123,18 +125,23 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
|
|||||||
-- "2008/01/01-2008/12/31", not "2008").
|
-- "2008/01/01-2008/12/31", not "2008").
|
||||||
titledatestr = case balanceaccumulation of
|
titledatestr = case balanceaccumulation of
|
||||||
Historical -> showEndDates enddates
|
Historical -> showEndDates enddates
|
||||||
_ -> showDateSpan requestedspan
|
_ -> showDateSpan requestedspan
|
||||||
where
|
where
|
||||||
enddates = map (addDays (-1)) . mapMaybe spanEnd $ cbrDates cbr -- these spans will always have a definite end date
|
enddates = map (addDays (-1)) . mapMaybe spanEnd $ cbrDates cbr -- these spans will always have a definite end date
|
||||||
requestedspan = reportSpan j rspec
|
requestedspan = reportSpan j rspec
|
||||||
|
|
||||||
-- when user overrides, add an indication to the report title
|
-- when user overrides, add an indication to the report title
|
||||||
-- Do we need to deal with overridden BalanceCalculation?
|
-- Do we need to deal with overridden BalanceCalculation?
|
||||||
mtitleclarification = flip fmap mbalanceAccumulationOverride $ \case
|
mtitleclarification = case (balancecalc_, balanceaccumulation, mbalanceAccumulationOverride) of
|
||||||
PerPeriod | changingValuation -> "(Period-End Value Changes)"
|
(CalcValueChange, PerPeriod, _ ) -> Just "(Period-End Value Changes)"
|
||||||
PerPeriod -> "(Balance Changes)"
|
(CalcValueChange, Cumulative, _ ) -> Just "(Cumulative Period-End Value Changes)"
|
||||||
Cumulative -> "(Cumulative Ending Balances)"
|
(CalcGain, PerPeriod, _ ) -> Just "(Incremental Gain)"
|
||||||
Historical -> "(Historical Ending Balances)"
|
(CalcGain, Cumulative, _ ) -> Just "(Cumulative Gain)"
|
||||||
|
(CalcGain, Historical, _ ) -> Just "(Historical Gain)"
|
||||||
|
(_, _, Just PerPeriod ) -> Just "(Balance Changes)"
|
||||||
|
(_, _, Just Cumulative) -> Just "(Cumulative Ending Balances)"
|
||||||
|
(_, _, Just Historical) -> Just "(Historical Ending Balances)"
|
||||||
|
_ -> Nothing
|
||||||
|
|
||||||
valuationdesc =
|
valuationdesc =
|
||||||
(case cost_ of
|
(case cost_ of
|
||||||
@ -149,9 +156,9 @@ compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=r
|
|||||||
Nothing -> "")
|
Nothing -> "")
|
||||||
|
|
||||||
changingValuation = case (balancecalc_, balanceaccum_) of
|
changingValuation = case (balancecalc_, balanceaccum_) of
|
||||||
(CalcValueChange, PerPeriod) -> True
|
(CalcValueChange, PerPeriod) -> True
|
||||||
(CalcValueChange, Cumulative) -> True
|
(CalcValueChange, Cumulative) -> True
|
||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
-- make a CompoundBalanceReport.
|
-- make a CompoundBalanceReport.
|
||||||
cbr' = compoundBalanceReport rspec{_rsReportOpts=ropts'} j cbcqueries
|
cbr' = compoundBalanceReport rspec{_rsReportOpts=ropts'} j cbcqueries
|
||||||
|
|||||||
83
hledger/test/journal/gain.test
Normal file
83
hledger/test/journal/gain.test
Normal file
@ -0,0 +1,83 @@
|
|||||||
|
<
|
||||||
|
P 1999/12/01 stock 1 A
|
||||||
|
P 2000/01/01 stock 2 A
|
||||||
|
P 2000/02/01 stock 3 A
|
||||||
|
|
||||||
|
P 1999/12/01 B 1 A
|
||||||
|
P 2000/01/01 B 5 A
|
||||||
|
P 2000/02/01 B 6 A
|
||||||
|
|
||||||
|
1999/12/01
|
||||||
|
(assets:fake) 1 stock
|
||||||
|
(assets:fake) 1 A
|
||||||
|
(assets:fake) 1 B
|
||||||
|
|
||||||
|
1999/12/01
|
||||||
|
(assets:old) 2 stock @ 2 A
|
||||||
|
|
||||||
|
2000/01/01
|
||||||
|
(assets:new) 1 stock @ 3 A
|
||||||
|
(assets:b) 1 stock @ 3 B
|
||||||
|
|
||||||
|
# 1. multicolumn balance report showing changes in gain
|
||||||
|
$ hledger -f- bal -M --gain --no-total
|
||||||
|
Incremental gain in 1999-12-01..2000-02-29, valued at period ends:
|
||||||
|
|
||||||
|
|| 1999-12 2000-01 2000-02
|
||||||
|
============++===========================
|
||||||
|
assets:b || 0 -13 A -2 A
|
||||||
|
assets:new || 0 -1 A 1 A
|
||||||
|
assets:old || -2 A 2 A 2 A
|
||||||
|
|
||||||
|
# 2. multibalance report showing changes in gain including some historical postings
|
||||||
|
$ hledger -f- bal -M --gain -b 2000 --no-total
|
||||||
|
Incremental gain in 2000-01-01..2000-02-29, valued at period ends:
|
||||||
|
|
||||||
|
|| Jan Feb
|
||||||
|
============++=============
|
||||||
|
assets:b || -13 A -2 A
|
||||||
|
assets:new || -1 A 1 A
|
||||||
|
assets:old || 2 A 2 A
|
||||||
|
|
||||||
|
# 3. historical gain report
|
||||||
|
$ hledger -f- bal -M --gain -b 2000 --no-total --historical
|
||||||
|
Historical gain in 2000-01-01..2000-02-29, valued at period ends:
|
||||||
|
|
||||||
|
|| 2000-01-31 2000-02-29
|
||||||
|
============++========================
|
||||||
|
assets:b || -13 A -15 A
|
||||||
|
assets:new || -1 A 0
|
||||||
|
assets:old || 0 2 A
|
||||||
|
|
||||||
|
# 4. use a different valuation strategy
|
||||||
|
$ hledger -f- bal -M --gain --no-total --value=2000-02-01
|
||||||
|
Incremental gain in 1999-12-01..2000-01-31, valued at 2000-02-01:
|
||||||
|
|
||||||
|
|| 1999-12 2000-01
|
||||||
|
============++==================
|
||||||
|
assets:b || 0 -15 A
|
||||||
|
assets:old || 2 A 0
|
||||||
|
|
||||||
|
# 5. use a different valuation strategy for historical
|
||||||
|
$ hledger -f- bal -M --gain --no-total --value=2000-02-01 -b 2000 --historical
|
||||||
|
Historical gain in 2000-01, valued at 2000-02-01:
|
||||||
|
|
||||||
|
|| 2000-01-31
|
||||||
|
============++============
|
||||||
|
assets:b || -15 A
|
||||||
|
assets:old || 2 A
|
||||||
|
|
||||||
|
# 6. also works in balancesheet
|
||||||
|
$ hledger -f- bs -M --gain --no-total
|
||||||
|
Balance Sheet 1999-12-31..2000-02-29 (Historical Gain), valued at period ends
|
||||||
|
|
||||||
|
|| 1999-12-31 2000-01-31 2000-02-29
|
||||||
|
=============++====================================
|
||||||
|
Assets ||
|
||||||
|
-------------++------------------------------------
|
||||||
|
assets:b || 0 -13 A -15 A
|
||||||
|
assets:new || 0 -1 A 0
|
||||||
|
assets:old || -2 A 0 2 A
|
||||||
|
=============++====================================
|
||||||
|
Liabilities ||
|
||||||
|
-------------++------------------------------------
|
||||||
Loading…
Reference in New Issue
Block a user