zenith/src/Zenith/DB.hs

148 lines
4.2 KiB
Haskell
Raw Normal View History

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-17 12:17:52 +00:00
import ZcashHaskell.Types (Scope(..), ZcashNet)
import Zenith.Types
( OrchardSpendingKeyDB(..)
, PhraseDB(..)
, SaplingSpendingKeyDB(..)
, ScopeDB(..)
, TransparentSpendingKeyDB
, UnifiedAddressDB(..)
, ZcashNetDB(..)
)
2024-03-05 18:34:30 +00:00
2024-01-22 18:58:37 +00:00
share
[mkPersist sqlSettings, mkMigrate "migrateAll"]
[persistLowerCase|
ZcashWallet
name T.Text
2024-03-17 12:17:52 +00:00
network ZcashNetDB
seedPhrase PhraseDB
2024-03-01 20:57:13 +00:00
birthdayHeight Int
UniqueWallet name network
2024-03-01 20:57:13 +00:00
deriving Show Eq
ZcashAccount
index Int
2024-03-01 20:57:13 +00:00
walletId ZcashWalletId
name T.Text
2024-03-17 12:17:52 +00:00
orchSpendKey OrchardSpendingKeyDB
sapSpendKey SaplingSpendingKeyDB
tPrivateKey TransparentSpendingKeyDB
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
WalletAddress
index Int
2024-03-05 18:34:30 +00:00
accId ZcashAccountId
name T.Text
2024-03-17 12:17:52 +00:00
uAddress UnifiedAddressDB
scope ScopeDB
UniqueAddress index scope accId
2024-03-05 18:34:30 +00:00
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
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
2024-03-17 12:17:52 +00:00
getWallets dbFp n =
runSqlite dbFp $ selectList [ZcashWalletNetwork ==. ZcashNetDB n] []
2024-03-05 18:34:30 +00:00
-- | 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]
2024-03-17 12:17:52 +00:00
getAddresses dbFp a =
runSqlite dbFp $
selectList
[WalletAddressAccId ==. a, WalletAddressScope ==. ScopeDB External]
[]
2024-03-05 18:34:30 +00:00
-- | Returns the largest address index for the given account
getMaxAddress ::
T.Text -- ^ The database path
2024-03-17 12:17:52 +00:00
-> ZcashAccountId -- ^ The account ID to check
-> Scope -- ^ The scope of the address
2024-03-05 18:34:30 +00:00
-> IO Int
2024-03-17 12:17:52 +00:00
getMaxAddress dbFp aw s = do
2024-03-05 18:34:30 +00:00
a <-
runSqlite dbFp $
2024-03-17 12:17:52 +00:00
selectFirst
[WalletAddressAccId ==. aw, WalletAddressScope ==. ScopeDB s]
[Desc WalletAddressIndex]
2024-03-05 18:34:30 +00:00
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