pwncash/lib/Internal/Database/Ops.hs

326 lines
10 KiB
Haskell
Raw Normal View History

2022-12-11 17:51:11 -05:00
module Internal.Database.Ops
( migrate_
, nukeTables
2023-01-28 22:58:05 -05:00
-- , showBalances
2022-12-11 17:51:11 -05:00
, updateHashes
, getDBState
, tree2Records
, flattenAcntRoot
, paths2IDs
)
where
import Conduit
import Control.Monad.Logger
import Data.Hashable
import Database.Esqueleto.Experimental
import Database.Persist.Sql hiding (delete, (==.), (||.))
import Database.Persist.Sqlite hiding (delete, (==.), (||.))
import Database.Sqlite hiding (Config)
2023-01-28 22:58:05 -05:00
import GHC.Err
import Internal.Database.Model
import Internal.Types
import Internal.Utils
import RIO hiding (LogFunc, isNothing, on, (^.))
import RIO.List ((\\))
import qualified RIO.List as L
import qualified RIO.Map as M
2023-01-27 20:54:25 -05:00
import qualified RIO.NonEmpty as N
import qualified RIO.Text as T
2022-12-11 17:51:11 -05:00
2023-01-05 22:23:22 -05:00
migrate_
:: MonadUnliftIO m
=> SqlConfig
-> SqlPersistT (ResourceT (NoLoggingT m)) ()
-> m ()
migrate_ c more =
runNoLoggingT $
runResourceT $
withSqlConn
(openConnection c)
( \backend ->
flip runSqlConn backend $ do
2023-02-12 16:23:32 -05:00
_ <- askLoggerIO
runMigration migrateAll
more
)
2022-12-11 17:51:11 -05:00
2023-01-05 22:23:22 -05:00
openConnection :: MonadUnliftIO m => SqlConfig -> LogFunc -> m SqlBackend
2022-12-11 18:53:54 -05:00
openConnection c logfn = case c of
2023-01-05 22:23:22 -05:00
Sqlite p -> liftIO $ do
2022-12-11 18:53:54 -05:00
conn <- open p
wrapConnection conn logfn
Postgres -> error "postgres not implemented"
2022-12-11 17:51:11 -05:00
2023-01-05 22:23:22 -05:00
nukeTables :: MonadUnliftIO m => SqlPersistT m ()
2022-12-11 17:51:11 -05:00
nukeTables = do
deleteWhere ([] :: [Filter CommitR])
deleteWhere ([] :: [Filter CurrencyR])
deleteWhere ([] :: [Filter AccountR])
deleteWhere ([] :: [Filter TransactionR])
2023-01-28 22:58:05 -05:00
-- showBalances :: MonadUnliftIO m => SqlPersistT m ()
-- showBalances = do
-- xs <- select $ do
-- (accounts :& splits :& txs) <-
-- from
-- $ table @AccountR
-- `innerJoin` table @SplitR
-- `on` (\(a :& s) -> a ^. AccountRId ==. s ^. SplitRAccount)
-- `innerJoin` table @TransactionR
-- `on` (\(_ :& s :& t) -> s ^. SplitRTransaction ==. t ^. TransactionRId)
-- where_ $
-- isNothing (txs ^. TransactionRBucket)
-- &&. ( (accounts ^. AccountRFullpath `like` val "asset" ++. (%))
-- ||. (accounts ^. AccountRFullpath `like` val "liability" ++. (%))
-- )
-- groupBy (accounts ^. AccountRFullpath, accounts ^. AccountRName)
-- return
-- ( accounts ^. AccountRFullpath
-- , accounts ^. AccountRName
-- , sum_ $ splits ^. SplitRValue
-- )
-- -- TODO super stetchy table printing thingy
-- liftIO $ do
-- putStrLn $ T.unpack $ fmt "Account" "Balance"
-- putStrLn $ T.unpack $ fmt (T.replicate 60 "-") (T.replicate 15 "-")
-- mapM_ (putStrLn . T.unpack . fmtBalance) xs
-- where
-- fmtBalance (path, name, bal) = fmt (toFullPath path name) (toBal bal)
-- fmt a b = T.unwords ["| ", pad 60 a, " | ", pad 15 b, " |"]
-- pad n xs = T.append xs $ T.replicate (n - T.length xs) " "
-- toFullPath path name = T.unwords [unValue @T.Text path, "/", unValue @T.Text name]
-- toBal = maybe "???" (fmtRational 2) . unValue
2022-12-11 17:51:11 -05:00
hashConfig :: Config -> [Int]
hashConfig
Config_
2023-02-05 18:45:56 -05:00
{ budget = bs
, statements = ss
} =
2023-02-05 18:45:56 -05:00
concatMap budgetHashes bs ++ (hash <$> ms) ++ (hash <$> ps)
where
(ms, ps) = partitionEithers $ fmap go ss
go (StmtManual x) = Left x
go (StmtImport x) = Right x
2023-02-05 18:45:56 -05:00
budgetHashes Budget {transfers = xs, income = is} =
(hash <$> xs) ++ (hash <$> is)
2022-12-11 17:51:11 -05:00
setDiff :: Eq a => [a] -> [a] -> ([a], [a])
-- setDiff = setDiff' (==)
setDiff as bs = (as \\ bs, bs \\ as)
-- setDiff' :: Eq a => (a -> b -> Bool) -> [a] -> [b] -> ([a], [b])
-- setDiff' f = go []
-- where
-- go inA [] bs = (inA, bs)
-- go inA as [] = (as ++ inA, [])
-- go inA (a:as) bs = case inB a bs of
-- Just bs' -> go inA as bs'
-- Nothing -> go (a:inA) as bs
-- inB _ [] = Nothing
-- inB a (b:bs)
-- | f a b = Just bs
-- | otherwise = inB a bs
2023-01-05 22:23:22 -05:00
getDBHashes :: MonadUnliftIO m => SqlPersistT m [Int]
2022-12-11 17:51:11 -05:00
getDBHashes = fmap (commitRHash . entityVal) <$> dumpTbl
2023-01-05 22:23:22 -05:00
nukeDBHash :: MonadUnliftIO m => Int -> SqlPersistT m ()
2022-12-11 17:51:11 -05:00
nukeDBHash h = delete $ do
c <- from table
where_ (c ^. CommitRHash ==. val h)
2022-12-11 17:51:11 -05:00
2023-01-05 22:23:22 -05:00
nukeDBHashes :: MonadUnliftIO m => [Int] -> SqlPersistT m ()
2022-12-11 17:51:11 -05:00
nukeDBHashes = mapM_ nukeDBHash
2023-01-05 22:23:22 -05:00
getConfigHashes :: MonadUnliftIO m => Config -> SqlPersistT m ([Int], [Int])
2022-12-11 17:51:11 -05:00
getConfigHashes c = do
let ch = hashConfig c
dh <- getDBHashes
return $ setDiff dh ch
2023-01-05 22:23:22 -05:00
updateHashes :: MonadUnliftIO m => Config -> SqlPersistT m [Int]
2022-12-11 17:51:11 -05:00
updateHashes c = do
(del, new) <- getConfigHashes c
nukeDBHashes del
return new
2023-01-05 22:23:22 -05:00
dumpTbl :: (PersistEntity r, MonadUnliftIO m) => SqlPersistT m [Entity r]
2022-12-11 17:51:11 -05:00
dumpTbl = select $ from table
2023-01-05 22:23:22 -05:00
deleteAccount :: MonadUnliftIO m => Entity AccountR -> SqlPersistT m ()
2022-12-11 17:51:11 -05:00
deleteAccount e = delete $ do
c <- from $ table @AccountR
where_ (c ^. AccountRId ==. val k)
2022-12-11 17:51:11 -05:00
where
k = entityKey e
2023-01-05 22:23:22 -05:00
deleteCurrency :: MonadUnliftIO m => Entity CurrencyR -> SqlPersistT m ()
2022-12-11 17:51:11 -05:00
deleteCurrency e = delete $ do
c <- from $ table @CurrencyR
where_ (c ^. CurrencyRId ==. val k)
2022-12-11 17:51:11 -05:00
where
k = entityKey e
2023-01-05 22:23:22 -05:00
updateAccounts :: MonadUnliftIO m => AccountRoot -> SqlPersistT m AccountMap
2022-12-11 17:51:11 -05:00
updateAccounts ar = do
let (acnts, paths, acntMap) = indexAcntRoot ar
acnts' <- dumpTbl
let (toIns, toDel) = setDiff acnts acnts'
deleteWhere ([] :: [Filter AccountPathR])
mapM_ deleteAccount toDel
-- liftIO $ mapM_ print toDel
mapM_ insertFull toIns
mapM_ insert paths
return acntMap
insertFull
2023-01-05 22:23:22 -05:00
:: (MonadUnliftIO m, PersistStoreWrite b, PersistRecordBackend r b)
=> Entity r
-> ReaderT b m ()
2022-12-11 17:51:11 -05:00
insertFull (Entity k v) = insertKey k v
2023-01-05 22:23:22 -05:00
updateCurrencies :: MonadUnliftIO m => [Currency] -> SqlPersistT m CurrencyMap
2022-12-11 17:51:11 -05:00
updateCurrencies cs = do
let curs = fmap currency2Record cs
curs' <- select $ from $ table @CurrencyR
let (toIns, toDel) = setDiff curs curs'
mapM_ deleteCurrency toDel
mapM_ insertFull toIns
return $ currencyMap curs
currency2Record :: Currency -> Entity CurrencyR
2023-02-12 16:23:32 -05:00
currency2Record c@Currency {curSymbol, curFullname} =
Entity (toKey c) $ CurrencyR curSymbol curFullname
2022-12-11 17:51:11 -05:00
currencyMap :: [Entity CurrencyR] -> CurrencyMap
currencyMap = M.fromList . fmap (\e -> (currencyRSymbol $ entityVal e, entityKey e))
toKey :: (ToBackendKey SqlBackend b, Hashable a) => a -> Key b
toKey = toSqlKey . fromIntegral . hash
tree2Entity :: AcntType -> [T.Text] -> T.Text -> T.Text -> Entity AccountR
tree2Entity t parents name des =
Entity (toSqlKey $ fromIntegral h) $
AccountR name (toPath parents) des
2022-12-11 17:51:11 -05:00
where
p = AcntPath t (reverse (name : parents))
2022-12-11 17:51:11 -05:00
h = hash p
toPath = T.intercalate "/" . (atName t :) . reverse
2022-12-11 17:51:11 -05:00
tree2Records
:: AcntType
-> AccountTree
2023-02-12 21:52:41 -05:00
-> ([Entity AccountR], [AccountPathR], [(AcntPath, (AccountRId, AcntSign, AcntType))])
2022-12-11 17:51:11 -05:00
tree2Records t = go []
where
go ps (Placeholder d n cs) =
let e = tree2Entity t (fmap snd ps) n d
2022-12-11 17:51:11 -05:00
k = entityKey e
2023-01-28 22:58:05 -05:00
(as, aps, ms) = L.unzip3 $ fmap (go ((k, n) : ps)) cs
2022-12-11 17:51:11 -05:00
a0 = acnt k n (fmap snd ps) d
paths = expand k $ fmap fst ps
in (a0 : concat as, paths ++ concat aps, concat ms)
go ps (Account d n) =
2022-12-11 17:51:11 -05:00
let e = tree2Entity t (fmap snd ps) n d
k = entityKey e
in ( [acnt k n (fmap snd ps) d]
, expand k $ fmap fst ps
2023-02-12 21:52:41 -05:00
, [(AcntPath t $ reverse $ n : fmap snd ps, (k, sign, t))]
)
toPath = T.intercalate "/" . (atName t :) . reverse
2022-12-11 17:51:11 -05:00
acnt k n ps = Entity k . AccountR n (toPath ps)
expand h0 hs = (\(h, d) -> AccountPathR h h0 d) <$> zip (h0 : hs) [0 ..]
2022-12-11 17:51:11 -05:00
sign = accountSign t
paths2IDs :: [(AcntPath, a)] -> [(AcntID, a)]
paths2IDs =
uncurry zip
. first trimNames
2023-01-28 22:58:05 -05:00
. L.unzip
. L.sortOn fst
. fmap (first pathList)
2022-12-11 17:51:11 -05:00
where
2023-01-27 20:54:25 -05:00
pathList (AcntPath t []) = atName t :| []
pathList (AcntPath t ns) = N.reverse $ atName t :| ns
2022-12-11 17:51:11 -05:00
2023-01-27 20:54:25 -05:00
-- none of these errors should fire assuming that input is sorted and unique
trimNames :: [N.NonEmpty T.Text] -> [AcntID]
trimNames = fmap (T.intercalate "_" . reverse) . trimAll 0
2022-12-11 17:51:11 -05:00
where
trimAll _ [] = []
trimAll i (y : ys) = case L.foldl' (matchPre i) (y, [], []) ys of
(a, [], bs) -> reverse $ trim i a : bs
(a, as, bs) -> reverse bs ++ trimAll (i + 1) (reverse $ a : as)
2022-12-11 17:51:11 -05:00
matchPre i (y, ys, old) new = case (y !? i, new !? i) of
(Nothing, Just _) ->
case ys of
[] -> (new, [], trim i y : old)
_ -> err "unsorted input"
2022-12-11 17:51:11 -05:00
(Just _, Nothing) -> err "unsorted input"
(Nothing, Nothing) -> err "duplicated inputs"
(Just a, Just b)
| a == b -> (new, y : ys, old)
2022-12-11 17:51:11 -05:00
| otherwise ->
let next = case ys of
[] -> [trim i y]
_ -> trimAll (i + 1) (reverse $ y : ys)
in (new, [], reverse next ++ old)
2023-01-27 20:54:25 -05:00
trim i = N.take (i + 1)
2022-12-11 17:51:11 -05:00
err msg = errorWithoutStackTrace $ "Import.Database.Ops.hs: " ++ msg
2023-01-27 20:54:25 -05:00
(!?) :: N.NonEmpty a -> Int -> Maybe a
2022-12-11 17:51:11 -05:00
xs !? n
| n < 0 = Nothing
-- Definition adapted from GHC.List
| otherwise =
foldr
( \x r k -> case k of
0 -> Just x
_ -> r (k - 1)
)
(const Nothing)
xs
n
2022-12-11 17:51:11 -05:00
flattenAcntRoot :: AccountRoot -> [(AcntType, AccountTree)]
2023-02-12 16:23:32 -05:00
flattenAcntRoot AccountRoot_ {arIncome, arExpenses, arLiabilities, arAssets, arEquity} =
2022-12-11 17:51:11 -05:00
((IncomeT,) <$> arIncome)
++ ((ExpenseT,) <$> arExpenses)
++ ((LiabilityT,) <$> arLiabilities)
++ ((AssetT,) <$> arAssets)
++ ((EquityT,) <$> arEquity)
2022-12-11 17:51:11 -05:00
indexAcntRoot :: AccountRoot -> ([Entity AccountR], [AccountPathR], AccountMap)
indexAcntRoot r =
( concat ars
, concat aprs
, M.fromList $ paths2IDs $ concat ms
)
where
2023-01-28 22:58:05 -05:00
(ars, aprs, ms) = L.unzip3 $ uncurry tree2Records <$> flattenAcntRoot r
2022-12-11 17:51:11 -05:00
2023-01-25 23:04:54 -05:00
getDBState
:: MonadUnliftIO m
=> Config
-> SqlPersistT m (EitherErrs (FilePath -> DBState))
2023-01-28 19:32:56 -05:00
getDBState c = do
am <- updateAccounts $ accounts c
cm <- updateCurrencies $ currencies c
hs <- updateHashes c
-- TODO not sure how I feel about this, probably will change this struct alot
-- in the future so whatever...for now
return $ concatEither2 bi si $ \b s f ->
2023-01-28 19:32:56 -05:00
DBState
{ kmCurrency = cm
, kmAccount = am
, kmBudgetInterval = b
, kmStatementInterval = s
2023-01-28 19:32:56 -05:00
, kmNewCommits = hs
, kmConfigDir = f
}
where
bi = resolveBounds $ budgetInterval $ global c
si = resolveBounds $ statementInterval $ global c