zenith/src/Zenith/Core.hs

74 lines
2.5 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
-- Core wallet functionality for Zenith
module Zenith.Core where
import Control.Exception (throwIO)
import Data.Aeson
import qualified Data.ByteString as BS
import qualified Data.Text as T
import Database.Persist
import Network.HTTP.Client
import ZcashHaskell.Keys
import ZcashHaskell.Orchard
import ZcashHaskell.Types
import ZcashHaskell.Utils
import Zenith.DB
-- * Zebra Node interaction
-- | Checks the status of the `zebrad` node
checkZebra ::
T.Text -- ^ Host where `zebrad` is available
-> Int -- ^ Port where `zebrad` is available
-> IO (Maybe ZebraGetInfo)
checkZebra nodeHost nodePort = do
res <- makeZebraCall nodeHost nodePort "getinfo" []
let body = responseBody (res :: Response (RpcResponse ZebraGetInfo))
return $ result body
-- | Checks the status of the Zcash blockchain
checkBlockChain ::
T.Text -- ^ Host where `zebrad` is available
-> Int -- ^ Port where `zebrad` is available
-> IO (Maybe ZebraGetBlockChainInfo)
checkBlockChain nodeHost nodePort = do
let f = makeZebraCall nodeHost nodePort
result <$> (responseBody <$> f "getblockchaininfo" [])
-- | Generic RPC call function
connectZebra ::
FromJSON a => T.Text -> Int -> T.Text -> [Data.Aeson.Value] -> IO (Maybe a)
connectZebra nodeHost nodePort m params = do
res <- makeZebraCall nodeHost nodePort m params
let body = responseBody res
return $ result body
-- * Spending Keys
-- | Create an Orchard Spending Key for the given wallet and account index
createOrchardSpendingKey :: ZcashWallet -> Int -> IO BS.ByteString
createOrchardSpendingKey zw i = do
let s = getWalletSeed $ zcashWalletSeedPhrase zw
case s of
Nothing -> throwIO $ userError "Unable to generate seed"
Just s' -> do
let coinType =
case zcashWalletNetwork zw of
MainNet -> MainNetCoin
TestNet -> TestNetCoin
RegTestNet -> RegTestNetCoin
let r = genOrchardSpendingKey s' coinType i
case r of
Nothing -> throwIO $ userError "Unable to generate Orchard spending key"
Just sk -> return sk
-- * Accounts
-- | Create an account for the given wallet and account index
createZcashAccount ::
T.Text -- ^ The account's name
-> Int -- ^ The account's index
-> Entity ZcashWallet -- ^ The Zcash wallet that this account will be attached to
-> IO ZcashAccount
createZcashAccount n i zw = do
orSk <- createOrchardSpendingKey (entityVal zw) i
return $ ZcashAccount i (entityKey zw) n orSk "fakeSapKey" "fakeTkey"