Compare commits

..

4 commits

6 changed files with 56 additions and 29 deletions

View file

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
-- Core wallet functionality for Zenith
-- | Core wallet functionality for Zenith
module Zenith.Core where
import Control.Exception (throwIO)

View file

@ -19,13 +19,15 @@ module Zenith.DB where
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString as BS
import Data.HexString
import qualified Data.Text as T
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
import ZcashHaskell.Types (Scope(..), ZcashNet)
import Zenith.Types
( OrchardSpendingKeyDB(..)
( HexStringDB(..)
, OrchardSpendingKeyDB(..)
, PhraseDB(..)
, SaplingSpendingKeyDB(..)
, ScopeDB(..)
@ -65,6 +67,18 @@ share
deriving Show Eq
|]
share
[mkPersist sqlSettings, mkMigrate "rawStorage"]
[persistLowerCase|
WalletTransaction
block Int
txId HexStringDB
conf Int
time Int
hex HexStringDB
deriving Show Eq
|]
-- * Database functions
-- | Initializes the database
initDb ::
@ -73,6 +87,12 @@ initDb ::
initDb dbName = do
runSqlite dbName $ do runMigration migrateAll
-- | Initializes the raw data storage
initRawStore ::
T.Text -- ^ the database path
-> IO ()
initRawStore dbFilePath = runSqlite dbFilePath $ runMigration rawStorage
-- | Get existing wallets from database
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
getWallets dbFp n =

22
src/Zenith/Scanner.hs Normal file
View file

@ -0,0 +1,22 @@
module Zenith.Scanner where
import Control.Monad (when)
import qualified Data.Text as T
import Zenith.Core (checkBlockChain)
-- | Function to scan the Zcash blockchain through the Zebra node and populate the Zenith database
scanZebra ::
Int -- ^ Starting block
-> T.Text -- ^ Host
-> Int -- ^ Port
-> T.Text -- ^ Path to database file
-> IO ()
scanZebra b host port dbFilePath = do
bc <- checkBlockChain host port
case bc of
Nothing -> throwIO $ userError "Failed to determine blockchain status"
Just bStatus -> do
if b > zgb_blocks bStatus
then throwIO $ userError "Invalid starting block for scan"
else do
let bList = [b .. (zgb_blocks bStatus)]

View file

@ -14,6 +14,7 @@ import Data.Aeson.Types (prependFailure, typeMismatch)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Char8 as C
import Data.HexString
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
@ -29,6 +30,13 @@ import ZcashHaskell.Types
, ZcashNet(..)
)
-- * Database field type wrappers
newtype HexStringDB = HexStringDB
{ getHex :: HexString
} deriving newtype (Eq, Show, Read)
derivePersistField "HexStringDB"
newtype ZcashNetDB = ZcashNetDB
{ getNet :: ZcashNet
} deriving newtype (Eq, Show, Read)
@ -71,15 +79,8 @@ newtype TransparentSpendingKeyDB = TransparentSpendingKeyDB
derivePersistField "TransparentSpendingKeyDB"
-- | A type to model Zcash RPC calls
data RpcCall = RpcCall
{ jsonrpc :: T.Text
, id :: T.Text
, method :: T.Text
, params :: [Value]
} deriving (Show, Generic, ToJSON, FromJSON)
-- | Type for modelling the different address sources for Zcash 5.0.0
-- * RPC
-- | Type for modelling the different address sources for `zcashd` 5.0.0
data AddressSource
= LegacyRandom
| Imported
@ -128,24 +129,6 @@ instance Show ZcashAddress where
T.unpack (T.take 8 a) ++
"..." ++ T.unpack (T.takeEnd 8 a) ++ " Pools: " ++ show p
-- | A type to model the response of the Zcash RPC
data RpcResponse r = RpcResponse
{ err :: Maybe T.Text
, respId :: T.Text
, result :: r
} deriving (Show, Generic, ToJSON)
instance (FromJSON r) => FromJSON (RpcResponse r) where
parseJSON (Object obj) = do
e <- obj .: "error"
rId <- obj .: "id"
r <- obj .: "result"
pure $ RpcResponse e rId r
parseJSON invalid =
prependFailure
"parsing RpcResponse failed, "
(typeMismatch "Object" invalid)
newtype NodeVersion =
NodeVersion Integer
deriving (Eq, Show)

View file

@ -32,6 +32,7 @@ library
Zenith.Types
Zenith.Utils
Zenith.Zcashd
Zenith.Scanner
hs-source-dirs:
src
build-depends:

View file

@ -3,3 +3,4 @@ nodePwd = "superSecret"
dbFilePath = "zenith.db"
zebraHost = "127.0.0.1"
zebraPort = 18232
dataStorePath = "datastore.db"