module Main where import Brick.AttrMap qualified as A import Brick.Main qualified as M import Brick.Types ( BrickEvent (..), Widget, ) import Brick.Types qualified as T import Brick.Util (bg, on) import Brick.Widgets.Center qualified as C import Brick.Widgets.Core ( padAll, str, ) import Brick.Widgets.Dialog qualified as D import Graphics.Vty qualified as V import Import.Ing.CurrentAccountCsv qualified import Import.Ing.SavingsAccountCsv qualified import System.IO (IOMode (ReadMode), withFile) import Text.Pretty.Simple (pPrint) data AccountType = Asset | Equity | Liability | Expense | Income data TxAction = Inc | Dec txAopp :: TxAction -> TxAction txaOpp Inc = Dec txaOpp Dec = Inc onDebit :: AccountType -> TxAction onDebit Asset = Inc onDebit Equity = Dec onDebit Liability = Dec onDebit Expense = Inc onDebit Income = Dec onCredit :: AccountType -> TxAction onCredit = txaOpp . onDebit data Ledger = [LedgerEntry] data LedgerEntry = TxEntry Tx | BalAssertEntry BalAssert -- A balance assertion is only valid when all transactions before it have been -- cleared and the balance of the account agrees with the amount in the -- assertion. data BalAssert = BalAssert { amount :: Decimal, tags :: Tags } data Tx = Tx { txClearedAt :: Maybe UTCTime, txCommodity :: Commodity, txDebit :: [(Account, Commodity, Rate, Amount)], txCredit :: [(Account, Commodity, Rate, Amount)] -- Description -- Type: } deriving Show data Account = Account { acName :: [T.Text], acCommodity :: Commodity, acBalance :: Amount } data Choice = Red | Blue | Green deriving (Show) data Name = RedButton | BlueButton | GreenButton deriving (Show, Eq, Ord) drawUI :: D.Dialog Choice Name -> [Widget Name] drawUI d = [ui] where ui = D.renderDialog d $ C.hCenter $ padAll 1 $ str "This is the dialog body." appEvent :: BrickEvent Name e -> T.EventM Name (D.Dialog Choice Name) () appEvent (VtyEvent ev) = case ev of V.EvKey V.KEsc [] -> M.halt V.EvKey V.KEnter [] -> M.halt _ -> D.handleDialogEvent ev appEvent _ = return () initialState :: D.Dialog Choice Name initialState = D.dialog (Just $ str "Title") (Just (RedButton, choices)) 50 where choices = [ ("Red", RedButton, Red), ("Blue", BlueButton, Blue), ("Green", GreenButton, Green) ] theMap :: A.AttrMap theMap = A.attrMap V.defAttr [ (D.dialogAttr, V.white `on` V.blue), (D.buttonAttr, V.black `on` V.white), (D.buttonSelectedAttr, bg V.yellow) ] theApp :: M.App (D.Dialog Choice Name) e Name theApp = M.App { M.appDraw = drawUI, M.appChooseCursor = M.showFirstCursor, M.appHandleEvent = appEvent, M.appStartEvent = return (), M.appAttrMap = const theMap } main :: IO () main = do let filename = "/home/rutgerbrf/Code/P/rdcapsis/test3.csv" putStrLn $ "Reading " ++ filename withFile filename ReadMode $ \h -> do entries <- Import.Ing.CurrentAccountCsv.readFile h pPrint entries -- d <- M.defaultMain theApp initialState -- putStrLn $ "You chose: " <> show (D.dialogSelection d)