lib: roi now supports --value/--infer-value

This commit is contained in:
Dmitry Astapov 2021-01-12 10:06:32 +00:00 committed by Simon Michael
parent 9869624c5c
commit fc32f22f86
2 changed files with 45 additions and 10 deletions

View File

@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ParallelListComp #-} {-# LANGUAGE ParallelListComp #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
{-| {-|
The @roi@ command prints internal rate of return and time-weighted rate of return for and investment. The @roi@ command prints internal rate of return and time-weighted rate of return for and investment.
@ -18,6 +19,7 @@ import Data.Time.Calendar
import Text.Printf import Text.Printf
import Data.Function (on) import Data.Function (on)
import Data.List import Data.List
import Data.Maybe (fromMaybe)
import Numeric.RootFinding import Numeric.RootFinding
import Data.Decimal import Data.Decimal
import qualified Data.Text as T import qualified Data.Text as T
@ -55,12 +57,21 @@ data OneSpan = OneSpan
roi :: CliOpts -> Journal -> IO () roi :: CliOpts -> Journal -> IO ()
roi CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{rsOpts=ReportOpts{..}}} j = do
d <- getCurrentDay d <- getCurrentDay
-- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports".
let
tvalue t@Transaction{..} = t{tpostings=map pvalue tpostings}
where
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
prettyTables = pretty_tables_ ropts prettyTables = pretty_tables_
makeQuery flag = do makeQuery flag = do
q <- either usageError (return . fst) . parseQuery d . T.pack $ stringopt flag rawopts q <- either usageError (return . fst) . parseQuery d . T.pack $ stringopt flag rawopts
return . simplifyQuery $ And [queryFromFlags ropts{period_=PeriodAll}, q] return . simplifyQuery $ And [queryFromFlags ropts{period_=PeriodAll}, q]
@ -69,14 +80,14 @@ roi CliOpts{rawopts_=rawopts, reportspec_=rspec} j = do
pnlQuery <- makeQuery "pnl" pnlQuery <- makeQuery "pnl"
let let
trans = dbg3 "investments" $ jtxns $ filterJournalTransactions investmentsQuery j trans = dbg3 "investments" $ map tvalue $ jtxns $ filterJournalTransactions investmentsQuery j
journalSpan = journalSpan =
let dates = map transactionDate2 trans in let dates = map transactionDate2 trans in
DateSpan (Just $ minimum dates) (Just $ addDays 1 $ maximum dates) DateSpan (Just $ minimum dates) (Just $ addDays 1 $ maximum dates)
requestedSpan = periodAsDateSpan $ period_ ropts requestedSpan = periodAsDateSpan period_
requestedInterval = interval_ ropts requestedInterval = interval_
wholeSpan = spanDefaultsFrom requestedSpan journalSpan wholeSpan = spanDefaultsFrom requestedSpan journalSpan
@ -265,4 +276,6 @@ unMix :: MixedAmount -> Quantity
unMix a = unMix a =
case (unifyMixedAmount $ mixedAmountCost a) of case (unifyMixedAmount $ mixedAmountCost a) of
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." ++
"\nFor example, \"--value cost,<commodity> --infer-value\", where commodity is the one that was used to pay for the investment."

View File

@ -230,13 +230,35 @@ hledger -f- roi -p 2019-11
hledger -f- roi -p 2019-11 --inv Investment --pnl PnL hledger -f- roi -p 2019-11 --inv Investment --pnl PnL
<<< <<<
2019/11/01 Example 2019/11/01 Example
Assets:Checking -1 A Assets:Checking -100 A
Investment 10 B Investment 10 B
2019/11/02 Example 2019/11/02 Example
Investment -10 B @@ 1 A Investment -10 B @@ 100 A
Assets:Checking 12 A Assets:Checking 101 A
Unrealized PnL Unrealized PnL
>>>2 >>>2
hledger: Amounts could not be converted to a single cost basis: ["10 B","-10 B @@ 1 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.
For example, "--value cost,<commodity> --infer-value", where commodity is the one that was used to pay for the investment.
>>>=1 >>>=1
# 10. Forcing valuation via --value
hledger -f- roi -p 2019-11 --inv Investment --pnl PnL --value cost,A --infer-value
<<<
2019/11/01 Example
Assets:Checking -100 A
Investment 10 B
2019/11/02 Example
Investment -10 B @@ 100 A
Assets:Checking 101 A
Unrealized PnL
>>>
+---++------------+------------++---------------+----------+-------------+-----++----------+-------+
| || Begin | End || Value (begin) | Cashflow | Value (end) | PnL || IRR | TWR |
+===++============+============++===============+==========+=============+=====++==========+=======+
| 1 || 2019-11-01 | 2019-11-30 || 0 | -1 | 0 | 1 || 3678.34% | 0.00% |
+---++------------+------------++---------------+----------+-------------+-----++----------+-------+
>>>=0