diff options
author | Ben Sima <ben@bsima.me> | 2020-10-28 21:53:12 -0400 |
---|---|---|
committer | Ben Sima <ben@bsima.me> | 2020-10-28 21:53:12 -0400 |
commit | 3e767bf301e7b00c708275ed3f55abb57951f150 (patch) | |
tree | ae863b605494eccd6d46884c47ba29a4b275900d | |
parent | 632ece1210035d63f66d046180959e0436a3fc48 (diff) |
update fire calculations, merge with overview script
-rwxr-xr-x | hledger-fire.hs | 86 | ||||
-rwxr-xr-x | hledger-overview.hs | 161 |
2 files changed, 125 insertions, 122 deletions
diff --git a/hledger-fire.hs b/hledger-fire.hs index 68ea5a8..8b13789 100755 --- a/hledger-fire.hs +++ b/hledger-fire.hs @@ -1,87 +1 @@ -#!/usr/bin/env runhaskell --- | Calculations for FIRE (financial independence, retire early) -module Main where -import Data.Decimal (Decimal(..), DecimalRaw(..), roundTo, divide) -import Data.Either (fromRight) -import qualified Data.List as List -import Data.Text (pack) -import Data.Time.Calendar (Day, toGregorian) -import Data.Time.Clock (UTCTime(utctDay), getCurrentTime) -import Hledger -data Config = Config - { age :: Decimal - } - -main = do - j <- getJournal - today <- getCurrentTime >>= return . utctDay - let (thisyear, _, _) = toGregorian today - let cfg = Config { age = (fromInteger thisyear) - 1992 } - say [ "savings rate:", show $ savingsRate j today ] - say [ "target fund:", show $ targetFund j today ] - let n = whenFreedom j today - say [ "when free:", show $ n, "months" - , "(I'll be", show $ roundTo 1 $ (n/12) + (age cfg), "years old)" - ] - -say = putStrLn . unwords - -getJournal :: IO Journal -getJournal = do - jp <- defaultJournalPath - let opts = definputopts { auto_ = True } - ej <- readJournalFile opts jp - return $ fromRight undefined ej - --- | Helper for getting the total out of a balance report. -getTotal :: Journal -> Day -> String -> Quantity -getTotal j d q = head $ map aquantity $ total - where - opts = defreportopts { balancetype_ = CumulativeChange } - (query, _) = parseQuery d $ pack q - (_, (Mixed total)) = balanceReport opts query j - --- | These are the accounts that I consider a part of my savings and not my --- cash-spending accounts. -savingsAccounts :: [String] -savingsAccounts = - [ "as:me:save", "as:me:vest" ] - --- | Savings rate is a FIRE staple. Basically take your savings and divide it by --- your income on a monthly basis. --- -savingsRate :: Journal -> Day -> Quantity -savingsRate j d = roundTo 2 $ allSavings / (- allIncome) - -- gotta flip the sign because income is negative - where - allSavings = getTotal j d query - query = List.intercalate " " $ savingsAccounts ++ ["cur:USD", "-p 'from 2019-11-01'"] - allIncome = getTotal j d "^in" - --- | The target fund is simply 25x your annual expenditure. --- --- This is going to be incomplete until I have a full year of --- expenses.. currently, I just use my most recent quarter times 4 as a proxy --- for the yearly expenses. --- --- Assumptions: 4% withdrawal rate, 3-5% return on investments. --- -targetFund :: Journal -> Day -> Quantity -targetFund j d = 25 * yearlyExpenses - where - yearlyExpenses = 4 * quarterlyExpenses - quarterlyExpenses = sum $ map aquantity $ total - (query, _) = parseQuery d $ pack "^ex -p lastquarter cur:USD" - (_, (Mixed total)) = balanceReport opts query j - opts = defreportopts - --- | How long until I can live off of my savings and investment returns? --- --- Return integer is number of months until I'm free. --- -whenFreedom :: Journal -> Day -> Quantity -whenFreedom j d = roundTo 1 $ targetFund j d / monthlySavings - where - monthlySavings = sum $ map (getTotal j d) $ map appendMonthly savingsAccounts - appendMonthly s = s ++ " --monthly" diff --git a/hledger-overview.hs b/hledger-overview.hs index c97dee6..bdddff4 100755 --- a/hledger-overview.hs +++ b/hledger-overview.hs @@ -1,48 +1,86 @@ #!/usr/bin/env runhaskell +{-# LANGUAGE OverloadedStrings #-} + -- | Calculates and displays an overview of my finances. module Main where -import Data.Decimal (Decimal) +import Data.Decimal (Decimal (..), DecimalRaw (..), divide, roundTo) import Data.Either (fromRight) -import Data.Text (pack) -import Data.Time.Calendar (Day) +import Data.Function ((&)) +import qualified Data.List as List +import Data.Text (Text, pack) +import qualified Data.Text as T +import qualified Data.Text.IO as IO +import Data.Time.Calendar (Day, toGregorian) import Data.Time.Clock (UTCTime (utctDay), getCurrentTime) import Hledger +data Config = Config + { age :: Decimal + } + main = do j <- getJournal today <- getCurrentTime >>= return . utctDay - let bal = getTotal j today Nothing - let balUSD = getTotal j today $ Just $ pack "USD" + let bal = getTotal j today $ defreportopts + let balUSD = getTotal j today $ defreportopts {value_ = inUsd} sec "cash balances" - row "simple" (bal "^as:me:cash:simple status:! status:*") Nothing - row "wallet" (bal "^as:me:cash:wallet") Nothing - row " disc" (bal "^li:me:cred:discover status:*") Nothing - row " citi" (bal "^li:me:cred:citi status:*") Nothing - row " btc" (bal "^as cur:BTC") Nothing + row "simple" (prn $ bal "^as:me:cash:simple status:! status:*") Nothing + row "wallet" (prn $ bal "^as:me:cash:wallet") Nothing + row " disc" (prn $ bal "^li:me:cred:discover status:*") Nothing + row " citi" (prn $ bal "^li:me:cred:citi status:*") Nothing + row " btc" (prn $ bal "^as cur:BTC") Nothing sec "metrics" - let netLiquid = bal "^as:me:cash ^li:me:cred cur:USD" - let netWorth = balUSD "^as ^li" - row " in - ex" (bal "^in ^ex cur:USD -p thismonth") $ Just "keep this negative to make progress" - row "cred load" netLiquid $ Just "net liquid: credit spending minus cash assets. keep it positive" - row "net worth" netWorth Nothing - row " level" (level netWorth) Nothing + let netLiquid = roundTo 2 $ bal "^as:me:cash ^li:me:cred cur:USD" + let netWorth = roundTo 2 $ balUSD "^as ^li" + row " in - ex" (prn $ bal "^in ^ex cur:USD") $ Just "keep this negative to make progress" + row "cred load" (prn netLiquid) $ Just "net liquid: credit spending minus cash assets. keep it positive" + row "net worth" (prn netWorth) Nothing + row " level" (pr $ level netWorth) Nothing sec "trivials" - let trivialWorth = trivial * netWorth - let trivialLiquid = trivial * netLiquid - row " net" trivialWorth Nothing - row "liquid" trivialLiquid Nothing + let trivialWorth = roundTo 2 $ trivial * netWorth + let trivialLiquid = roundTo 2 $ trivial * netLiquid + row " net" (pr trivialWorth) Nothing + row "liquid" (pr trivialLiquid) Nothing + + sec "fire" + let (thisyear, _, _) = toGregorian today + let cfg = Config {age = (fromInteger thisyear) - 1992} + let n = whenFreedom j today + let ageFree = roundTo 1 $ (n / 12) + (age cfg) + row "savings rate" (pr $ savingsRate j today) Nothing + row " target fund" (prn $ roundTo 2 $ targetFund j today) Nothing + row " when free" ((pr n) <> " months") $ Just $ "I'll be " <> pr ageFree <> " years old" +sec :: String -> IO () sec label = putStrLn $ "\n" <> label <> ":" -row label value Nothing = putStrLn $ gap <> label <> ":" <> gap <> show value -row label value (Just nb) = putStrLn $ gap <> label <> ":" <> gap <> show value <> gap <> "\t(" <> nb <> ")" +pr :: Show s => s -> Text +pr = pack . show +row :: Text -> Text -> Maybe Text -> IO () +row label value Nothing = IO.putStrLn $ gap <> label <> ":" <> gap <> value +row label value (Just nb) = IO.putStrLn $ gap <> label <> ":" <> gap <> value <> gap <> "\t(" <> nb <> ")" + +gap :: Text gap = " " +-- Pretty-print a number. From https://stackoverflow.com/a/61070523/1146898 +prn :: Quantity -> Text +prn d = T.intercalate "." $ case T.splitOn "." $ T.pack $ show d of + x : xs -> (T.pack . reverse . go . reverse . T.unpack) x : xs + xs -> xs + where + go (x : y : z : []) = x : y : z : [] + go (x : y : z : ['-']) = x : y : z : ['-'] + go (x : y : z : xs) = x : y : z : ',' : go xs + go xs = xs + +-- | There's levels to life, a proxy metric for what level you're at is your net +-- worth rounded down to the nearest power of 10. level :: Decimal -> Integer level = floor . logBase 10 . realToFrac @@ -50,23 +88,21 @@ level = floor . logBase 10 . realToFrac -- uses the upper bound of that range. -- -- From <https://ofdollarsanddata.com/climbing-the-wealth-ladder/> +trivial :: Quantity trivial = 0.001 -getTotal :: Journal -> Day -> Maybe CommoditySymbol -> String -> Quantity -getTotal j d commodity q = sum $ map aquantity $ total +inUsd :: Maybe ValuationType +inUsd = Just $ AtNow $ Just "USD" + +getTotal :: Journal -> Day -> ReportOpts -> String -> Quantity +getTotal j d opts q = sum $ map aquantity $ total where - value = case commodity of - Nothing -> Nothing - Just txt -> Just $ AtNow $ Just txt - opts = - defreportopts - { balancetype_ = CumulativeChange, - real_ = True, - today_ = Just d, - value_ = value + opts' = + opts + { today_ = Just d } (query, _) = parseQuery d $ pack q - (_, (Mixed total)) = balanceReport opts query j + (_, (Mixed total)) = balanceReport opts' query j getJournal :: IO Journal getJournal = do @@ -75,6 +111,59 @@ getJournal = do ej <- readJournalFile opts jp return $ fromRight undefined ej +-- | These are the accounts that I consider a part of my savings and not my +-- cash-spending accounts. +savingsAccounts :: [String] +savingsAccounts = + ["as:me:save", "as:me:vest"] + +-- | Savings rate is a FIRE staple. Basically take your savings and divide it by +-- your income on a monthly basis. +savingsRate :: Journal -> Day -> Quantity +savingsRate j d = roundTo 2 $ allSavings / allIncome + where + allSavings = getTotal j d (defreportopts {value_ = inUsd}) query + query = List.intercalate " " $ savingsAccounts + -- gotta flip the sign because income is negative + allIncome = - getTotal j d (defreportopts {value_ = inUsd}) "^in" + +-- | The target fund is simply 25x your annual expenditure. +-- +-- This is going to be incomplete until I have a full year of +-- expenses.. currently, I just use my most recent quarter times 4 as a proxy +-- for the yearly expenses. +-- +-- Assumptions: 4% withdrawal rate, 3-5% return on investments. +targetFund :: Journal -> Day -> Quantity +targetFund j d = 25 * yearlyExpenses + where + yearlyExpenses = sum $ map aquantity $ total + (query, _) = parseQuery d $ pack "^ex" + (_, (Mixed total)) = balanceReport opts query j + opts = + defreportopts + { -- idk what the '2020 4' is for, but this actually results in the yearly + -- report for some reason + period_ = QuarterPeriod 2020 4, + value_ = Just $ AtNow $ Just "USD", + today_ = Just d + } + +-- | How long until I can live off of my savings and investment returns? +-- +-- Return integer is number of months until I'm free. +whenFreedom :: Journal -> Day -> Quantity +whenFreedom j d = roundTo 1 $ targetFund j d / monthlySavings + where + (year, month, _) = toGregorian d + -- I have data going back to 2018.12 + monthsSinceBeginning = fromInteger $ (year - 2019) * 12 + toInteger month + 1 + monthlySavings = + savingsAccounts + & map (getTotal j d (defreportopts {value_ = inUsd, period_ = MonthPeriod 2020 10})) + & sum + & \n -> (n / monthsSinceBeginning) + -- | Escape velocity: -- -- In physics it is basically the movement of an object away from the earth, @@ -92,9 +181,9 @@ getJournal = do -- -- v = sqrt(2 * 3% * li / net_worth) -- --- v = sqrt(2 * 3% * 18534.54 / 17580.93) +-- v = sqrt(2 * 3% * 20,000 / 100,000) -- --- v = 0.25 +-- v = 0.1095 -- -- I don't know what this means... maybe my money must be growing at a 25% rate in -- order to cover the debt? I need to think about this equation some more. |