summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Sima <ben@bsima.me>2021-05-16 09:42:00 -0400
committerBen Sima <ben@bsima.me>2021-05-16 09:42:00 -0400
commit57187bb97dc47bfb810471820fba33e120b12e89 (patch)
tree408f0959ba24541cb43f5467fd306afcbb481ec3
parent0b027e8f3e3be88516245354793c5e073a6397e3 (diff)
lots of stuff
add banner, currency arg, condense display, fix some account queries
-rwxr-xr-xhledger-overview.hs264
1 files changed, 116 insertions, 148 deletions
diff --git a/hledger-overview.hs b/hledger-overview.hs
index 5418059..4676958 100755
--- a/hledger-overview.hs
+++ b/hledger-overview.hs
@@ -1,6 +1,8 @@
#!/usr/bin/env runhaskell
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
@@ -20,6 +22,8 @@ import Data.Time.Calendar (Day, fromGregorian, toGregorian)
import Data.Time.Clock (UTCTime (..), diffTimeToPicoseconds, diffUTCTime, getCurrentTime)
import Hledger
import Rainbow
+import System.Environment (getArgs)
+import qualified System.Process as Process
today :: IO Day
today = getCurrentTime >>= return . utctDay
@@ -32,67 +36,62 @@ run f = do
return $ f j t
main = do
+ let janj = Just . AtNow . Just
+ let banner txt = Process.callProcess "figlet" ["-f", "small", txt ]
+ (cur, value_) <-
+ getArgs
+ >>= \case
+ ["sat"] -> banner "sats" >> pure (SAT, janj "sat")
+ ["sats"] -> banner "sats" >> pure (SAT, janj "sat")
+ ["btc"] -> banner "bitcion" >> pure (BTC, janj "BTC")
+ _ -> banner "fiat" >> pure (USD, janj "USD")
+
+ let reportopts = defreportopts {value_ = value_}
j <- defaultJournal
t <- today
- let bal = getTotal j t $ defreportopts
- let balVal = getTotal j t $ defreportopts {value_ = inUsdNow}
+ let bal = getTotal j t reportopts
sec "cash balances"
- row "simple" (bal "^as:me:cash:simple status:! status:*") Nothing
- row "cashap" (bal "^as:me:cash:cashapp 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
- let btcBal q = sum . map aquantity $ getTotalAmounts j t defreportopts q
- let btcBalUSD q = sum . map aquantity $ getTotalAmounts j t (defreportopts {value_ = inUsdNow}) q
- row " btc" (Target 4 $ btcBal "^as cur:BTC") $ Just $ display $ btcBalUSD "^as cur:BTC"
+ row "cashap" (cur $ bal "^as:me:cash:cashapp status:! status:*") Nothing
+ row "wallet" (cur $ bal "^as:me:cash:wallet") Nothing
+ row " cse" (cur $ bal "^as:me:cash:cse") Nothing
+ row " disc" (cur $ bal "^li:me:cred:discover status:*") Nothing
+ row " citi" (cur $ bal "^li:me:cred:citi status:*") Nothing
+ -- net cash is limited to USD because that is what I can effectively spend
let netCash = bal "^as:me:cash ^li:me:cred cur:USD"
- let netWorth = balVal "^as ^li"
+ let netWorth = bal "^as ^li"
let (year, month, _) = toGregorian t
- let expectedLevel = fromJust $ Map.lookup (roundTo 2 $ (fromIntegral year + fromIntegral month / 12) - (1992 + 7 / 12)) levelSchedule
+ let expectedLevel = fromJust $ Map.lookup (roundTo 2 $ (fromIntegral year + fromIntegral month / 12) - (1992 + 7 / 12)) $ levelSchedule cur
let expectedNetWorth = unlevel expectedLevel
- let monthlyNut = nut t $ balVal "^ex"
- let thisMonth = balVal "^ex date:thismonth"
+ let monthlyNut = nut t $ bal "^ex:me:want ^ex:me:need"
+ let thisMonth = bal "^ex:me:want ^ex:me:need date:thismonth"
sec "metrics"
- row " in - ex" (Limit 0 $ bal "^in ^ex" / monthsSinceBeginning t) $ Just "keep this negative to make progress"
+ row " in-ex" (Limit 0 $ bal "^in ^ex:me:want ^ex:me:need" / monthsSinceBeginning t) $ Just "keep this negative to make progress"
+ row " li:as" (Percent_ $ 100 * (- bal "^li") / bal "^as") Nothing
row "cred load" (Target 0 netCash) $ Just "credit spending minus cash. keep it positive"
- row "month exp" (Limit monthlyNut thisMonth) $ Just $ "avg: " <> (display $ Diff $ monthlyNut - thisMonth)
+ row "month nut" (Limit monthlyNut thisMonth) $ Just $ "avg: " <> (display $ Diff $ monthlyNut - thisMonth)
+ row " trivial" (pr $ roundTo 2 $ trivial * netWorth) Nothing
+ let (_, _, runwayMo) = runway j t reportopts
+ row " runway" (Target 36 runwayMo) $ Just "want: 36 months"
+ let (_, _, ramenMo) = ramen j t reportopts
+ row " ramen" (Target 3 ramenMo) $ Just "want: 3 months"
+ let (thisyear, _, _) = toGregorian t
+ let age = (fromInteger thisyear) - 1992
+ let n = whenFreedom j t reportopts
+ let ageFree = roundTo 1 $ (n / 12) + age :: Decimal
+ row "fire rate" (Percent_ $ savingsRate j t reportopts) Nothing
+ row "fire fund" (targetFund j t reportopts) Nothing
+ row "when free" (Months_ n) $ Just $ "I'll be " <> pr ageFree <> " years old"
sec "plan"
- row "net worth" (Target expectedNetWorth $ netWorth) $ Just $ "plan: " <> display expectedNetWorth
+ row "net worth" (Target expectedNetWorth $ netWorth) $ Just $ "plan: " <> display (cur expectedNetWorth)
row " level" (Target expectedLevel $ level netWorth) $ Just $ "plan: " <> display expectedLevel
let levelup n = level netWorth & (+ n) & roundTo' floor 1 & unlevel & \target -> target - netWorth
- row " next" (levelup 0.1) $ Just $ display $ roundTo' floor 1 $ level netWorth + 0.1
- row " nnext" (levelup 0.2) $ Just $ display $ roundTo' floor 1 $ level netWorth + 0.2
- row " nnnext" (levelup 0.3) $ Just $ display $ roundTo' floor 1 $ level netWorth + 0.3
-
- sec "trivials"
- let trivialWorth = roundTo 2 $ trivial * netWorth
- let trivialCash = roundTo 2 $ trivial * netCash
- row " net" (pr trivialWorth) Nothing
- row " cash" (pr trivialCash) Nothing
-
- sec "fire"
- let (thisyear, _, _) = toGregorian t
- let age = (fromInteger thisyear) - 1992
- let n = whenFreedom j t
- let ageFree = roundTo 1 $ (n / 12) + age :: Decimal
- row "savings rate" (Percent_ $ savingsRate j t) Nothing
- row " target fund" (targetFund j t) Nothing
- row " when free" (Months_ n) $ Just $ "I'll be " <> pr ageFree <> " years old"
-
- sec "runway"
- let (nut, cash, months) = runway j t
- row " nut" nut Nothing
- row " cash" cash Nothing
- row "months" (Target 36 months) $ Just "want: 3 years"
-
- sec "ramen"
- let (nut, cash, months) = ramen j t
- row " nut" nut Nothing
- row " cash" cash Nothing
- row "months" (Target 3 months) $ Just "want: 3 months"
+ let nextLevel n = Just $ display $ roundTo' floor 1 $ level netWorth + n
+ row " next" (levelup 0.1) $ nextLevel 0.1
+ row " nnext" (levelup 0.2) $ nextLevel 0.2
+ row " nnnext" (levelup 0.3) $ nextLevel 0.3
-- | <type> <expected> <actual>
data Metric
@@ -111,26 +110,30 @@ instance Display Chunk where
-- yellow = within 5% of achieving
-- red = work to do
instance Display Metric where
- display (Target expected actual) = color $ display actual
+ display = \case
+ Target expected actual -> color actual (>=) expected $ display actual
+ Limit expected actual -> color actual (<=) expected $ display actual
where
- color
- | actual >= expected = fore green
- | actual >= (expected * 0.95) = fore yellow
- | otherwise = fore red
- display (Limit expected actual) = color $ display actual
- where
- color
- | actual <= expected = fore green
- | actual <= (expected * 0.95) = fore yellow
+ color :: Quantity -> (Quantity -> Quantity -> Bool) -> Quantity -> Chunk -> Chunk
+ color actual cmp expected
+ | actual `cmp` expected = fore green
+ | actual `cmp` (expected * 0.95) = fore yellow
| otherwise = fore red
-- | Tag numbers for different kinds of displays
-data Number
- = Months_ Quantity
- | Percent_ Quantity
- | Diff Quantity
-
-instance Display Number where
+data Tagged a
+ = Months_ a
+ | Percent_ a
+ | Diff a
+ | USD a
+ | SAT a
+ | BTC a
+ | Months a
+
+instance (Num a, Ord a, Display a) => Display (Tagged a) where
+ display (USD q) = display q <> chunk " USD"
+ display (SAT q) = display q <> chunk " sat"
+ display (BTC q) = display q <> chunk " BTC"
display (Months_ q) = display q <> " months"
display (Percent_ p) = display p <> "%"
display (Diff n)
@@ -161,7 +164,7 @@ pr = chunk . pack . show
row :: (Display a) => Chunk -> a -> Maybe Chunk -> IO ()
row label value note =
- putChunkLn $ gap <> label <> ":" <> gap <> display value <> rest
+ putChunkLn $ gap <> label <> ":" <> gap <> display value <> " " <> rest
where
rest = case note of
Nothing -> ""
@@ -179,40 +182,59 @@ level = realFracToDecimal 2 . logBase 10 . realToFrac
unlevel :: Decimal -> Decimal
unlevel = realFracToDecimal 2 . (10 **) . realToFrac
+levelAtAge cur age = fromJust $ Map.lookup (roundTo 2 age) $ levelSchedule cur
+
+unlevelAtAge cur = unlevel . levelAtAge cur
+
-- Shows the steps between levels
steps start = zip (map realToFrac lvls) (zipWith (-) (ls ++ [0]) (0 : ls))
where
lvls = [start, start + 0.01 .. 8.0]
ls = map (realToFrac . unlevel) lvls
-levelSchedule = Map.fromList $ zip ages lvls
+-- | Map of age to level. Age is year + month as a decimal.
+levelSchedule :: (Quantity -> Tagged Decimal) -> Map.Map Decimal Decimal
+levelSchedule cur = Map.fromList $ zip ages lvls
where
- start = 5.0
- goal = 9.0
+ ultimateGoal = cur 1_000_000_000 -- thats a billion usd
+ (start, goal) = case ultimateGoal of
+ USD n -> (5.0, level n)
+ -- normalize btc/sat levels to comparative usd levels, given exchange rate
+ -- assumptions below
+ BTC n -> (level $ usdToBtc $ unlevel 5, level $ usdToBtc n)
+ SAT n -> (level $ usdToSat $ unlevel 5, level $ usdToSat n)
step = (goal - start) / 600
ages = map (roundTo 2) [20, 20 + 1 / 12 .. 70]
lvls = map (roundTo 2) [start, start + step .. goal]
--- | A trivial decision is one that is between 0.01% of the total.
+-- This is a bit speculative, but I'm assuming the value of a bitcoin is
+-- 100,000 USD. Eventually I should change this to actually use the USD/BTC
+-- exchange rate, but it changes so much that it would be hard to have a
+-- concrete plan when dealing in BTC/sats. So I figure 100k is a good price
+-- target for the next year or so.
+usdToBtc usd = usd / 100_000
+
+btcToUsd btc = btc * 100_000
+
+btcToSat btc = btc * 100_000_000
+
+satToBtc sat = sat / 100_000_000
+
+usdToSat usd = btcToSat $ usdToBtc usd
+
+-- | A trivial decision is one that is 0.01% of the total.
--
-- From <https://ofdollarsanddata.com/climbing-the-wealth-ladder/>
trivial :: Quantity
trivial = 0.0001
-inUsdNow :: Maybe ValuationType
-inUsdNow = Just $ AtNow $ Just "USD"
-
-inSatNow :: Maybe ValuationType
-inSatNow = Just . AtNow $ Just "SAT"
-
getTotal :: Journal -> Day -> ReportOpts -> String -> Quantity
-getTotal j t o q = last . map aquantity $ getTotalAmounts j t o q
+getTotal j t o q = sum . map aquantity $ getTotalAmounts j t o q
getTotalAmounts :: Journal -> Day -> ReportOpts -> String -> [Amount]
getTotalAmounts j d opts q = totals
where
- opts' = opts {today_ = Just d}
- (_, (Mixed totals)) = balanceReport opts' query j
+ (_, (Mixed totals)) = balanceReport (ReportSpec opts d query []) j
Right (query, _) = parseQuery d $ pack q
-- | These are the accounts that I consider a part of my savings and not my
@@ -222,39 +244,24 @@ savingsAccounts =
["as:me:save", "as:me:vest"]
-- | Savings rate is a FIRE staple: (Income - Expenses) / Income * 100
-savingsRate :: Journal -> Day -> Quantity
-savingsRate j d = roundTo 2 $ 100 * (income - expenses) / income
+savingsRate :: Journal -> Day -> ReportOpts -> Quantity
+savingsRate j d opts = roundTo 2 $ 100 * (income - expenses) / income
where
- -- I used to do just savings/income, but this is wrong because it also
- -- includes capital gains, which are not technically part of the savings rate.
- --roundTo 2 $ savings / income
-
- opts = defreportopts {value_ = inUsdNow}
savings = getTotal j d opts query
query = List.intercalate " " $ savingsAccounts
- -- gotta flip the sign because income is negative
income = - getTotal j d opts "^in"
- expenses = getTotal j d opts "^ex"
+ expenses = getTotal j d opts "^ex:me:want ^ex:me:need"
-- | 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
+targetFund :: Journal -> Day -> ReportOpts -> Quantity
+targetFund j d opts = 25 * yearlyExpenses
where
yearlyExpenses = expenses / yearsSinceBeginning d
expenses = sum $ map aquantity $ total
- Right (query, _) = parseQuery d $ pack "^ex"
- (_, (Mixed total)) = balanceReport opts query j
- opts =
- defreportopts
- { value_ = inUsdNow,
- today_ = Just d
- }
+ Right (query, _) = parseQuery d $ pack "^ex:me:want ^ex:me:need"
+ (_, (Mixed total)) = balanceReport (ReportSpec opts d query []) j
-- | I have expense data going back to 2019.10. Use this for calculating
-- averages per month.
@@ -274,71 +281,32 @@ yearsSinceBeginning d = monthsSinceBeginning d / 12
-- | 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 j d
+whenFreedom :: Journal -> Day -> ReportOpts -> Quantity
+whenFreedom j d opts = roundTo 1 $ targetFund j d opts / monthlySavings j d opts
-monthlySavings :: Journal -> Day -> Quantity
-monthlySavings j d =
+monthlySavings :: Journal -> Day -> ReportOpts -> Quantity
+monthlySavings j d opts =
savingsAccounts
- & map (getTotal j d (defreportopts {value_ = inUsdNow}))
+ & map (getTotal j d opts)
& sum
& \n -> (n / monthsSinceBeginning d)
-- | How many months I could sustain myself with my cash and savings, given my
-- current expenses.
-runway :: Journal -> Day -> (Quantity, Quantity, Quantity)
-runway j d = (nut d total, cash, cash / nut d total)
+runway :: Journal -> Day -> ReportOpts -> (Quantity, Quantity, Quantity)
+runway j d opts = (nut d total, cash, cash / nut d total)
where
- opts = defreportopts {value_ = inUsdNow}
- total = getTotal j d opts "^ex:me"
+ total = getTotal j d opts "^ex:me:need ^ex:me:want"
cash = getTotal j d opts "^as:me:save ^as:me:cash ^li:me:cred"
-- | Ramen profitability. Like 'runway', except let's say I live on /only/ the
-- necessities, and don't spend my bitcoin. So cash flow in my checking account
-- is primary.
-ramen :: Journal -> Day -> (Quantity, Quantity, Quantity)
-ramen j d = (nut d total, cash, cash / nut d total)
+ramen :: Journal -> Day -> ReportOpts -> (Quantity, Quantity, Quantity)
+ramen j d opts = (nut d total, cash, cash / nut d total)
where
- opts = defreportopts {value_ = inUsdNow}
total = getTotal j d opts "^ex:me:need"
cash = getTotal j d opts "^as:me:cash ^li:me:cred"
nut :: Day -> Quantity -> Quantity
nut d total = total / monthsSinceBeginning d
-
--- | Escape velocity:
---
--- In physics it is basically the movement of an object away from the earth,
--- calculated as:
---
--- v = sqrt(2 * G * M / r)
---
--- where:
---
--- - G :: gravitational constant (inflation rate)
--- - M :: mass to be escaped from (liabilities)
--- - r :: distance from center of M (current net worth)
---
--- So, to translate that into my finances would be something like:
---
--- v = sqrt(2 * .03 * li / net_worth)
--- v = sqrt(2 * .03 * 20,000 / 100,000)
---
--- v = 0.1095
---
--- I don't know what this means... maybe my money must be growing at an 11% rate
--- in order to cover the debt? I need to think about this equation some more.
---
--- Basically, escape velocity will be when my assets are growing faster than my
--- debts. In order to know this, I need:
---
--- 1. the accrual of every liability
--- 2. the return on every investment i make
--- 3. accrual rate must be less than return rate
--- 4. my income must always be more than my expenses
---
--- Once I have all four conditions satisfied, then my finances will be in
--- correct order. The challenge then is to have a system that continually
--- satisfies the 4 conditions.
-escapeVelocity :: Journal -> Quantity
-escapeVelocity = undefined