{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeOperators #-} module Zenith.DB where import Control.Monad.IO.Class (liftIO) import qualified Data.ByteString as BS import qualified Data.Text as T import Database.Persist import Database.Persist.Sqlite import Database.Persist.TH import ZcashHaskell.Types (Phrase, UnifiedAddress(..), ZcashNet) derivePersistField "ZcashNet" derivePersistField "UnifiedAddress" share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| ZcashWallet name T.Text network ZcashNet seedPhrase Phrase birthdayHeight Int UniqueWallet name network deriving Show Eq ZcashAccount index Int walletId ZcashWalletId name T.Text orchSpendKey BS.ByteString sapSpendKey BS.ByteString tPrivateKey BS.ByteString UniqueAccount index walletId UniqueAccName walletId name deriving Show Eq WalletAddress index Int accId ZcashAccountId name T.Text uAddress UnifiedAddress UniqueAddress index accId UniqueAddName accId name deriving Show Eq |] -- * 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] 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