zenith/src/Zenith/DB.hs

319 lines
8.7 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-04-03 20:14:14 +00:00
import Control.Monad (when)
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 Data.HexString
2024-04-03 20:14:14 +00:00
import Data.Maybe (fromJust, isJust)
2024-01-22 18:58:37 +00:00
import qualified Data.Text as T
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
2024-04-03 20:14:14 +00:00
import Haskoin.Transaction.Common (TxOut(..))
import ZcashHaskell.Types
( OrchardAction(..)
, OrchardBundle(..)
, SaplingBundle(..)
, Scope(..)
, ShieldedOutput(..)
, ShieldedSpend(..)
, Transaction(..)
, TransparentBundle(..)
, ZcashNet
)
2024-03-17 12:17:52 +00:00
import Zenith.Types
( HexStringDB(..)
, OrchardSpendingKeyDB(..)
2024-03-17 12:17:52 +00:00
, 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
WalletTransaction
2024-04-04 18:21:55 +00:00
txId HexStringDB
2024-04-04 19:35:08 +00:00
block Int
2024-04-04 18:21:55 +00:00
conf Int
time Int
deriving Show Eq
WalletTrNote
tx WalletTransactionId
2024-04-04 19:35:08 +00:00
addrId WalletAddressId
2024-04-04 18:21:55 +00:00
value Int
rawId TransparentNoteId
spent Bool
deriving Show Eq
WalletSapNote
tx WalletTransactionId
2024-04-04 19:35:08 +00:00
addrId WalletAddressId
2024-04-04 18:21:55 +00:00
value Int
recipient BS.ByteString
memo T.Text
rawId ShieldOutputId
spent Bool
deriving Show Eq
WalletOrchNote
tx WalletTransactionId
2024-04-04 19:35:08 +00:00
addrId WalletAddressId
2024-04-04 18:21:55 +00:00
value Int
recipient BS.ByteString
memo T.Text
rawId OrchActionId
spent Bool
deriving Show Eq
ZcashTransaction
block Int
txId HexStringDB
conf Int
time Int
deriving Show Eq
2024-04-03 20:14:14 +00:00
TransparentNote
2024-04-04 18:21:55 +00:00
tx ZcashTransactionId
2024-04-03 20:14:14 +00:00
value Int
script BS.ByteString
OrchAction
2024-04-04 18:21:55 +00:00
tx ZcashTransactionId
nf HexStringDB
rk HexStringDB
cmx HexStringDB
ephKey HexStringDB
encCipher HexStringDB
outCipher HexStringDB
cv HexStringDB
auth HexStringDB
deriving Show Eq
ShieldOutput
2024-04-04 18:21:55 +00:00
tx ZcashTransactionId
cv HexStringDB
cmu HexStringDB
ephKey HexStringDB
encCipher HexStringDB
outCipher HexStringDB
proof HexStringDB
deriving Show Eq
ShieldSpend
2024-04-04 18:21:55 +00:00
tx ZcashTransactionId
cv HexStringDB
anchor HexStringDB
nullifier HexStringDB
rk HexStringDB
proof HexStringDB
authSig HexStringDB
deriving Show Eq
|]
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
2024-04-04 18:21:55 +00:00
-- | Returns the largest block in storage
getMaxBlock ::
T.Text -- ^ The database path
-> IO Int
getMaxBlock dbPath = do
b <-
runSqlite dbPath $
selectFirst [ZcashTransactionBlock >. 0] [Desc ZcashTransactionBlock]
case b of
Nothing -> return $ -1
Just x -> return $ zcashTransactionBlock $ entityVal x
2024-04-04 19:35:08 +00:00
-- | Returns the largest block in the wallet
getMaxWalletBlock ::
T.Text -- ^ The database path
-> IO Int
getMaxWalletBlock dbPath = do
b <-
runSqlite dbPath $
selectFirst [WalletTransactionBlock >. 0] [Desc WalletTransactionBlock]
case b of
Nothing -> return $ -1
Just x -> return $ walletTransactionBlock $ entityVal x
2024-03-05 18:34:30 +00:00
-- | 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
2024-04-03 20:14:14 +00:00
-- | Save a transaction to the data model
saveTransaction ::
T.Text -- ^ the database path
-> Int -- ^ block time
-> Transaction -- ^ The transaction to save
2024-04-04 18:21:55 +00:00
-> IO (Key ZcashTransaction)
2024-04-03 20:14:14 +00:00
saveTransaction dbFp t wt =
runSqlite dbFp $ do
w <-
insert $
2024-04-04 18:21:55 +00:00
ZcashTransaction (tx_height wt) (HexStringDB $ tx_id wt) (tx_conf wt) t
2024-04-03 20:14:14 +00:00
when (isJust $ tx_transpBundle wt) $
insertMany_ $
map (storeTxOut w) $ (tb_vout . fromJust . tx_transpBundle) wt
when (isJust $ tx_saplingBundle wt) $ do
_ <-
insertMany_ $
map (storeSapSpend w) $ (sbSpends . fromJust . tx_saplingBundle) wt
_ <-
insertMany_ $
map (storeSapOutput w) $ (sbOutputs . fromJust . tx_saplingBundle) wt
return ()
when (isJust $ tx_orchardBundle wt) $
insertMany_ $
map (storeOrchAction w) $ (obActions . fromJust . tx_orchardBundle) wt
return w
where
2024-04-04 18:21:55 +00:00
storeTxOut :: ZcashTransactionId -> TxOut -> TransparentNote
2024-04-03 20:14:14 +00:00
storeTxOut wid (TxOut v s) = TransparentNote wid (fromIntegral v) s
2024-04-04 18:21:55 +00:00
storeSapSpend :: ZcashTransactionId -> ShieldedSpend -> ShieldSpend
2024-04-03 20:14:14 +00:00
storeSapSpend wid 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)
2024-04-04 18:21:55 +00:00
storeSapOutput :: ZcashTransactionId -> ShieldedOutput -> ShieldOutput
2024-04-03 20:14:14 +00:00
storeSapOutput wid 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)
2024-04-04 18:21:55 +00:00
storeOrchAction :: ZcashTransactionId -> OrchardAction -> OrchAction
2024-04-03 20:14:14 +00:00
storeOrchAction wid 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)