diff --git a/CHANGELOG.md b/CHANGELOG.md index 091e91c..8d6dc03 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -17,6 +17,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0 - `listreceived` RPC method - `getbalance` RPC method - `getnewwallet` RPC method +- `getnewaccount` RPC method ### Changed diff --git a/app/Server.hs b/app/Server.hs index af5bf4a..ea64684 100644 --- a/app/Server.hs +++ b/app/Server.hs @@ -10,7 +10,7 @@ import Servant import ZcashHaskell.Types (ZebraGetBlockChainInfo(..), ZebraGetInfo(..)) import Zenith.Core (checkBlockChain, checkZebra) import Zenith.DB (initDb) -import Zenith.RPC (ZenithRPC(..), authenticate, zenithServer) +import Zenith.RPC (State(..), ZenithRPC(..), authenticate, zenithServer) import Zenith.Scanner (rescanZebra) import Zenith.Types (Config(..)) @@ -39,8 +39,16 @@ main = do Left e2 -> throwIO $ userError e2 Right x' -> do when x' $ rescanZebra zebraHost zebraPort dbFilePath + let myState = + State + (zgb_net chainInfo) + zebraHost + zebraPort + dbFilePath + (zgi_build zebra) + (zgb_blocks chainInfo) run nodePort $ serveWithContext (Proxy :: Proxy ZenithRPC) ctx - (zenithServer myConfig) + (zenithServer myState) diff --git a/src/Zenith/DB.hs b/src/Zenith/DB.hs index 129a958..45399dc 100644 --- a/src/Zenith/DB.hs +++ b/src/Zenith/DB.hs @@ -451,6 +451,16 @@ getWallets pool n = where_ (wallets ^. ZcashWalletNetwork ==. val (ZcashNetDB n)) pure wallets +walletExists :: ConnectionPool -> Int -> IO (Maybe (Entity ZcashWallet)) +walletExists pool n = + runNoLoggingT $ + PS.retryOnBusy $ + flip PS.runSqlPool pool $ do + selectOne $ do + wallets <- from $ table @ZcashWallet + where_ (wallets ^. ZcashWalletId ==. val (toSqlKey $ fromIntegral n)) + pure wallets + getNetwork :: ConnectionPool -> WalletAddressId -> IO ZcashNet getNetwork pool a = do n <- diff --git a/src/Zenith/RPC.hs b/src/Zenith/RPC.hs index b1e4ff1..e80d76e 100644 --- a/src/Zenith/RPC.hs +++ b/src/Zenith/RPC.hs @@ -25,30 +25,29 @@ import Servant import Text.Read (readMaybe) import ZcashHaskell.Keys (generateWalletSeedPhrase) import ZcashHaskell.Orchard (parseAddress) -import ZcashHaskell.Types - ( RpcError(..) - , ZcashNet(..) - , ZebraGetBlockChainInfo(..) - , ZebraGetInfo(..) - ) -import Zenith.Core (checkBlockChain, checkZebra) +import ZcashHaskell.Types (RpcError(..), ZcashNet(..)) +import Zenith.Core (createZcashAccount) import Zenith.DB - ( ZcashWallet(..) + ( ZcashAccount(..) + , ZcashWallet(..) , findNotesByAddress , getAccountById , getAccounts , getAddressById , getAddresses , getExternalAddresses + , getMaxAccount , getPoolBalance , getUnconfPoolBalance , getWalletNotes , getWallets , initPool + , saveAccount , saveWallet , toZcashAccountAPI , toZcashAddressAPI , toZcashWalletAPI + , walletExists ) import Zenith.Types ( AccountBalance(..) @@ -70,6 +69,7 @@ data ZenithMethod | ListReceived | GetBalance | GetNewWallet + | GetNewAccount | UnknownMethod deriving (Eq, Prelude.Show) @@ -81,6 +81,7 @@ instance ToJSON ZenithMethod where toJSON ListReceived = Data.Aeson.String "listreceived" toJSON GetBalance = Data.Aeson.String "getbalance" toJSON GetNewWallet = Data.Aeson.String "getnewwallet" + toJSON GetNewAccount = Data.Aeson.String "getnewaccount" toJSON UnknownMethod = Data.Aeson.Null instance FromJSON ZenithMethod where @@ -93,6 +94,7 @@ instance FromJSON ZenithMethod where "listreceived" -> pure ListReceived "getbalance" -> pure GetBalance "getnewwallet" -> pure GetNewWallet + "getnewaccount" -> pure GetNewAccount _ -> pure UnknownMethod data ZenithParams @@ -103,6 +105,7 @@ data ZenithParams | NotesParams !T.Text | BalanceParams !Int64 | NameParams !T.Text + | NameIdParams !T.Text !Int | TestParams !T.Text deriving (Eq, Prelude.Show) @@ -114,6 +117,8 @@ instance ToJSON ZenithParams where toJSON (TestParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t] toJSON (NotesParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t] toJSON (NameParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t] + toJSON (NameIdParams t i) = + Data.Aeson.Array $ V.fromList [Data.Aeson.String t, jsonNumber i] toJSON (BalanceParams n) = Data.Aeson.Array $ V.fromList [jsonNumber $ fromIntegral n] @@ -311,14 +316,34 @@ instance FromJSON RpcCall where pure $ RpcCall v i GetNewWallet (NameParams x) else pure $ RpcCall v i GetNewWallet BadParams _anyOther -> pure $ RpcCall v i GetNewWallet BadParams + 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 type ZenithRPC = "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody '[ JSON] RpcCall :> Post '[ JSON] ZenithResponse -zenithServer :: Config -> Server ZenithRPC -zenithServer config = getinfo :<|> handleRPC +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 where getinfo :: Handler Value getinfo = @@ -335,55 +360,49 @@ zenithServer config = getinfo :<|> handleRPC ListWallets -> case parameters req of BlankParams -> do - let dbPath = c_dbPath config - let host = c_zebraHost config - let port = c_zebraPort config - bc <- - liftIO $ try $ checkBlockChain host port :: Handler - (Either IOError ZebraGetBlockChainInfo) - case bc of - Left _e1 -> - return $ - ErrorResponse (callId req) (-32000) "Zebra not available" - Right chainInfo -> do - pool <- liftIO $ runNoLoggingT $ initPool dbPath - walList <- liftIO $ getWallets pool $ zgb_net chainInfo - 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" + 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" _anyOther -> return $ ErrorResponse (callId req) (-32602) "Invalid params" ListAccounts -> case parameters req of AccountsParams w -> do - let dbPath = c_dbPath config + let dbPath = w_dbPath state pool <- liftIO $ runNoLoggingT $ initPool dbPath - accList <- - liftIO $ - runNoLoggingT $ getAccounts pool (toSqlKey $ fromIntegral w) - 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" + 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." _anyOther -> return $ ErrorResponse (callId req) (-32602) "Invalid params" ListAddresses -> case parameters req of AddressesParams a -> do - let dbPath = c_dbPath config + let dbPath = w_dbPath state pool <- liftIO $ runNoLoggingT $ initPool dbPath addrList <- liftIO $ @@ -402,29 +421,11 @@ zenithServer config = getinfo :<|> handleRPC return $ ErrorResponse (callId req) (-32602) "Invalid params" GetInfo -> case parameters req of - BlankParams -> do - let host = c_zebraHost config - let port = c_zebraPort config - zInfo <- - liftIO $ try $ checkZebra host port :: Handler - (Either IOError ZebraGetInfo) - case zInfo of - Left _e -> - return $ - ErrorResponse (callId req) (-32000) "Zebra not available" - Right zI -> do - bInfo <- - liftIO $ try $ checkBlockChain host port :: Handler - (Either IOError ZebraGetBlockChainInfo) - case bInfo of - Left _e1 -> - return $ - ErrorResponse (callId req) (-32000) "Zebra not available" - Right bI -> - return $ - InfoResponse - (callId req) - (ZenithInfo "0.7.0.0-beta" (zgb_net bI) (zgi_build zI)) + BlankParams -> + return $ + InfoResponse + (callId req) + (ZenithInfo "0.7.0.0-beta" (w_network state) (w_build state)) _anyOtherParams -> return $ ErrorResponse (callId req) (-32602) "Invalid params" ListReceived -> @@ -432,7 +433,7 @@ zenithServer config = getinfo :<|> handleRPC NotesParams x -> do case (readMaybe (T.unpack x) :: Maybe Int64) of Just x' -> do - let dbPath = c_dbPath config + let dbPath = w_dbPath state pool <- liftIO $ runNoLoggingT $ initPool dbPath a <- liftIO $ getAddressById pool $ toSqlKey x' case a of @@ -454,7 +455,7 @@ zenithServer config = getinfo :<|> handleRPC (-32005) "Unable to parse address" Just x' -> do - let dbPath = c_dbPath config + let dbPath = w_dbPath state pool <- liftIO $ runNoLoggingT $ initPool dbPath addrs <- liftIO $ getExternalAddresses pool nList <- @@ -466,7 +467,7 @@ zenithServer config = getinfo :<|> handleRPC GetBalance -> case parameters req of BalanceParams i -> do - let dbPath = c_dbPath config + let dbPath = w_dbPath state pool <- liftIO $ runNoLoggingT $ initPool dbPath acc <- liftIO $ getAccountById pool $ toSqlKey i case acc of @@ -482,38 +483,63 @@ zenithServer config = getinfo :<|> handleRPC GetNewWallet -> case parameters req of NameParams t -> do - let host = c_zebraHost config - let port = c_zebraPort config - let dbPath = c_dbPath config + let dbPath = w_dbPath state sP <- liftIO generateWalletSeedPhrase pool <- liftIO $ runNoLoggingT $ initPool dbPath - bInfo <- - liftIO $ try $ checkBlockChain host port :: Handler - (Either IOError ZebraGetBlockChainInfo) - case bInfo of - Left _e1 -> + r <- + liftIO $ + saveWallet pool $ + ZcashWallet + t + (ZcashNetDB $ w_network state) + (PhraseDB sP) + (w_startBlock state) + 0 + case r of + Nothing -> return $ - ErrorResponse (callId req) (-32000) "Zebra not available" - Right bI -> do - r <- - liftIO $ - saveWallet pool $ - ZcashWallet - t - (ZcashNetDB $ zgb_net bI) - (PhraseDB sP) - (zgb_blocks bI) - 0 - case r of - Nothing -> + 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 -> return $ - ErrorResponse - (callId req) - (-32007) - "Entity with that name already exists." - Just r' -> - return $ - NewItemResponse (callId req) $ fromSqlKey $ entityKey r' + ErrorResponse (callId req) (-32610) $ T.pack $ show e + 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 $ + ErrorResponse (callId req) (-32608) "Wallet does not exist." _anyOtherParams -> return $ ErrorResponse (callId req) (-32602) "Invalid params" diff --git a/test/ServerSpec.hs b/test/ServerSpec.hs index 5bafd43..18d74de 100644 --- a/test/ServerSpec.hs +++ b/test/ServerSpec.hs @@ -1,7 +1,7 @@ {-# LANGUAGE OverloadedStrings #-} import Control.Concurrent (forkIO, threadDelay) -import Control.Exception (SomeException, try) +import Control.Exception (SomeException, throwIO, try) import Control.Monad (when) import Data.Aeson import qualified Data.ByteString as BS @@ -12,12 +12,18 @@ import Network.HTTP.Simple import Network.Wai.Handler.Warp (run) import Servant import System.Directory -import Test.HUnit +import Test.HUnit hiding (State) import Test.Hspec -import ZcashHaskell.Types (ZcashNet(..)) +import ZcashHaskell.Types + ( ZcashNet(..) + , ZebraGetBlockChainInfo(..) + , ZebraGetInfo(..) + ) +import Zenith.Core (checkBlockChain, checkZebra) import Zenith.DB (initDb) import Zenith.RPC ( RpcCall(..) + , State(..) , ZenithInfo(..) , ZenithMethod(..) , ZenithParams(..) @@ -26,7 +32,7 @@ import Zenith.RPC , authenticate , zenithServer ) -import Zenith.Types (Config(..), ZcashWalletAPI(..)) +import Zenith.Types (Config(..), ZcashAccountAPI(..), ZcashWalletAPI(..)) main :: IO () main = do @@ -176,7 +182,95 @@ main = do ListAccounts BlankParams res `shouldBe` Left "Invalid credentials" - it "correct credentials, no accounts" $ do + describe "correct credentials" $ do + it "invalid wallet" $ do + res <- + makeZenithCall + "127.0.0.1" + nodePort + nodeUser + nodePwd + ListAccounts + (AccountsParams 17) + case res of + Left e -> assertFailure e + Right r -> + r `shouldBe` + ErrorResponse "zh" (-32008) "Wallet does not exist." + it "valid wallet, no accounts" $ do + res <- + makeZenithCall + "127.0.0.1" + nodePort + nodeUser + nodePwd + ListAccounts + (AccountsParams 1) + case res of + Left e -> assertFailure e + Right r -> + r `shouldBe` + ErrorResponse + "zh" + (-32002) + "No accounts available for this wallet. Please create one first" + describe "getnewaccount" $ do + it "invalid credentials" $ do + res <- + makeZenithCall + "127.0.0.1" + nodePort + "baduser" + "idontknow" + GetNewAccount + BlankParams + res `shouldBe` Left "Invalid credentials" + describe "correct credentials" $ do + it "invalid wallet" $ do + res <- + makeZenithCall + "127.0.0.1" + nodePort + nodeUser + nodePwd + GetNewAccount + (NameIdParams "Personal" 17) + case res of + Left e -> assertFailure e + Right r -> + r `shouldBe` + ErrorResponse "zh" (-32608) "Wallet does not exist." + it "valid wallet" $ do + res <- + makeZenithCall + "127.0.0.1" + nodePort + nodeUser + nodePwd + GetNewAccount + (NameIdParams "Personal" 1) + case res of + Left e -> assertFailure e + Right r -> r `shouldBe` NewItemResponse "zh" 1 + it "valid wallet, duplicate name" $ do + res <- + makeZenithCall + "127.0.0.1" + nodePort + nodeUser + nodePwd + GetNewAccount + (NameIdParams "Personal" 1) + case res of + Left e -> assertFailure e + Right r -> + r `shouldBe` + ErrorResponse + "zh" + (-32007) + "Entity with that name already exists." + describe "listaccounts" $ do + it "valid wallet" $ do res <- makeZenithCall "127.0.0.1" @@ -189,10 +283,7 @@ main = do Left e -> assertFailure e Right r -> r `shouldBe` - ErrorResponse - "zh" - (-32002) - "No accounts available for this wallet. Please create one first" + AccountListResponse "zh" [ZcashAccountAPI 1 1 "Personal"] describe "Addresses" $ do describe "listaddresses" $ do it "bad credentials" $ do @@ -302,16 +393,38 @@ startAPI config = do putStrLn "Starting test RPC server" checkDbFile <- doesFileExist "test.db" when checkDbFile $ removeFile "test.db" - _ <- initDb "test.db" let ctx = authenticate config :. EmptyContext - forkIO $ - run (c_zenithPort config) $ - serveWithContext - (Servant.Proxy :: Servant.Proxy ZenithRPC) - ctx - (zenithServer config) - threadDelay 1000000 - putStrLn "Test server is up!" + w <- + try $ checkZebra (c_zebraHost config) (c_zebraPort config) :: IO + (Either IOError ZebraGetInfo) + case w of + Right zebra -> do + bc <- + try $ checkBlockChain (c_zebraHost config) (c_zebraPort config) :: IO + (Either IOError ZebraGetBlockChainInfo) + case bc of + Left e1 -> throwIO e1 + Right chainInfo -> do + x <- initDb "test.db" + case x of + Left e2 -> throwIO $ userError e2 + Right x' -> do + let myState = + State + (zgb_net chainInfo) + (c_zebraHost config) + (c_zebraPort config) + "test.db" + (zgi_build zebra) + (zgb_blocks chainInfo) + forkIO $ + run (c_zenithPort config) $ + serveWithContext + (Servant.Proxy :: Servant.Proxy ZenithRPC) + ctx + (zenithServer myState) + threadDelay 1000000 + putStrLn "Test server is up!" -- | Make a Zebra RPC call makeZenithCall :: diff --git a/zenith-openrpc.json b/zenith-openrpc.json index 7adc277..0f66324 100644 --- a/zenith-openrpc.json +++ b/zenith-openrpc.json @@ -190,7 +190,7 @@ "name": "getnewaccount", "summary": "Create a new account", "description": "Create a new account in the given wallet.", - "tags": [{"$ref": "#/components/tags/draft"}, {"$ref": "#/components/tags/wip"}], + "tags": [], "params": [ { "$ref": "#/components/contentDescriptors/Name"}, { "$ref": "#/components/contentDescriptors/WalletId"} @@ -212,6 +212,11 @@ "name": "Account name", "summary": "The user-friendly name for the Account", "value": "Personal" + }, + { + "name": "Wallet Id", + "summary": "The internal index of the Wallet to use", + "value": 1 } ], "result": { @@ -222,7 +227,8 @@ ], "errors": [ { "$ref": "#/components/errors/ZebraNotAvailable" }, - { "$ref": "#/components/errors/DuplicateName" } + { "$ref": "#/components/errors/DuplicateName" }, + { "$ref": "#/components/errors/InvalidWallet" } ] }, { @@ -604,6 +610,10 @@ "InvalidWallet": { "code": -32008, "message": "Wallet does not exist." + }, + "InternalError": { + "code": -32010, + "message": "Varies" } } } diff --git a/zenith.cabal b/zenith.cabal index d192ba1..07fac93 100644 --- a/zenith.cabal +++ b/zenith.cabal @@ -67,6 +67,7 @@ library , microlens-mtl , microlens-th , monad-logger + , transformers , monomer , mtl , persistent