Compare commits

..

No commits in common. "82e4c576c2141fb35cf05e5b83921005b20fbc49" and "efdb97a685f28cb087e179af25b595b5fd0b0c90" have entirely different histories.

6 changed files with 7 additions and 283 deletions

View file

@ -5,16 +5,6 @@ All notable changes to this project will be documented in this file.
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).
## [0.8.0.0-beta]
### Added
- RPC methods:
- `shieldnotes`
- `deshieldfunds`
- `getfullvk`
- `getincomingvk`
## [0.7.2.0-beta]
### Fixed

View file

@ -831,7 +831,7 @@ shieldTransparentNotes pool zHost zPort znet za bh = do
prepTSpends
(getTranSK $ zcashAccountTPrivateKey $ entityVal acc)
trNotes
chgAddr <- liftIO $ getInternalAddresses pool $ entityKey acc
chgAddr <- getInternalAddresses pool $ entityKey acc
let internalUA =
getUA $ walletAddressUAddress $ entityVal $ head chgAddr
let oRcvr =

View file

@ -13,10 +13,10 @@
module Zenith.RPC where
import Control.Concurrent (forkIO)
import Control.Exception (SomeException(..), try)
import Control.Monad (unless)
import Control.Exception (try)
import Control.Monad (unless, when)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Logger (runNoLoggingT, runStderrLoggingT)
import Control.Monad.Logger (runFileLoggingT, runNoLoggingT, runStderrLoggingT)
import Data.Aeson
import qualified Data.HexString as H
import Data.Int
@ -36,7 +36,7 @@ import Database.Esqueleto.Experimental
)
import Servant
import Text.Read (readMaybe)
import ZcashHaskell.Keys (deriveUfvk, deriveUivk, generateWalletSeedPhrase)
import ZcashHaskell.Keys (generateWalletSeedPhrase)
import ZcashHaskell.Orchard (parseAddress)
import ZcashHaskell.Types
( BlockResponse(..)
@ -98,12 +98,9 @@ import Zenith.Types
( AccountBalance(..)
, Config(..)
, HexStringDB(..)
, OrchardSpendingKeyDB(..)
, PhraseDB(..)
, PrivacyPolicy(..)
, ProposedNote(..)
, SaplingSpendingKeyDB(..)
, TransparentSpendingKeyDB(..)
, ZcashAccountAPI(..)
, ZcashAddressAPI(..)
, ZcashNetDB(..)
@ -128,8 +125,6 @@ data ZenithMethod
| SendMany
| ShieldNotes
| DeshieldFunds
| GetFVK
| GetIVK
| UnknownMethod
deriving (Eq, Prelude.Show)
@ -147,8 +142,6 @@ instance ToJSON ZenithMethod where
toJSON SendMany = Data.Aeson.String "sendmany"
toJSON ShieldNotes = Data.Aeson.String "shieldnotes"
toJSON DeshieldFunds = Data.Aeson.String "deshieldfunds"
toJSON GetFVK = Data.Aeson.String "getfullvk"
toJSON GetIVK = Data.Aeson.String "getincomingvk"
toJSON UnknownMethod = Data.Aeson.Null
instance FromJSON ZenithMethod where
@ -167,8 +160,6 @@ instance FromJSON ZenithMethod where
"sendmany" -> pure SendMany
"shieldnotes" -> pure ShieldNotes
"deshieldfunds" -> pure DeshieldFunds
"getfullvk" -> pure GetFVK
"getincomingvk" -> pure GetIVK
_ -> pure UnknownMethod
data ZenithParams
@ -186,7 +177,6 @@ data ZenithParams
| TestParams !T.Text
| ShieldNotesParams !Int
| DeshieldParams !Int !Scientific
| ViewingKeyParams !Int
deriving (Eq, Prelude.Show)
instance ToJSON ZenithParams where
@ -214,7 +204,6 @@ instance ToJSON ZenithParams where
toJSON (ShieldNotesParams i) = Data.Aeson.Array $ V.fromList [jsonNumber i]
toJSON (DeshieldParams i s) =
Data.Aeson.Array $ V.fromList [jsonNumber i, Data.Aeson.Number s]
toJSON (ViewingKeyParams i) = Data.Aeson.Array $ V.fromList [jsonNumber i]
data ZenithResponse
= InfoResponse !T.Text !ZenithInfo
@ -228,7 +217,6 @@ data ZenithResponse
| OpResponse !T.Text !Operation
| SendResponse !T.Text !U.UUID
| MultiOpResponse !T.Text ![T.Text]
| ViewingKeyResponse !T.Text !T.Text
| ErrorResponse !T.Text !Double !T.Text
deriving (Eq, Prelude.Show)
@ -251,7 +239,6 @@ instance ToJSON ZenithResponse where
toJSON (OpResponse i u) = packRpcResponse i u
toJSON (SendResponse i o) = packRpcResponse i o
toJSON (MultiOpResponse i o) = packRpcResponse i o
toJSON (ViewingKeyResponse i k) = packRpcResponse i k
instance FromJSON ZenithResponse where
parseJSON =
@ -336,7 +323,7 @@ instance FromJSON ZenithResponse where
Right k' -> pure $ NewItemResponse i k'
String s -> do
case U.fromText s of
Nothing -> pure $ ViewingKeyResponse i s
Nothing -> fail "Unknown value"
Just u -> pure $ SendResponse i u
_anyOther -> fail "Malformed JSON"
Just e1 -> pure $ ErrorResponse i (ecode e1) (emessage e1)
@ -541,26 +528,6 @@ instance FromJSON RpcCall where
pure $ RpcCall v i DeshieldFunds (DeshieldParams x y)
else pure $ RpcCall v i DeshieldFunds BadParams
_anyOther -> pure $ RpcCall v i DeshieldFunds BadParams
GetFVK -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ a V.! 0
pure $ RpcCall v i GetFVK (ViewingKeyParams x)
else pure $ RpcCall v i GetFVK BadParams
_anyOther -> pure $ RpcCall v i GetFVK BadParams
GetIVK -> do
p <- obj .: "params"
case p of
Array a ->
if V.length a == 1
then do
x <- parseJSON $ a V.! 0
pure $ RpcCall v i GetIVK (ViewingKeyParams x)
else pure $ RpcCall v i GetIVK BadParams
_anyOther -> pure $ RpcCall v i GetIVK BadParams
type ZenithRPC
= "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody
@ -1074,62 +1041,6 @@ zenithServer state = getinfo :<|> handleRPC
"Account does not exist."
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
GetFVK -> do
case parameters req of
ViewingKeyParams aid -> do
let dbPath = w_dbPath state
let net = w_network state
pool <- liftIO $ runNoLoggingT $ initPool dbPath
acc <- liftIO $ getAccountById pool $ toSqlKey $ fromIntegral aid
case acc of
Just acc' -> do
fvk <-
liftIO $
try
(deriveUfvk
net
(getOrchSK $ zcashAccountOrchSpendKey $ entityVal acc')
(getSapSK $ zcashAccountSapSpendKey $ entityVal acc')
(getTranSK $ zcashAccountTPrivateKey $ entityVal acc')) :: Handler
(Either SomeException T.Text)
case fvk of
Left _ ->
return $
ErrorResponse (callId req) (-32010) "Internal Error"
Right fvk' -> return $ ViewingKeyResponse (callId req) fvk'
Nothing ->
return $
ErrorResponse (callId req) (-32006) "Account does not exist."
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
GetIVK -> do
case parameters req of
ViewingKeyParams aid -> do
let dbPath = w_dbPath state
let net = w_network state
pool <- liftIO $ runNoLoggingT $ initPool dbPath
acc <- liftIO $ getAccountById pool $ toSqlKey $ fromIntegral aid
case acc of
Just acc' -> do
ivk <-
liftIO $
try
(deriveUivk
net
(getOrchSK $ zcashAccountOrchSpendKey $ entityVal acc')
(getSapSK $ zcashAccountSapSpendKey $ entityVal acc')
(getTranSK $ zcashAccountTPrivateKey $ entityVal acc')) :: Handler
(Either SomeException T.Text)
case ivk of
Left _ ->
return $
ErrorResponse (callId req) (-32010) "Internal Error"
Right ivk' -> return $ ViewingKeyResponse (callId req) ivk'
Nothing ->
return $
ErrorResponse (callId req) (-32006) "Account does not exist."
_anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params"
authenticate :: Config -> BasicAuthCheck Bool
authenticate config = BasicAuthCheck check

View file

@ -724,105 +724,6 @@ main = do
case res of
Left e -> assertFailure e
Right (MultiOpResponse i c) -> c `shouldNotBe` []
describe "Viewing Keys" $ do
describe "Full" $ do
it "bad credentials" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
"baduser"
"idontknow"
GetFVK
BlankParams
res `shouldBe` Left "Invalid credentials"
describe "correct credentials" $ do
it "no parameters" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
nodeUser
nodePwd
GetFVK
BlankParams
case res of
Left e -> assertFailure e
Right (ErrorResponse i c m) -> c `shouldBe` (-32602)
it "invalid account" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
nodeUser
nodePwd
GetFVK
(ViewingKeyParams 27)
case res of
Left e -> assertFailure e
Right (ErrorResponse i c m) -> c `shouldBe` (-32006)
it "valid account" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
nodeUser
nodePwd
GetFVK
(ViewingKeyParams 1)
case res of
Left e -> assertFailure e
Right (ViewingKeyResponse i c) -> c `shouldNotBe` ""
Right x -> assertFailure $ show x
describe "Incoming" $ do
it "bad credentials" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
"baduser"
"idontknow"
GetIVK
BlankParams
res `shouldBe` Left "Invalid credentials"
describe "correct credentials" $ do
it "no parameters" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
nodeUser
nodePwd
GetIVK
BlankParams
case res of
Left e -> assertFailure e
Right (ErrorResponse i c m) -> c `shouldBe` (-32602)
it "invalid account" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
nodeUser
nodePwd
GetIVK
(ViewingKeyParams 27)
case res of
Left e -> assertFailure e
Right (ErrorResponse i c m) -> c `shouldBe` (-32006)
it "valid account" $ do
res <-
makeZenithCall
"127.0.0.1"
nodePort
nodeUser
nodePwd
GetIVK
(ViewingKeyParams 1)
case res of
Left e -> assertFailure e
Right (ViewingKeyResponse i c) -> c `shouldNotBe` ""
Right x -> assertFailure $ show x
startAPI :: Config -> IO ()
startAPI config = do

View file

@ -791,80 +791,6 @@
{ "$ref": "#/components/errors/ZenithBusy" },
{ "$ref": "#/components/errors/InvalidAccount" }
]
},
{
"name": "getfullvk",
"summary": "Derive the full viewing key for the given account.",
"description": "Derive the full viewing key for the given account, encoded per ZIP-316.",
"tags": [],
"params": [
{ "$ref": "#/components/contentDescriptors/AccountId"}
],
"paramStructure": "by-position",
"result": {
"name": "Full viewing key",
"schema": {
"$ref": "#/components/schemas/ViewingKey"
}
},
"examples": [
{
"name": "Get full viewing key",
"summary": "Get the full viewing key",
"description": "Get the full viewing key for the give account, encoded per ZIP-316",
"params": [
{
"name": "Account index",
"summary": "The index for the account to use",
"value": 1
}
],
"result": {
"name": "Full Viewing key",
"value": "uview16qdhd9e283s4y53gmw72ag7adzdrj9f9v96dw89ggv9el0yrf7vkappau69j8luq7uf540sr78ncslnqk6kwpc4qeqgfg5vn4xcmllynyfr32cgq6nx5ptku44kfxtsj99px2g9yp7kyc32quun0elakgltqmqflprwmryuelcfwwt58vqap065as7qwljg02l6mkutsh2y9aefd284dsrj0246fd2n4hra3r03uftsh4njh3w590z78tpnfqhjvvwhgus476zrw3fd69qekru709ghr0zr7h8majy9aclwg7uhakt24lmuec8dd7t270kamcs99rz8jasj3jl6m9y77dvkdn23e2kwuc6kyagpstzrdjnlzdldmgsu4k056v80ucajcjvl99pcf2znjg37vztdp4zr5qrphxs4y7wppxmankmdwwgjxhlmyrjd68z80q0n0t2cyqge6mlc7pd5wre4392pjtdaqvtyeg0denh4ekynnjxnm"
}
}
],
"errors": [
{ "$ref": "#/components/errors/InvalidAccount" }
]
},
{
"name": "getincomingvk",
"summary": "Get the incoming viewing key for the given account.",
"description": "Derives the incoming viewing key for the given account per ZIP-316.",
"tags": [],
"params": [
{ "$ref": "#/components/contentDescriptors/AccountId"}
],
"paramStructure": "by-position",
"result": {
"name": "Incoming viewing key",
"schema": {
"$ref": "#/components/schemas/ViewingKey"
}
},
"examples": [
{
"name": "Get incoming viewing key",
"summary": "Get the incoming viewing key",
"description": "Get the incoming viewing key for the give account, encoded per ZIP-316",
"params": [
{
"name": "Account index",
"summary": "The index for the account to use",
"value": 1
}
],
"result": {
"name": "Incoming Viewing key",
"value": "uivk199qcjxrj73n7fapg79a2ltah6f3j83haljcux5t5kvn5unn7rpfmvglttdt9g6na3llkefnd3pn0x9ky6lh8s42trj0vfg5wtv0nrerq0wsq5v4q7lt5j4l9svppspr6h7407ztgsuvkfk977c3tj408nx5phxap8fn3ecdmdrah9spp76md9tel89tuqz6m0xplqp83wj33qf7s3hwfe79t04rq49g24nr3emlpm298wpqla2dvh4rr584kwdtxc9ahse5x0drcjr95tt4k0hxr32l6yturje7dptlgjnr4cm6uk29ysu9l5xwgz40p6alyedzzqltqf5nswy48ekru4ahapw"
}
}
],
"errors": [
{ "$ref": "#/components/errors/InvalidAccount" }
]
}
],
"components": {
@ -1040,10 +966,6 @@
"amount": { "type": "number", "description": "The amount to send in ZEC"},
"memo": { "type": "string", "description": "The shielded memo to include, if applicable"}
}
},
"ViewingKey": {
"type": "string",
"description": "The viewing key, encoded per ZIP-316"
}
},
"examples": {},

View file

@ -1,6 +1,6 @@
cabal-version: 3.0
name: zenith
version: 0.8.0.0-beta
version: 0.7.2.0-beta
license: MIT
license-file: LICENSE
author: Rene Vergara