{-# 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 #-} {-# LANGUAGE TypeApplications #-} module Zenith.DB where import Control.Monad (when) import qualified Data.ByteString as BS import Data.HexString import Data.Maybe (fromJust, isJust) import qualified Data.Text as T import qualified Data.Text.Encoding as TE import Database.Esqueleto.Experimental import qualified Database.Persist as P import qualified Database.Persist.Sqlite as PS import Database.Persist.TH import Haskoin.Transaction.Common ( OutPoint(..) , TxIn(..) , TxOut(..) , txHashToHex ) import ZcashHaskell.Orchard (isValidUnifiedAddress) import ZcashHaskell.Types ( OrchardAction(..) , OrchardBundle(..) , SaplingBundle(..) , Scope(..) , ShieldedOutput(..) , ShieldedSpend(..) , Transaction(..) , TransparentAddress(..) , TransparentBundle(..) , UnifiedAddress(..) , ZcashNet ) import Zenith.Types ( HexStringDB(..) , OrchardSpendingKeyDB(..) , PhraseDB(..) , SaplingSpendingKeyDB(..) , ScopeDB(..) , TransparentSpendingKeyDB , UnifiedAddressDB(..) , ZcashNetDB(..) ) share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| ZcashWallet name T.Text network ZcashNetDB seedPhrase PhraseDB birthdayHeight Int UniqueWallet name network deriving Show Eq ZcashAccount index Int walletId ZcashWalletId name T.Text orchSpendKey OrchardSpendingKeyDB sapSpendKey SaplingSpendingKeyDB tPrivateKey TransparentSpendingKeyDB UniqueAccount index walletId UniqueAccName walletId name deriving Show Eq WalletAddress index Int accId ZcashAccountId name T.Text uAddress UnifiedAddressDB scope ScopeDB UniqueAddress index scope accId UniqueAddName accId name deriving Show Eq WalletTransaction txId HexStringDB block Int conf Int time Int UniqueWTx txId deriving Show Eq WalletTrNote tx WalletTransactionId addrId WalletAddressId value Int rawId TransparentNoteId spent Bool deriving Show Eq WalletSapNote tx WalletTransactionId addrId WalletAddressId value Int recipient BS.ByteString memo T.Text rawId ShieldOutputId spent Bool nullifier HexStringDB deriving Show Eq WalletOrchNote tx WalletTransactionId addrId WalletAddressId value Int recipient BS.ByteString memo T.Text rawId OrchActionId spent Bool nullifier HexStringDB deriving Show Eq ZcashTransaction block Int txId HexStringDB conf Int time Int deriving Show Eq TransparentNote tx ZcashTransactionId value Int script BS.ByteString position Int UniqueTNPos tx position deriving Show Eq TransparentSpend tx ZcashTransactionId outPointHash HexStringDB outPointIndex Int script BS.ByteString seq Int position Int UniqueTSPos tx position deriving Show Eq OrchAction tx ZcashTransactionId nf HexStringDB rk HexStringDB cmx HexStringDB ephKey HexStringDB encCipher HexStringDB outCipher HexStringDB cv HexStringDB auth HexStringDB position Int UniqueOAPos tx position deriving Show Eq ShieldOutput tx ZcashTransactionId cv HexStringDB cmu HexStringDB ephKey HexStringDB encCipher HexStringDB outCipher HexStringDB proof HexStringDB position Int UniqueSOPos tx position deriving Show Eq ShieldSpend tx ZcashTransactionId cv HexStringDB anchor HexStringDB nullifier HexStringDB rk HexStringDB proof HexStringDB authSig HexStringDB position Int UniqueSSPos tx position deriving Show Eq |] -- * Database functions -- | Initializes the database initDb :: T.Text -- ^ The database path to check -> IO () initDb dbName = do PS.runSqlite dbName $ do runMigration migrateAll -- | Get existing wallets from database getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet] getWallets dbFp n = PS.runSqlite dbFp $ select $ do wallets <- from $ table @ZcashWallet where_ (wallets ^. ZcashWalletNetwork ==. val (ZcashNetDB n)) pure wallets -- | 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 = PS.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 = PS.runSqlite dbFp $ select $ do accs <- from $ table @ZcashAccount where_ (accs ^. ZcashAccountWalletId ==. val w) pure accs -- | 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 <- PS.runSqlite dbFp $ selectOne $ do accs <- from $ table @ZcashAccount where_ (accs ^. ZcashAccountWalletId ==. val w) orderBy [desc $ accs ^. ZcashAccountIndex] pure accs 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 = PS.runSqlite dbFp $ insertUniqueEntity a -- | Returns the largest block in storage getMaxBlock :: T.Text -- ^ The database path -> IO Int getMaxBlock dbPath = do b <- PS.runSqlite dbPath $ selectOne $ do txs <- from $ table @ZcashTransaction where_ (txs ^. ZcashTransactionBlock >. val 0) orderBy [desc $ txs ^. ZcashTransactionBlock] pure txs case b of Nothing -> return $ -1 Just x -> return $ zcashTransactionBlock $ entityVal x -- | 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 = PS.runSqlite dbFp $ select $ do addrs <- from $ table @WalletAddress where_ (addrs ^. WalletAddressAccId ==. val a) where_ (addrs ^. WalletAddressScope ==. val (ScopeDB External)) pure addrs -- | Returns a list of addressess associated with the given wallet getWalletAddresses :: T.Text -- ^ The database path -> ZcashWalletId -- ^ the wallet to search -> IO [Entity WalletAddress] getWalletAddresses dbFp w = do accs <- getAccounts dbFp w addrs <- mapM (getAddresses dbFp . entityKey) accs return $ concat addrs -- | Returns the largest address index for the given account getMaxAddress :: T.Text -- ^ The database path -> ZcashAccountId -- ^ The account ID to check -> Scope -- ^ The scope of the address -> IO Int getMaxAddress dbFp aw s = do a <- PS.runSqlite dbFp $ selectOne $ do addrs <- from $ table @WalletAddress where_ $ addrs ^. WalletAddressAccId ==. val aw where_ $ addrs ^. WalletAddressScope ==. val (ScopeDB s) orderBy [desc $ addrs ^. WalletAddressIndex] pure addrs 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 = PS.runSqlite dbFp $ insertUniqueEntity w -- | Save a transaction to the data model saveTransaction :: T.Text -- ^ the database path -> Int -- ^ block time -> Transaction -- ^ The transaction to save -> IO (Key ZcashTransaction) saveTransaction dbFp t wt = PS.runSqlite dbFp $ do let ix = [0 ..] w <- insert $ ZcashTransaction (tx_height wt) (HexStringDB $ tx_id wt) (tx_conf wt) t when (isJust $ tx_transpBundle wt) $ do _ <- insertMany_ $ zipWith (curry (storeTxOut w)) ix $ (tb_vout . fromJust . tx_transpBundle) wt _ <- insertMany_ $ zipWith (curry (storeTxIn w)) ix $ (tb_vin . fromJust . tx_transpBundle) wt return () when (isJust $ tx_saplingBundle wt) $ do _ <- insertMany_ $ zipWith (curry (storeSapSpend w)) ix $ (sbSpends . fromJust . tx_saplingBundle) wt _ <- insertMany_ $ zipWith (curry (storeSapOutput w)) ix $ (sbOutputs . fromJust . tx_saplingBundle) wt return () when (isJust $ tx_orchardBundle wt) $ insertMany_ $ zipWith (curry (storeOrchAction w)) ix $ (obActions . fromJust . tx_orchardBundle) wt return w where storeTxOut :: ZcashTransactionId -> (Int, TxOut) -> TransparentNote storeTxOut wid (i, TxOut v s) = TransparentNote wid (fromIntegral v) s i storeTxIn :: ZcashTransactionId -> (Int, TxIn) -> TransparentSpend storeTxIn wid (i, TxIn (OutPoint h k) s sq) = TransparentSpend wid (HexStringDB . fromText $ txHashToHex h) (fromIntegral k) s (fromIntegral sq) i storeSapSpend :: ZcashTransactionId -> (Int, ShieldedSpend) -> ShieldSpend storeSapSpend wid (i, sp) = ShieldSpend wid (HexStringDB $ sp_cv sp) (HexStringDB $ sp_anchor sp) (HexStringDB $ sp_nullifier sp) (HexStringDB $ sp_rk sp) (HexStringDB $ sp_proof sp) (HexStringDB $ sp_auth sp) i storeSapOutput :: ZcashTransactionId -> (Int, ShieldedOutput) -> ShieldOutput storeSapOutput wid (i, so) = ShieldOutput wid (HexStringDB $ s_cv so) (HexStringDB $ s_cmu so) (HexStringDB $ s_ephKey so) (HexStringDB $ s_encCipherText so) (HexStringDB $ s_outCipherText so) (HexStringDB $ s_proof so) i storeOrchAction :: ZcashTransactionId -> (Int, OrchardAction) -> OrchAction storeOrchAction wid (i, oa) = OrchAction wid (HexStringDB $ nf oa) (HexStringDB $ rk oa) (HexStringDB $ cmx oa) (HexStringDB $ eph_key oa) (HexStringDB $ enc_ciphertext oa) (HexStringDB $ out_ciphertext oa) (HexStringDB $ cv oa) (HexStringDB $ auth oa) i -- | Get the transactions from a particular block forward getZcashTransactions :: T.Text -- ^ The database path -> Int -- ^ Block -> IO [Entity ZcashTransaction] getZcashTransactions dbFp b = PS.runSqlite dbFp $ select $ do txs <- from $ table @ZcashTransaction where_ $ txs ^. ZcashTransactionBlock >. val b orderBy [asc $ txs ^. ZcashTransactionBlock] return txs -- * Wallet -- | Get the block of the last transaction known to the wallet getMaxWalletBlock :: T.Text -- ^ The database path -> IO Int getMaxWalletBlock dbPath = do b <- PS.runSqlite dbPath $ selectOne $ do txs <- from $ table @WalletTransaction where_ $ txs ^. WalletTransactionBlock >. val 0 orderBy [desc $ txs ^. WalletTransactionBlock] return txs case b of Nothing -> return $ -1 Just x -> return $ walletTransactionBlock $ entityVal x -- | Find the Transparent Notes that match the given transparent receiver findTransparentNotes :: T.Text -- ^ The database path -> Int -- ^ Starting block -> WalletAddress -> IO [(Entity ZcashTransaction, Entity TransparentNote)] findTransparentNotes dbPath b t = do let tReceiver = t_rec =<< readUnifiedAddressDB t case tReceiver of Just tR -> do let s = BS.concat [ BS.pack [0x76, 0xA9, 0x14] , (toBytes . ta_bytes) tR , BS.pack [0x88, 0xAC] ] PS.runSqlite dbPath $ select $ do (txs :& tNotes) <- from $ table @ZcashTransaction `innerJoin` table @TransparentNote `on` (\(txs :& tNotes) -> txs ^. ZcashTransactionId ==. tNotes ^. TransparentNoteTx) where_ (txs ^. ZcashTransactionBlock >. val b) where_ (tNotes ^. TransparentNoteScript ==. val s) pure (txs, tNotes) Nothing -> return [] -- | Add the transparent notes to the wallet saveWalletTrNote :: T.Text -- ^ the database path -> (Entity ZcashTransaction, Entity TransparentNote) -> WalletAddressId -> IO () saveWalletTrNote dbPath (zt, tn) wa = do let zT' = entityVal zt PS.runSqlite dbPath $ do t <- upsert (WalletTransaction (zcashTransactionTxId zT') (zcashTransactionBlock zT') (zcashTransactionConf zT') (zcashTransactionTime zT')) [] insert_ $ WalletTrNote (entityKey t) wa (transparentNoteValue $ entityVal tn) (entityKey tn) False -- | Helper function to extract a Unified Address from the database readUnifiedAddressDB :: WalletAddress -> Maybe UnifiedAddress readUnifiedAddressDB = isValidUnifiedAddress . TE.encodeUtf8 . getUA . walletAddressUAddress