ENH use cli flag for config path

This commit is contained in:
Nathan Dwarshuis 2022-12-11 18:34:05 -05:00
parent 7dc9b7b07b
commit 5d6038292e
7 changed files with 85 additions and 54 deletions

View File

@ -10,84 +10,101 @@ import Internal.Insert
import Internal.Types import Internal.Types
import Internal.Utils import Internal.Utils
-- import Import.Config
import Control.Monad.Trans.Reader import Control.Monad.Trans.Reader
import Options.Applicative import Options.Applicative
import System.FilePath
main :: IO () main :: IO ()
main = parse =<< execParser o main = parse =<< execParser o
where where
o = info (options <**> helper) o = info (options <**> helper)
( fullDesc ( fullDesc
<> progDesc "Pwn your budget" <> progDesc "Pwn your budget"
<> header "pwncase - your budget, your life" <> header "pwncash - your budget, your life"
) )
data Options = Reset data Options = Options FilePath Mode
data Mode = Reset
| DumpCurrencies | DumpCurrencies
| DumpAccounts | DumpAccounts
| DumpAccountKeys | DumpAccountKeys
| Sync | Sync
options :: Parser Options configFile :: Parser FilePath
options = reset configFile = strOption
<|> dumpCurrencies ( long "config"
<|> dumpAccounts <> short 'c'
<|> dumpAccountKeys <> metavar "CONFIG"
<|> sync <> value "main.dhall"
<> help "config file to use"
)
reset :: Parser Options options :: Parser Options
options = getConf reset
<|> getConf dumpCurrencies
<|> getConf dumpAccounts
<|> getConf dumpAccountKeys
<|> getConf sync
where
getConf m = Options <$> configFile <*> m
reset :: Parser Mode
reset = flag' Reset reset = flag' Reset
( long "reset" ( long "reset"
<> short 'r' <> short 'R'
<> help "Reset the database" <> help "Reset the database"
) )
dumpCurrencies :: Parser Options dumpCurrencies :: Parser Mode
dumpCurrencies = flag' DumpCurrencies dumpCurrencies = flag' DumpCurrencies
( long "currencies" ( long "currencies"
<> short 'c' <> short 'C'
<> help "Dump all currencies in the configuration" <> help "Dump all currencies in the configuration"
) )
dumpAccounts :: Parser Options dumpAccounts :: Parser Mode
dumpAccounts = flag' DumpAccounts dumpAccounts = flag' DumpAccounts
( long "accounts" ( long "accounts"
<> short 'a' <> short 'A'
<> help "Dump all accounts in the configuration" <> help "Dump all accounts in the configuration"
) )
-- TODO 'alias' is a better name for these -- TODO 'alias' is a better name for these
dumpAccountKeys :: Parser Options dumpAccountKeys :: Parser Mode
dumpAccountKeys = flag' DumpAccountKeys dumpAccountKeys = flag' DumpAccountKeys
( long "account_keys" ( long "account_keys"
<> short 'k' <> short 'K'
<> help "Dump all account keys/aliases" <> help "Dump all account keys/aliases"
) )
sync :: Parser Options sync :: Parser Mode
sync = pure Sync sync = flag' Sync
( long "sync"
<> short 'S'
<> help "Sync config to database"
)
parse :: Options -> IO () parse :: Options -> IO ()
parse Reset = migrate_ nukeTables parse (Options _ Reset) = migrate_ nukeTables
parse DumpAccounts = runDumpAccounts parse (Options c DumpAccounts) = runDumpAccounts c
parse DumpAccountKeys = runDumpAccountKeys parse (Options c DumpAccountKeys) = runDumpAccountKeys c
parse DumpCurrencies = runDumpCurrencies parse (Options c DumpCurrencies) = runDumpCurrencies c
parse Sync = runSync parse (Options c Sync) = runSync c
runDumpCurrencies :: IO () runDumpCurrencies :: FilePath -> IO ()
runDumpCurrencies = do runDumpCurrencies c = do
cs <- currencies <$> readConfig "config/config.dhall" cs <- currencies <$> readConfig c
putStrLn $ T.unpack $ T.unlines $ fmap fmt cs putStrLn $ T.unpack $ T.unlines $ fmap fmt cs
where where
fmt Currency { curSymbol = s, curFullname = f } = fmt Currency { curSymbol = s, curFullname = f } =
T.concat [s, ": ", f] T.concat [s, ": ", f]
runDumpAccounts :: IO () runDumpAccounts :: FilePath -> IO ()
runDumpAccounts = do runDumpAccounts c = do
ar <- accounts <$> readConfig "config/config.dhall" ar <- accounts <$> readConfig c
mapM_ (\(h, f) -> printTree h $ f ar) ps mapM_ (\(h, f) -> printTree h $ f ar) ps
where where
ps = [ ("Assets", arAssets) ps = [ ("Assets", arAssets)
@ -107,9 +124,9 @@ runDumpAccounts = do
let ind = T.replicate (i * 2) " " let ind = T.replicate (i * 2) " "
putStrLn $ T.unpack $ T.concat [ind, n, ": ", d] putStrLn $ T.unpack $ T.concat [ind, n, ": ", d]
runDumpAccountKeys :: IO () runDumpAccountKeys :: FilePath -> IO ()
runDumpAccountKeys = do runDumpAccountKeys c = do
ar <- accounts <$> readConfig "config/config.dhall" ar <- accounts <$> readConfig c
let ks = paths2IDs let ks = paths2IDs
$ fmap (double . fst) $ fmap (double . fst)
$ concatMap (t3 . uncurry tree2Records) $ concatMap (t3 . uncurry tree2Records)
@ -121,12 +138,12 @@ runDumpAccountKeys = do
t3 (_, _, x) = x t3 (_, _, x) = x
double x = (x, x) double x = (x, x)
runSync :: IO () runSync :: FilePath -> IO ()
runSync = do runSync c = do
config <- readConfig "config/config.dhall" config <- readConfig c
migrate_ $ do migrate_ $ do
s <- getDBState config s <- getDBState config
flip runReaderT s $ do flip runReaderT (s $ takeDirectory c) $ do
insertBudget $ budget config insertBudget $ budget config
insertStatements config insertStatements config
showBalances showBalances

View File

@ -46,6 +46,7 @@ library
, data-fix , data-fix
, dhall >=1.41.2 , dhall >=1.41.2
, esqueleto , esqueleto
, filepath
, ghc >=9.0.2 , ghc >=9.0.2
, hashable , hashable
, lens >=5.0.1 , lens >=5.0.1
@ -81,6 +82,7 @@ executable pwncash
, data-fix , data-fix
, dhall >=1.41.2 , dhall >=1.41.2
, esqueleto , esqueleto
, filepath
, ghc >=9.0.2 , ghc >=9.0.2
, hashable , hashable
, lens >=5.0.1 , lens >=5.0.1

View File

@ -72,6 +72,7 @@ data DBState = DBState
, kmBudgetInterval :: !MaybeBounds , kmBudgetInterval :: !MaybeBounds
, kmStatementInterval :: !MaybeBounds , kmStatementInterval :: !MaybeBounds
, kmNewCommits :: ![Int] , kmNewCommits :: ![Int]
, kmConfigDir :: FilePath
} }
type MappingT m a = ReaderT DBState (SqlPersistT m) a type MappingT m a = ReaderT DBState (SqlPersistT m) a

View File

@ -280,15 +280,18 @@ indexAcntRoot r =
where where
(ars, aprs, ms) = unzip3 $ uncurry tree2Records <$> flattenAcntRoot r (ars, aprs, ms) = unzip3 $ uncurry tree2Records <$> flattenAcntRoot r
getDBState :: MonadIO m => Config -> SqlPersistT m DBState getDBState :: MonadIO m => Config -> SqlPersistT m (FilePath -> DBState)
getDBState c = do getDBState c = do
am <- updateAccounts $ accounts c am <- updateAccounts $ accounts c
cm <- updateCurrencies $ currencies c cm <- updateCurrencies $ currencies c
hs <- updateHashes c hs <- updateHashes c
return $ DBState -- TODO not sure how I feel about this, probably will change this struct alot
-- in the future so whatever...for now
return $ \f -> DBState
{ kmCurrency = cm { kmCurrency = cm
, kmAccount = am , kmAccount = am
, kmBudgetInterval = intervalMaybeBounds $ budgetInterval $ global c , kmBudgetInterval = intervalMaybeBounds $ budgetInterval $ global c
, kmStatementInterval = intervalMaybeBounds $ statementInterval $ global c , kmStatementInterval = intervalMaybeBounds $ statementInterval $ global c
, kmNewCommits = hs , kmNewCommits = hs
, kmConfigDir = f
} }

View File

@ -252,7 +252,7 @@ insertManual m@Manual { manualDate = dp
insertImport :: MonadIO m => Import -> MappingT m () insertImport :: MonadIO m => Import -> MappingT m ()
insertImport i = whenHash CTImport i $ \c -> do insertImport i = whenHash CTImport i $ \c -> do
bounds <- asks kmStatementInterval bounds <- asks kmStatementInterval
bs <- liftIO $ readImport i bs <- readImport i
-- TODO this isn't efficient, the whole file will be read and maybe no -- TODO this isn't efficient, the whole file will be read and maybe no
-- transactions will be desired -- transactions will be desired
rs <- mapM resolveTx $ filter (inMaybeBounds bounds . txDate) bs rs <- mapM resolveTx $ filter (inMaybeBounds bounds . txDate) bs

View File

@ -7,45 +7,52 @@ module Internal.Statement
( readImport ( readImport
) where ) where
import Control.Monad.IO.Class
import Control.Monad.Trans.Reader
import Data.Bifunctor import Data.Bifunctor
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Data.Csv import Data.Csv
import Data.Either import Data.Either
import qualified Data.List as L import qualified Data.List as L
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe import Data.Maybe
import Data.Ord import Data.Ord
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as TE import qualified Data.Text.Encoding as TE
import Data.Time import Data.Time
import qualified Data.Vector as V import qualified Data.Vector as V
import Internal.Database.Model
import Internal.Types import Internal.Types
import Internal.Utils import Internal.Utils
import Numeric.Natural import Numeric.Natural
import System.FilePath
-- TODO this probably won't scale well (pipes?) -- TODO this probably won't scale well (pipes?)
readImport :: Import -> IO [BalTx] readImport :: MonadIO m => Import -> MappingT m [BalTx]
readImport Import { impPaths = ps readImport Import { impPaths = ps
, impMatches = ms , impMatches = ms
, impTxOpts = ns , impTxOpts = ns
, impDelim = d , impDelim = d
, impSkipLines = n , impSkipLines = n
-- , impTx = f
} = do } = do
rs <- L.sort . concat <$> mapM (readImport_ n d ns) ps rs <- L.sort . concat <$> mapM (readImport_ n d ns) ps
let (ts, es, notfound) = matchRecords ms rs let (ts, es, notfound) = matchRecords ms rs
mapM_ putStrLn $ reverse es liftIO $ mapM_ putStrLn $ reverse es
mapM_ print notfound liftIO $ mapM_ print notfound
return ts return ts
readImport_ :: Natural -> Word -> TxOpts -> FilePath -> IO [TxRecord] readImport_ :: MonadIO m => Natural -> Word -> TxOpts -> FilePath
-> MappingT m [TxRecord]
readImport_ n delim tns p = do readImport_ n delim tns p = do
bs <- BL.readFile p dir <- asks kmConfigDir
bs <- liftIO $ BL.readFile $ dir </> p
case decodeByNameWithP (parseTxRecord tns) opts $ skip bs of case decodeByNameWithP (parseTxRecord tns) opts $ skip bs of
Left m -> putStrLn m >> return [] Left m -> liftIO $ putStrLn m >> return []
Right (_, v) -> return $ catMaybes $ V.toList v Right (_, v) -> return $ catMaybes $ V.toList v
where where
opts = defaultDecodeOptions { decDelimiter = fromIntegral delim } opts = defaultDecodeOptions { decDelimiter = fromIntegral delim }

View File

@ -45,6 +45,7 @@ dependencies:
- optparse-applicative - optparse-applicative
- recursion-schemes - recursion-schemes
- data-fix - data-fix
- filepath
library: library:
source-dirs: lib/ source-dirs: lib/