zenith/src/Zenith/RPC.hs

697 lines
26 KiB
Haskell
Raw Permalink Normal View History

2024-07-23 18:46:37 +00:00
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
2024-07-24 21:03:49 +00:00
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
2024-08-05 17:54:02 +00:00
{-# LANGUAGE LambdaCase #-}
2024-07-23 18:46:37 +00:00
module Zenith.RPC where
2024-08-03 12:01:11 +00:00
import Control.Exception (try)
import Control.Monad.IO.Class (liftIO)
2024-08-05 17:54:02 +00:00
import Control.Monad.Logger (runNoLoggingT)
2024-07-23 18:46:37 +00:00
import Data.Aeson
2024-08-12 20:35:00 +00:00
import Data.Int
2024-08-24 12:45:42 +00:00
import Data.Scientific (floatingOrInteger)
2024-07-23 18:46:37 +00:00
import qualified Data.Text as T
2024-08-15 16:17:24 +00:00
import qualified Data.Text.Encoding as E
2024-09-04 18:10:09 +00:00
import qualified Data.UUID as U
2024-08-05 17:54:02 +00:00
import qualified Data.Vector as V
2024-09-04 18:10:09 +00:00
import Database.Esqueleto.Experimental
( entityKey
, entityVal
, fromSqlKey
, toSqlKey
)
2024-07-23 18:46:37 +00:00
import Servant
2024-08-12 20:35:00 +00:00
import Text.Read (readMaybe)
2024-08-24 12:45:42 +00:00
import ZcashHaskell.Keys (generateWalletSeedPhrase)
2024-08-15 16:17:24 +00:00
import ZcashHaskell.Orchard (parseAddress)
2024-08-30 20:14:48 +00:00
import ZcashHaskell.Types (RpcError(..), Scope(..), ZcashNet(..))
import Zenith.Core (createCustomWalletAddress, createZcashAccount)
2024-08-06 18:38:00 +00:00
import Zenith.DB
2024-09-04 18:10:09 +00:00
( Operation(..)
, ZcashAccount(..)
2024-08-26 20:25:31 +00:00
, ZcashWallet(..)
2024-08-24 12:45:42 +00:00
, findNotesByAddress
2024-08-16 18:31:25 +00:00
, getAccountById
2024-08-15 16:17:24 +00:00
, getAccounts
2024-08-12 20:35:00 +00:00
, getAddressById
2024-08-07 15:21:04 +00:00
, getAddresses
2024-08-15 16:17:24 +00:00
, getExternalAddresses
2024-08-26 20:25:31 +00:00
, getMaxAccount
2024-08-30 20:14:48 +00:00
, getMaxAddress
2024-09-04 18:10:09 +00:00
, getOperation
2024-08-16 18:31:25 +00:00
, getPoolBalance
, getUnconfPoolBalance
2024-08-12 20:35:00 +00:00
, getWalletNotes
2024-08-06 18:38:00 +00:00
, getWallets
, initPool
2024-08-26 20:25:31 +00:00
, saveAccount
2024-08-30 20:14:48 +00:00
, saveAddress
2024-08-24 12:45:42 +00:00
, saveWallet
2024-08-06 18:38:00 +00:00
, toZcashAccountAPI
2024-08-07 15:21:04 +00:00
, toZcashAddressAPI
2024-08-06 18:38:00 +00:00
, toZcashWalletAPI
2024-08-26 20:25:31 +00:00
, walletExists
2024-08-06 18:38:00 +00:00
)
2024-08-07 15:21:04 +00:00
import Zenith.Types
2024-08-16 18:31:25 +00:00
( AccountBalance(..)
, Config(..)
2024-08-24 12:45:42 +00:00
, PhraseDB(..)
2024-08-07 15:21:04 +00:00
, ZcashAccountAPI(..)
, ZcashAddressAPI(..)
2024-08-24 12:45:42 +00:00
, ZcashNetDB(..)
2024-08-10 12:04:40 +00:00
, ZcashNoteAPI(..)
2024-08-07 15:21:04 +00:00
, ZcashWalletAPI(..)
2024-09-04 18:10:09 +00:00
, ZenithUuid(..)
2024-08-07 15:21:04 +00:00
)
2024-08-06 18:38:00 +00:00
import Zenith.Utils (jsonNumber)
2024-08-05 17:54:02 +00:00
data ZenithMethod
= GetInfo
| ListWallets
2024-08-06 18:38:00 +00:00
| ListAccounts
2024-08-07 15:21:04 +00:00
| ListAddresses
2024-08-10 12:04:40 +00:00
| ListReceived
2024-08-16 18:31:25 +00:00
| GetBalance
2024-08-24 12:45:42 +00:00
| GetNewWallet
2024-08-26 20:25:31 +00:00
| GetNewAccount
2024-08-30 20:14:48 +00:00
| GetNewAddress
2024-09-04 18:10:09 +00:00
| GetOperationStatus
2024-08-05 17:54:02 +00:00
| UnknownMethod
deriving (Eq, Prelude.Show)
instance ToJSON ZenithMethod where
toJSON GetInfo = Data.Aeson.String "getinfo"
toJSON ListWallets = Data.Aeson.String "listwallets"
2024-08-06 18:38:00 +00:00
toJSON ListAccounts = Data.Aeson.String "listaccounts"
2024-08-07 15:21:04 +00:00
toJSON ListAddresses = Data.Aeson.String "listaddresses"
2024-08-10 12:04:40 +00:00
toJSON ListReceived = Data.Aeson.String "listreceived"
2024-08-16 18:31:25 +00:00
toJSON GetBalance = Data.Aeson.String "getbalance"
2024-08-24 12:45:42 +00:00
toJSON GetNewWallet = Data.Aeson.String "getnewwallet"
2024-08-26 20:25:31 +00:00
toJSON GetNewAccount = Data.Aeson.String "getnewaccount"
2024-08-30 20:14:48 +00:00
toJSON GetNewAddress = Data.Aeson.String "getnewaddress"
2024-09-04 18:10:09 +00:00
toJSON GetOperationStatus = Data.Aeson.String "getoperationstatus"
2024-08-05 17:54:02 +00:00
toJSON UnknownMethod = Data.Aeson.Null
instance FromJSON ZenithMethod where
parseJSON =
withText "ZenithMethod" $ \case
"getinfo" -> pure GetInfo
"listwallets" -> pure ListWallets
2024-08-06 18:38:00 +00:00
"listaccounts" -> pure ListAccounts
2024-08-07 15:21:04 +00:00
"listaddresses" -> pure ListAddresses
2024-08-10 12:04:40 +00:00
"listreceived" -> pure ListReceived
2024-08-16 18:31:25 +00:00
"getbalance" -> pure GetBalance
2024-08-24 12:45:42 +00:00
"getnewwallet" -> pure GetNewWallet
2024-08-26 20:25:31 +00:00
"getnewaccount" -> pure GetNewAccount
2024-08-30 20:14:48 +00:00
"getnewaddress" -> pure GetNewAddress
2024-09-04 18:10:09 +00:00
"getoperationstatus" -> pure GetOperationStatus
2024-08-05 17:54:02 +00:00
_ -> pure UnknownMethod
data ZenithParams
= BlankParams
| BadParams
2024-08-06 18:38:00 +00:00
| AccountsParams !Int
2024-08-07 15:21:04 +00:00
| AddressesParams !Int
2024-08-10 12:04:40 +00:00
| NotesParams !T.Text
2024-08-16 18:31:25 +00:00
| BalanceParams !Int64
2024-08-24 12:45:42 +00:00
| NameParams !T.Text
2024-08-26 20:25:31 +00:00
| NameIdParams !T.Text !Int
2024-08-30 20:14:48 +00:00
| NewAddrParams !Int !T.Text !Bool !Bool
2024-09-04 18:10:09 +00:00
| OpParams !ZenithUuid
2024-08-05 17:54:02 +00:00
| TestParams !T.Text
deriving (Eq, Prelude.Show)
instance ToJSON ZenithParams where
toJSON BlankParams = Data.Aeson.Array V.empty
toJSON BadParams = Data.Aeson.Null
2024-08-06 18:38:00 +00:00
toJSON (AccountsParams n) = Data.Aeson.Array $ V.fromList [jsonNumber n]
2024-08-07 15:21:04 +00:00
toJSON (AddressesParams n) = Data.Aeson.Array $ V.fromList [jsonNumber n]
2024-08-05 17:54:02 +00:00
toJSON (TestParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t]
2024-08-10 12:04:40 +00:00
toJSON (NotesParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t]
2024-08-24 12:45:42 +00:00
toJSON (NameParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t]
2024-08-26 20:25:31 +00:00
toJSON (NameIdParams t i) =
Data.Aeson.Array $ V.fromList [Data.Aeson.String t, jsonNumber i]
2024-08-16 18:31:25 +00:00
toJSON (BalanceParams n) =
Data.Aeson.Array $ V.fromList [jsonNumber $ fromIntegral n]
2024-08-30 20:14:48 +00:00
toJSON (NewAddrParams a n s t) =
Data.Aeson.Array $
V.fromList $
[jsonNumber a, Data.Aeson.String n] <>
[Data.Aeson.String "ExcludeSapling" | s] <>
[Data.Aeson.String "ExcludeTransparent" | t]
2024-09-04 18:10:09 +00:00
toJSON (OpParams i) =
Data.Aeson.Array $ V.fromList [Data.Aeson.String $ U.toText $ getUuid i]
2024-08-05 17:54:02 +00:00
data ZenithResponse
= InfoResponse !T.Text !ZenithInfo
| WalletListResponse !T.Text ![ZcashWalletAPI]
2024-08-06 18:38:00 +00:00
| AccountListResponse !T.Text ![ZcashAccountAPI]
2024-08-07 15:21:04 +00:00
| AddressListResponse !T.Text ![ZcashAddressAPI]
2024-08-10 12:04:40 +00:00
| NoteListResponse !T.Text ![ZcashNoteAPI]
2024-08-16 18:31:25 +00:00
| BalanceResponse !T.Text !AccountBalance !AccountBalance
2024-08-24 12:45:42 +00:00
| NewItemResponse !T.Text !Int64
2024-08-30 20:14:48 +00:00
| NewAddrResponse !T.Text !ZcashAddressAPI
2024-09-04 18:10:09 +00:00
| OpResponse !T.Text !Operation
2024-08-05 17:54:02 +00:00
| ErrorResponse !T.Text !Double !T.Text
deriving (Eq, Prelude.Show)
instance ToJSON ZenithResponse where
2024-08-10 12:04:40 +00:00
toJSON (InfoResponse t i) = packRpcResponse t i
toJSON (WalletListResponse i w) = packRpcResponse i w
toJSON (AccountListResponse i a) = packRpcResponse i a
toJSON (AddressListResponse i a) = packRpcResponse i a
toJSON (NoteListResponse i n) = packRpcResponse i n
2024-08-05 17:54:02 +00:00
toJSON (ErrorResponse i c m) =
object
[ "jsonrpc" .= ("2.0" :: String)
, "id" .= i
, "error" .= object ["code" .= c, "message" .= m]
]
2024-08-16 18:31:25 +00:00
toJSON (BalanceResponse i c u) =
packRpcResponse i $ object ["confirmed" .= c, "unconfirmed" .= u]
2024-08-24 12:45:42 +00:00
toJSON (NewItemResponse i ix) = packRpcResponse i ix
2024-08-30 20:14:48 +00:00
toJSON (NewAddrResponse i a) = packRpcResponse i a
2024-09-04 18:10:09 +00:00
toJSON (OpResponse i u) = packRpcResponse i u
2024-08-05 17:54:02 +00:00
instance FromJSON ZenithResponse where
parseJSON =
2024-08-10 12:04:40 +00:00
withObject "ZenithResponse" $ \obj -> do
2024-08-05 17:54:02 +00:00
jr <- obj .: "jsonrpc"
i <- obj .: "id"
e <- obj .:? "error"
r <- obj .:? "result"
if jr /= ("2.0" :: String)
then fail "Malformed JSON"
else do
case e of
Nothing -> do
case r of
Nothing -> fail "Malformed JSON"
Just r1 ->
case r1 of
Object k -> do
v <- k .:? "version"
2024-08-16 18:31:25 +00:00
v5 <- k .:? "unconfirmed"
2024-08-30 20:14:48 +00:00
v6 <- k .:? "ua"
2024-09-04 18:10:09 +00:00
v7 <- k .:? "uuid"
2024-08-05 17:54:02 +00:00
case (v :: Maybe String) of
Just _v' -> do
k1 <- parseJSON r1
pure $ InfoResponse i k1
2024-08-16 18:31:25 +00:00
Nothing ->
case (v5 :: Maybe AccountBalance) of
Just _v5' -> do
k6 <- parseJSON r1
j1 <- k6 .: "confirmed"
j2 <- k6 .: "unconfirmed"
pure $ BalanceResponse i j1 j2
2024-08-30 20:14:48 +00:00
Nothing ->
case (v6 :: Maybe String) of
Just _v6' -> do
k7 <- parseJSON r1
pure $ NewAddrResponse i k7
2024-09-04 18:10:09 +00:00
Nothing ->
case (v7 :: Maybe U.UUID) of
Just _v7' -> do
k8 <- parseJSON r1
pure $ OpResponse i k8
Nothing -> fail "Unknown object"
2024-08-05 17:54:02 +00:00
Array n -> do
if V.null n
then fail "Malformed JSON"
else do
case V.head n of
Object n' -> do
v1 <- n' .:? "lastSync"
2024-08-07 15:21:04 +00:00
v2 <- n' .:? "wallet"
2024-08-10 12:04:40 +00:00
v3 <- n' .:? "ua"
2024-08-16 18:31:25 +00:00
v4 <- n' .:? "amountZats"
2024-08-05 17:54:02 +00:00
case (v1 :: Maybe Int) of
Just _v1' -> do
k2 <- parseJSON r1
pure $ WalletListResponse i k2
2024-08-07 15:21:04 +00:00
Nothing ->
case (v2 :: Maybe Int) of
Just _v2' -> do
k3 <- parseJSON r1
pure $ AccountListResponse i k3
2024-08-10 12:04:40 +00:00
Nothing ->
case (v3 :: Maybe String) of
Just _v3' -> do
k4 <- parseJSON r1
pure $ AddressListResponse i k4
2024-08-16 18:31:25 +00:00
Nothing ->
case (v4 :: Maybe Int) of
Just _v4' -> do
k5 <- parseJSON r1
pure $ NoteListResponse i k5
Nothing -> fail "Unknown object"
2024-08-05 17:54:02 +00:00
_anyOther -> fail "Malformed JSON"
2024-08-24 12:45:42 +00:00
Number k -> do
case floatingOrInteger k of
Left _e -> fail "Unknown value"
Right k' -> pure $ NewItemResponse i k'
2024-08-05 17:54:02 +00:00
_anyOther -> fail "Malformed JSON"
Just e1 -> pure $ ErrorResponse i (ecode e1) (emessage e1)
data ZenithInfo = ZenithInfo
{ zi_version :: !T.Text
, zi_network :: !ZcashNet
, zi_zebra :: !T.Text
} deriving (Eq, Prelude.Show)
instance ToJSON ZenithInfo where
toJSON (ZenithInfo v n z) =
object ["version" .= v, "network" .= n, "zebraVersion" .= z]
instance FromJSON ZenithInfo where
parseJSON =
withObject "ZenithInfo" $ \obj -> do
v <- obj .: "version"
n <- obj .: "network"
z <- obj .: "zebraVersion"
pure $ ZenithInfo v n z
-- | A type to model Zenith RPC calls
data RpcCall = RpcCall
{ jsonrpc :: !T.Text
, callId :: !T.Text
, method :: !ZenithMethod
, parameters :: !ZenithParams
} deriving (Eq, Prelude.Show)
instance ToJSON RpcCall where
toJSON (RpcCall jr i m p) =
object ["jsonrpc" .= jr, "id" .= i, "method" .= m, "params" .= p]
instance FromJSON RpcCall where
parseJSON =
withObject "RpcCall" $ \obj -> do
v <- obj .: "jsonrpc"
i <- obj .: "id"
m <- obj .: "method"
case m of
UnknownMethod -> pure $ RpcCall v i UnknownMethod BlankParams
ListWallets -> do
p <- obj .: "params"
if null (p :: [Value])
then pure $ RpcCall v i ListWallets BlankParams
else pure $ RpcCall v i ListWallets BadParams
GetInfo -> do
p <- obj .: "params"
if null (p :: [Value])
then pure $ RpcCall v i GetInfo BlankParams
else pure $ RpcCall v i GetInfo BadParams
2024-08-06 18:38:00 +00:00
ListAccounts -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
w <- parseJSON $ V.head a
pure $ RpcCall v i ListAccounts (AccountsParams w)
else pure $ RpcCall v i ListAccounts BadParams
_anyOther -> pure $ RpcCall v i ListAccounts BadParams
2024-08-07 15:21:04 +00:00
ListAddresses -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ V.head a
pure $ RpcCall v i ListAddresses (AddressesParams x)
else pure $ RpcCall v i ListAddresses BadParams
_anyOther -> pure $ RpcCall v i ListAddresses BadParams
2024-08-10 12:04:40 +00:00
ListReceived -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ V.head a
pure $ RpcCall v i ListReceived (NotesParams x)
else pure $ RpcCall v i ListReceived BadParams
_anyOther -> pure $ RpcCall v i ListReceived BadParams
2024-08-16 18:31:25 +00:00
GetBalance -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ V.head a
pure $ RpcCall v i GetBalance (BalanceParams x)
else pure $ RpcCall v i GetBalance BadParams
_anyOther -> pure $ RpcCall v i GetBalance BadParams
2024-08-24 12:45:42 +00:00
GetNewWallet -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ V.head a
pure $ RpcCall v i GetNewWallet (NameParams x)
else pure $ RpcCall v i GetNewWallet BadParams
_anyOther -> pure $ RpcCall v i GetNewWallet BadParams
2024-08-26 20:25:31 +00:00
GetNewAccount -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 2
then do
x <- parseJSON $ a V.! 0
y <- parseJSON $ a V.! 1
pure $ RpcCall v i GetNewAccount (NameIdParams x y)
else pure $ RpcCall v i GetNewAccount BadParams
_anyOther -> pure $ RpcCall v i GetNewAccount BadParams
2024-08-30 20:14:48 +00:00
GetNewAddress -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a >= 2
then do
x <- parseJSON $ a V.! 0
y <- parseJSON $ a V.! 1
(sap, tr) <-
case a V.!? 2 of
Nothing -> return (False, False)
Just s -> do
s' <- parseJSON s
case s' of
("ExcludeSapling" :: String) -> do
case a V.!? 3 of
Nothing -> return (True, False)
Just t -> do
t' <- parseJSON t
return
(True, t' == ("ExcludeTransparent" :: String))
("ExcludeTransparent" :: String) -> do
case a V.!? 3 of
Nothing -> return (False, True)
Just t -> do
t' <- parseJSON t
return
(t' == ("ExcludeSapling" :: String), True)
_anyOther -> return (False, False)
pure $ RpcCall v i GetNewAddress (NewAddrParams x y sap tr)
else pure $ RpcCall v i GetNewAddress BadParams
_anyOther -> pure $ RpcCall v i GetNewAddress BadParams
2024-09-04 18:10:09 +00:00
GetOperationStatus -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ a V.! 0
case U.fromText x of
Just u -> do
pure $
RpcCall v i GetOperationStatus (OpParams $ ZenithUuid u)
Nothing -> pure $ RpcCall v i GetOperationStatus BadParams
else pure $ RpcCall v i GetOperationStatus BadParams
_anyOther -> pure $ RpcCall v i GetOperationStatus BadParams
2024-07-23 18:46:37 +00:00
type ZenithRPC
2024-07-24 21:13:13 +00:00
= "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody
2024-07-23 18:46:37 +00:00
'[ JSON]
2024-08-03 12:01:11 +00:00
RpcCall :> Post '[ JSON] ZenithResponse
2024-07-23 18:46:37 +00:00
2024-08-26 20:25:31 +00:00
data State = State
{ w_network :: !ZcashNet
, w_host :: !T.Text
, w_port :: !Int
, w_dbPath :: !T.Text
, w_build :: !T.Text
, w_startBlock :: !Int
}
zenithServer :: State -> Server ZenithRPC
zenithServer state = getinfo :<|> handleRPC
2024-07-23 18:46:37 +00:00
where
getinfo :: Handler Value
getinfo =
return $
object
[ "version" .= ("0.7.0.0-beta" :: String)
, "network" .= ("testnet" :: String)
]
2024-08-03 12:01:11 +00:00
handleRPC :: Bool -> RpcCall -> Handler ZenithResponse
2024-07-24 21:13:13 +00:00
handleRPC isAuth req =
2024-07-23 18:46:37 +00:00
case method req of
2024-07-24 21:03:49 +00:00
UnknownMethod ->
2024-08-03 12:01:11 +00:00
return $ ErrorResponse (callId req) (-32601) "Method not found"
2024-08-05 17:54:02 +00:00
ListWallets ->
case parameters req of
BlankParams -> do
2024-08-26 20:25:31 +00:00
pool <- liftIO $ runNoLoggingT $ initPool $ w_dbPath state
walList <- liftIO $ getWallets pool $ w_network state
if not (null walList)
then return $
WalletListResponse
(callId req)
(map toZcashWalletAPI walList)
else return $
ErrorResponse
(callId req)
(-32001)
"No wallets available. Please create one first"
2024-08-05 17:54:02 +00:00
_anyOther ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-08-06 18:38:00 +00:00
ListAccounts ->
case parameters req of
AccountsParams w -> do
2024-08-26 20:25:31 +00:00
let dbPath = w_dbPath state
2024-08-06 18:38:00 +00:00
pool <- liftIO $ runNoLoggingT $ initPool dbPath
2024-08-26 20:25:31 +00:00
wl <- liftIO $ walletExists pool w
case wl of
Just wl' -> do
accList <-
liftIO $ runNoLoggingT $ getAccounts pool (entityKey wl')
if not (null accList)
then return $
AccountListResponse
(callId req)
(map toZcashAccountAPI accList)
else return $
ErrorResponse
(callId req)
(-32002)
"No accounts available for this wallet. Please create one first"
Nothing ->
return $
ErrorResponse (callId req) (-32008) "Wallet does not exist."
2024-08-06 18:38:00 +00:00
_anyOther ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-08-07 15:21:04 +00:00
ListAddresses ->
case parameters req of
AddressesParams a -> do
2024-08-26 20:25:31 +00:00
let dbPath = w_dbPath state
2024-08-07 15:21:04 +00:00
pool <- liftIO $ runNoLoggingT $ initPool dbPath
addrList <-
liftIO $
runNoLoggingT $ getAddresses pool (toSqlKey $ fromIntegral a)
if not (null addrList)
then return $
AddressListResponse
(callId req)
(map toZcashAddressAPI addrList)
else return $
ErrorResponse
(callId req)
(-32003)
"No addresses available for this account. Please create one first"
_anyOther ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-07-23 18:46:37 +00:00
GetInfo ->
case parameters req of
2024-08-26 20:25:31 +00:00
BlankParams ->
return $
InfoResponse
(callId req)
(ZenithInfo "0.7.0.0-beta" (w_network state) (w_build state))
2024-07-23 18:46:37 +00:00
_anyOtherParams ->
2024-08-03 12:01:11 +00:00
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-08-10 12:04:40 +00:00
ListReceived ->
case parameters req of
2024-08-12 20:35:00 +00:00
NotesParams x -> do
case (readMaybe (T.unpack x) :: Maybe Int64) of
Just x' -> do
2024-08-26 20:25:31 +00:00
let dbPath = w_dbPath state
2024-08-12 20:35:00 +00:00
pool <- liftIO $ runNoLoggingT $ initPool dbPath
a <- liftIO $ getAddressById pool $ toSqlKey x'
case a of
Just a' -> do
nList <- liftIO $ getWalletNotes pool a'
return $ NoteListResponse (callId req) nList
Nothing ->
return $
ErrorResponse
(callId req)
(-32004)
"Address does not belong to the wallet"
2024-08-15 16:17:24 +00:00
Nothing ->
case parseAddress (E.encodeUtf8 x) of
Nothing ->
return $
ErrorResponse
(callId req)
(-32005)
"Unable to parse address"
Just x' -> do
2024-08-26 20:25:31 +00:00
let dbPath = w_dbPath state
2024-08-15 16:17:24 +00:00
pool <- liftIO $ runNoLoggingT $ initPool dbPath
addrs <- liftIO $ getExternalAddresses pool
nList <-
liftIO $
concat <$> mapM (findNotesByAddress pool x') addrs
return $ NoteListResponse (callId req) nList
2024-08-10 12:04:40 +00:00
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-08-16 18:31:25 +00:00
GetBalance ->
case parameters req of
BalanceParams i -> do
2024-08-26 20:25:31 +00:00
let dbPath = w_dbPath state
2024-08-16 18:31:25 +00:00
pool <- liftIO $ runNoLoggingT $ initPool dbPath
acc <- liftIO $ getAccountById pool $ toSqlKey i
case acc of
Just acc' -> do
c <- liftIO $ getPoolBalance pool $ entityKey acc'
u <- liftIO $ getUnconfPoolBalance pool $ entityKey acc'
return $ BalanceResponse (callId req) c u
Nothing ->
return $
ErrorResponse (callId req) (-32006) "Account does not exist."
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-08-24 12:45:42 +00:00
GetNewWallet ->
case parameters req of
NameParams t -> do
2024-08-26 20:25:31 +00:00
let dbPath = w_dbPath state
2024-08-24 12:45:42 +00:00
sP <- liftIO generateWalletSeedPhrase
pool <- liftIO $ runNoLoggingT $ initPool dbPath
2024-08-26 20:25:31 +00:00
r <-
liftIO $
saveWallet pool $
ZcashWallet
t
(ZcashNetDB $ w_network state)
(PhraseDB sP)
(w_startBlock state)
0
case r of
Nothing ->
2024-08-24 12:45:42 +00:00
return $
2024-08-26 20:25:31 +00:00
ErrorResponse
(callId req)
(-32007)
"Entity with that name already exists."
Just r' ->
return $
NewItemResponse (callId req) $ fromSqlKey $ entityKey r'
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
GetNewAccount ->
case parameters req of
NameIdParams t i -> do
let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath
w <- liftIO $ walletExists pool i
case w of
Just w' -> do
aIdx <- liftIO $ getMaxAccount pool $ entityKey w'
nAcc <-
liftIO
(try $ createZcashAccount t (aIdx + 1) w' :: IO
(Either IOError ZcashAccount))
case nAcc of
Left e ->
2024-08-24 12:45:42 +00:00
return $
2024-08-30 20:14:48 +00:00
ErrorResponse (callId req) (-32010) $ T.pack $ show e
2024-08-26 20:25:31 +00:00
Right nAcc' -> do
r <- liftIO $ saveAccount pool nAcc'
case r of
Nothing ->
return $
ErrorResponse
(callId req)
(-32007)
"Entity with that name already exists."
Just x ->
return $
NewItemResponse (callId req) $
fromSqlKey $ entityKey x
Nothing ->
return $
2024-08-30 20:14:48 +00:00
ErrorResponse (callId req) (-32008) "Wallet does not exist."
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
GetNewAddress ->
case parameters req of
NewAddrParams i n s t -> do
let dbPath = w_dbPath state
let net = w_network state
pool <- liftIO $ runNoLoggingT $ initPool dbPath
acc <- liftIO $ getAccountById pool $ toSqlKey $ fromIntegral i
case acc of
Just acc' -> do
maxAddr <-
liftIO $ getMaxAddress pool (entityKey acc') External
newAddr <-
liftIO $
createCustomWalletAddress
n
(maxAddr + 1)
net
External
acc'
s
t
dbAddr <- liftIO $ saveAddress pool newAddr
case dbAddr of
Just nAddr -> do
return $
NewAddrResponse (callId req) (toZcashAddressAPI nAddr)
Nothing ->
return $
ErrorResponse
(callId req)
(-32007)
"Entity with that name already exists."
Nothing ->
return $
ErrorResponse (callId req) (-32006) "Account does not exist."
2024-08-24 12:45:42 +00:00
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-09-04 18:10:09 +00:00
GetOperationStatus ->
case parameters req of
OpParams u -> do
let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath
op <- liftIO $ getOperation pool $ getUuid u
case op of
Just o -> do
return $ OpResponse (callId req) $ entityVal o
Nothing ->
return $
ErrorResponse (callId req) (-32009) "Operation ID not found"
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
2024-07-24 21:03:49 +00:00
authenticate :: Config -> BasicAuthCheck Bool
authenticate config = BasicAuthCheck check
where
check (BasicAuthData username password) =
if username == c_zenithUser config && password == c_zenithPwd config
then return $ Authorized True
else return Unauthorized
2024-08-10 12:04:40 +00:00
packRpcResponse :: ToJSON a => T.Text -> a -> Value
packRpcResponse i x =
object ["jsonrpc" .= ("2.0" :: String), "id" .= i, "result" .= x]