2024-01-22 18:58:37 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE EmptyDataDecls #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE GADTs #-}
|
|
|
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
|
|
|
{-# LANGUAGE DerivingStrategies #-}
|
2024-03-01 20:57:13 +00:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
2024-01-22 18:58:37 +00:00
|
|
|
{-# LANGUAGE StandaloneDeriving #-}
|
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2024-01-23 15:55:24 +00:00
|
|
|
{-# LANGUAGE TypeOperators #-}
|
2024-01-22 18:58:37 +00:00
|
|
|
|
2024-01-17 18:15:21 +00:00
|
|
|
module Zenith.DB where
|
2024-01-22 18:58:37 +00:00
|
|
|
|
2024-02-19 20:05:32 +00:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
2024-01-22 18:58:37 +00:00
|
|
|
import qualified Data.ByteString as BS
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import Database.Persist
|
|
|
|
import Database.Persist.Sqlite
|
|
|
|
import Database.Persist.TH
|
2024-03-05 18:34:30 +00:00
|
|
|
import ZcashHaskell.Types (Phrase, UnifiedAddress(..), ZcashNet)
|
2024-02-09 22:18:48 +00:00
|
|
|
|
|
|
|
derivePersistField "ZcashNet"
|
2024-01-22 18:58:37 +00:00
|
|
|
|
2024-03-05 18:34:30 +00:00
|
|
|
derivePersistField "UnifiedAddress"
|
|
|
|
|
2024-01-22 18:58:37 +00:00
|
|
|
share
|
|
|
|
[mkPersist sqlSettings, mkMigrate "migrateAll"]
|
|
|
|
[persistLowerCase|
|
|
|
|
ZcashWallet
|
|
|
|
name T.Text
|
2024-02-09 22:18:48 +00:00
|
|
|
network ZcashNet
|
2024-03-01 20:57:13 +00:00
|
|
|
seedPhrase Phrase
|
|
|
|
birthdayHeight Int
|
2024-02-28 22:37:43 +00:00
|
|
|
UniqueWallet name network
|
2024-03-01 20:57:13 +00:00
|
|
|
deriving Show Eq
|
2024-02-27 14:33:12 +00:00
|
|
|
ZcashAccount
|
|
|
|
index Int
|
2024-03-01 20:57:13 +00:00
|
|
|
walletId ZcashWalletId
|
|
|
|
name T.Text
|
2024-02-27 14:33:12 +00:00
|
|
|
orchSpendKey BS.ByteString
|
|
|
|
sapSpendKey BS.ByteString
|
|
|
|
tPrivateKey BS.ByteString
|
2024-03-01 20:57:13 +00:00
|
|
|
UniqueAccount index walletId
|
2024-03-05 18:34:30 +00:00
|
|
|
UniqueAccName walletId name
|
2024-03-01 20:57:13 +00:00
|
|
|
deriving Show Eq
|
2024-02-27 14:33:12 +00:00
|
|
|
WalletAddress
|
|
|
|
index Int
|
2024-03-05 18:34:30 +00:00
|
|
|
accId ZcashAccountId
|
|
|
|
name T.Text
|
|
|
|
uAddress UnifiedAddress
|
|
|
|
UniqueAddress index accId
|
|
|
|
UniqueAddName accId name
|
2024-03-01 20:57:13 +00:00
|
|
|
deriving Show Eq
|
2024-01-22 18:58:37 +00:00
|
|
|
|]
|
2024-02-19 20:05:32 +00:00
|
|
|
|
2024-03-05 18:34:30 +00:00
|
|
|
-- * Database functions
|
|
|
|
-- | Initializes the database
|
|
|
|
initDb ::
|
|
|
|
T.Text -- ^ The database path to check
|
|
|
|
-> IO ()
|
|
|
|
initDb dbName = do
|
|
|
|
runSqlite dbName $ do runMigration migrateAll
|
|
|
|
|
|
|
|
-- | Get existing wallets from database
|
2024-02-27 14:33:12 +00:00
|
|
|
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
|
2024-03-05 18:34:30 +00:00
|
|
|
getWallets dbFp n = runSqlite dbFp $ selectList [ZcashWalletNetwork ==. n] []
|
|
|
|
|
|
|
|
-- | Save a new wallet to the database
|
|
|
|
saveWallet ::
|
|
|
|
T.Text -- ^ The database path to use
|
|
|
|
-> ZcashWallet -- ^ The wallet to add to the database
|
|
|
|
-> IO (Maybe (Entity ZcashWallet))
|
|
|
|
saveWallet dbFp w = runSqlite dbFp $ insertUniqueEntity w
|
|
|
|
|
|
|
|
-- | Returns a list of accounts associated with the given wallet
|
|
|
|
getAccounts ::
|
|
|
|
T.Text -- ^ The database path
|
|
|
|
-> ZcashWalletId -- ^ The wallet ID to check
|
|
|
|
-> IO [Entity ZcashAccount]
|
|
|
|
getAccounts dbFp w = runSqlite dbFp $ selectList [ZcashAccountWalletId ==. w] []
|
|
|
|
|
|
|
|
-- | Returns the largest account index for the given wallet
|
|
|
|
getMaxAccount ::
|
|
|
|
T.Text -- ^ The database path
|
|
|
|
-> ZcashWalletId -- ^ The wallet ID to check
|
|
|
|
-> IO Int
|
|
|
|
getMaxAccount dbFp w = do
|
|
|
|
a <-
|
|
|
|
runSqlite dbFp $
|
|
|
|
selectFirst [ZcashAccountWalletId ==. w] [Desc ZcashAccountIndex]
|
|
|
|
case a of
|
|
|
|
Nothing -> return $ -1
|
|
|
|
Just x -> return $ zcashAccountIndex $ entityVal x
|
|
|
|
|
|
|
|
-- | Save a new account to the database
|
|
|
|
saveAccount ::
|
|
|
|
T.Text -- ^ The database path
|
|
|
|
-> ZcashAccount -- ^ The account to add to the database
|
|
|
|
-> IO (Maybe (Entity ZcashAccount))
|
|
|
|
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a
|
|
|
|
|
|
|
|
-- | Returns a list of addresses associated with the given account
|
|
|
|
getAddresses ::
|
|
|
|
T.Text -- ^ The database path
|
|
|
|
-> ZcashAccountId -- ^ The account ID to check
|
|
|
|
-> IO [Entity WalletAddress]
|
|
|
|
getAddresses dbFp a = runSqlite dbFp $ selectList [WalletAddressAccId ==. a] []
|
|
|
|
|
|
|
|
-- | Returns the largest address index for the given account
|
|
|
|
getMaxAddress ::
|
|
|
|
T.Text -- ^ The database path
|
|
|
|
-> ZcashAccountId -- ^ The wallet ID to check
|
|
|
|
-> IO Int
|
|
|
|
getMaxAddress dbFp w = do
|
|
|
|
a <-
|
|
|
|
runSqlite dbFp $
|
|
|
|
selectFirst [WalletAddressAccId ==. w] [Desc WalletAddressIndex]
|
|
|
|
case a of
|
|
|
|
Nothing -> return $ -1
|
|
|
|
Just x -> return $ walletAddressIndex $ entityVal x
|
|
|
|
|
|
|
|
-- | Save a new address to the database
|
|
|
|
saveAddress ::
|
|
|
|
T.Text -- ^ the database path
|
|
|
|
-> WalletAddress -- ^ The wallet to add to the database
|
|
|
|
-> IO (Maybe (Entity WalletAddress))
|
|
|
|
saveAddress dbFp w = runSqlite dbFp $ insertUniqueEntity w
|