Implement getnewaccount

This commit is contained in:
Rene Vergara 2024-08-26 15:25:31 -05:00
parent 35ab075703
commit fae0def6a8
Signed by: pitmutt
GPG key ID: 65122AD495A7F5B2
7 changed files with 293 additions and 124 deletions

View file

@ -17,6 +17,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- `listreceived` RPC method - `listreceived` RPC method
- `getbalance` RPC method - `getbalance` RPC method
- `getnewwallet` RPC method - `getnewwallet` RPC method
- `getnewaccount` RPC method
### Changed ### Changed

View file

@ -10,7 +10,7 @@ import Servant
import ZcashHaskell.Types (ZebraGetBlockChainInfo(..), ZebraGetInfo(..)) import ZcashHaskell.Types (ZebraGetBlockChainInfo(..), ZebraGetInfo(..))
import Zenith.Core (checkBlockChain, checkZebra) import Zenith.Core (checkBlockChain, checkZebra)
import Zenith.DB (initDb) import Zenith.DB (initDb)
import Zenith.RPC (ZenithRPC(..), authenticate, zenithServer) import Zenith.RPC (State(..), ZenithRPC(..), authenticate, zenithServer)
import Zenith.Scanner (rescanZebra) import Zenith.Scanner (rescanZebra)
import Zenith.Types (Config(..)) import Zenith.Types (Config(..))
@ -39,8 +39,16 @@ main = do
Left e2 -> throwIO $ userError e2 Left e2 -> throwIO $ userError e2
Right x' -> do Right x' -> do
when x' $ rescanZebra zebraHost zebraPort dbFilePath when x' $ rescanZebra zebraHost zebraPort dbFilePath
let myState =
State
(zgb_net chainInfo)
zebraHost
zebraPort
dbFilePath
(zgi_build zebra)
(zgb_blocks chainInfo)
run nodePort $ run nodePort $
serveWithContext serveWithContext
(Proxy :: Proxy ZenithRPC) (Proxy :: Proxy ZenithRPC)
ctx ctx
(zenithServer myConfig) (zenithServer myState)

View file

@ -451,6 +451,16 @@ getWallets pool n =
where_ (wallets ^. ZcashWalletNetwork ==. val (ZcashNetDB n)) where_ (wallets ^. ZcashWalletNetwork ==. val (ZcashNetDB n))
pure wallets 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 :: ConnectionPool -> WalletAddressId -> IO ZcashNet
getNetwork pool a = do getNetwork pool a = do
n <- n <-

View file

@ -25,30 +25,29 @@ import Servant
import Text.Read (readMaybe) import Text.Read (readMaybe)
import ZcashHaskell.Keys (generateWalletSeedPhrase) import ZcashHaskell.Keys (generateWalletSeedPhrase)
import ZcashHaskell.Orchard (parseAddress) import ZcashHaskell.Orchard (parseAddress)
import ZcashHaskell.Types import ZcashHaskell.Types (RpcError(..), ZcashNet(..))
( RpcError(..) import Zenith.Core (createZcashAccount)
, ZcashNet(..)
, ZebraGetBlockChainInfo(..)
, ZebraGetInfo(..)
)
import Zenith.Core (checkBlockChain, checkZebra)
import Zenith.DB import Zenith.DB
( ZcashWallet(..) ( ZcashAccount(..)
, ZcashWallet(..)
, findNotesByAddress , findNotesByAddress
, getAccountById , getAccountById
, getAccounts , getAccounts
, getAddressById , getAddressById
, getAddresses , getAddresses
, getExternalAddresses , getExternalAddresses
, getMaxAccount
, getPoolBalance , getPoolBalance
, getUnconfPoolBalance , getUnconfPoolBalance
, getWalletNotes , getWalletNotes
, getWallets , getWallets
, initPool , initPool
, saveAccount
, saveWallet , saveWallet
, toZcashAccountAPI , toZcashAccountAPI
, toZcashAddressAPI , toZcashAddressAPI
, toZcashWalletAPI , toZcashWalletAPI
, walletExists
) )
import Zenith.Types import Zenith.Types
( AccountBalance(..) ( AccountBalance(..)
@ -70,6 +69,7 @@ data ZenithMethod
| ListReceived | ListReceived
| GetBalance | GetBalance
| GetNewWallet | GetNewWallet
| GetNewAccount
| UnknownMethod | UnknownMethod
deriving (Eq, Prelude.Show) deriving (Eq, Prelude.Show)
@ -81,6 +81,7 @@ instance ToJSON ZenithMethod where
toJSON ListReceived = Data.Aeson.String "listreceived" toJSON ListReceived = Data.Aeson.String "listreceived"
toJSON GetBalance = Data.Aeson.String "getbalance" toJSON GetBalance = Data.Aeson.String "getbalance"
toJSON GetNewWallet = Data.Aeson.String "getnewwallet" toJSON GetNewWallet = Data.Aeson.String "getnewwallet"
toJSON GetNewAccount = Data.Aeson.String "getnewaccount"
toJSON UnknownMethod = Data.Aeson.Null toJSON UnknownMethod = Data.Aeson.Null
instance FromJSON ZenithMethod where instance FromJSON ZenithMethod where
@ -93,6 +94,7 @@ instance FromJSON ZenithMethod where
"listreceived" -> pure ListReceived "listreceived" -> pure ListReceived
"getbalance" -> pure GetBalance "getbalance" -> pure GetBalance
"getnewwallet" -> pure GetNewWallet "getnewwallet" -> pure GetNewWallet
"getnewaccount" -> pure GetNewAccount
_ -> pure UnknownMethod _ -> pure UnknownMethod
data ZenithParams data ZenithParams
@ -103,6 +105,7 @@ data ZenithParams
| NotesParams !T.Text | NotesParams !T.Text
| BalanceParams !Int64 | BalanceParams !Int64
| NameParams !T.Text | NameParams !T.Text
| NameIdParams !T.Text !Int
| TestParams !T.Text | TestParams !T.Text
deriving (Eq, Prelude.Show) 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 (TestParams t) = Data.Aeson.Array $ V.fromList [Data.Aeson.String t]
toJSON (NotesParams 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 (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) = toJSON (BalanceParams n) =
Data.Aeson.Array $ V.fromList [jsonNumber $ fromIntegral n] Data.Aeson.Array $ V.fromList [jsonNumber $ fromIntegral n]
@ -311,14 +316,34 @@ instance FromJSON RpcCall where
pure $ RpcCall v i GetNewWallet (NameParams x) pure $ RpcCall v i GetNewWallet (NameParams x)
else pure $ RpcCall v i GetNewWallet BadParams else pure $ RpcCall v i GetNewWallet BadParams
_anyOther -> 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 type ZenithRPC
= "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody = "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody
'[ JSON] '[ JSON]
RpcCall :> Post '[ JSON] ZenithResponse RpcCall :> Post '[ JSON] ZenithResponse
zenithServer :: Config -> Server ZenithRPC data State = State
zenithServer config = getinfo :<|> handleRPC { 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 where
getinfo :: Handler Value getinfo :: Handler Value
getinfo = getinfo =
@ -335,19 +360,8 @@ zenithServer config = getinfo :<|> handleRPC
ListWallets -> ListWallets ->
case parameters req of case parameters req of
BlankParams -> do BlankParams -> do
let dbPath = c_dbPath config pool <- liftIO $ runNoLoggingT $ initPool $ w_dbPath state
let host = c_zebraHost config walList <- liftIO $ getWallets pool $ w_network state
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) if not (null walList)
then return $ then return $
WalletListResponse WalletListResponse
@ -363,11 +377,13 @@ zenithServer config = getinfo :<|> handleRPC
ListAccounts -> ListAccounts ->
case parameters req of case parameters req of
AccountsParams w -> do AccountsParams w -> do
let dbPath = c_dbPath config let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath pool <- liftIO $ runNoLoggingT $ initPool dbPath
wl <- liftIO $ walletExists pool w
case wl of
Just wl' -> do
accList <- accList <-
liftIO $ liftIO $ runNoLoggingT $ getAccounts pool (entityKey wl')
runNoLoggingT $ getAccounts pool (toSqlKey $ fromIntegral w)
if not (null accList) if not (null accList)
then return $ then return $
AccountListResponse AccountListResponse
@ -378,12 +394,15 @@ zenithServer config = getinfo :<|> handleRPC
(callId req) (callId req)
(-32002) (-32002)
"No accounts available for this wallet. Please create one first" "No accounts available for this wallet. Please create one first"
Nothing ->
return $
ErrorResponse (callId req) (-32008) "Wallet does not exist."
_anyOther -> _anyOther ->
return $ ErrorResponse (callId req) (-32602) "Invalid params" return $ ErrorResponse (callId req) (-32602) "Invalid params"
ListAddresses -> ListAddresses ->
case parameters req of case parameters req of
AddressesParams a -> do AddressesParams a -> do
let dbPath = c_dbPath config let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath pool <- liftIO $ runNoLoggingT $ initPool dbPath
addrList <- addrList <-
liftIO $ liftIO $
@ -402,29 +421,11 @@ zenithServer config = getinfo :<|> handleRPC
return $ ErrorResponse (callId req) (-32602) "Invalid params" return $ ErrorResponse (callId req) (-32602) "Invalid params"
GetInfo -> GetInfo ->
case parameters req of case parameters req of
BlankParams -> do BlankParams ->
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 $ return $
InfoResponse InfoResponse
(callId req) (callId req)
(ZenithInfo "0.7.0.0-beta" (zgb_net bI) (zgi_build zI)) (ZenithInfo "0.7.0.0-beta" (w_network state) (w_build state))
_anyOtherParams -> _anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params" return $ ErrorResponse (callId req) (-32602) "Invalid params"
ListReceived -> ListReceived ->
@ -432,7 +433,7 @@ zenithServer config = getinfo :<|> handleRPC
NotesParams x -> do NotesParams x -> do
case (readMaybe (T.unpack x) :: Maybe Int64) of case (readMaybe (T.unpack x) :: Maybe Int64) of
Just x' -> do Just x' -> do
let dbPath = c_dbPath config let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath pool <- liftIO $ runNoLoggingT $ initPool dbPath
a <- liftIO $ getAddressById pool $ toSqlKey x' a <- liftIO $ getAddressById pool $ toSqlKey x'
case a of case a of
@ -454,7 +455,7 @@ zenithServer config = getinfo :<|> handleRPC
(-32005) (-32005)
"Unable to parse address" "Unable to parse address"
Just x' -> do Just x' -> do
let dbPath = c_dbPath config let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath pool <- liftIO $ runNoLoggingT $ initPool dbPath
addrs <- liftIO $ getExternalAddresses pool addrs <- liftIO $ getExternalAddresses pool
nList <- nList <-
@ -466,7 +467,7 @@ zenithServer config = getinfo :<|> handleRPC
GetBalance -> GetBalance ->
case parameters req of case parameters req of
BalanceParams i -> do BalanceParams i -> do
let dbPath = c_dbPath config let dbPath = w_dbPath state
pool <- liftIO $ runNoLoggingT $ initPool dbPath pool <- liftIO $ runNoLoggingT $ initPool dbPath
acc <- liftIO $ getAccountById pool $ toSqlKey i acc <- liftIO $ getAccountById pool $ toSqlKey i
case acc of case acc of
@ -482,27 +483,17 @@ zenithServer config = getinfo :<|> handleRPC
GetNewWallet -> GetNewWallet ->
case parameters req of case parameters req of
NameParams t -> do NameParams t -> do
let host = c_zebraHost config let dbPath = w_dbPath state
let port = c_zebraPort config
let dbPath = c_dbPath config
sP <- liftIO generateWalletSeedPhrase sP <- liftIO generateWalletSeedPhrase
pool <- liftIO $ runNoLoggingT $ initPool dbPath pool <- liftIO $ runNoLoggingT $ initPool dbPath
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 -> do
r <- r <-
liftIO $ liftIO $
saveWallet pool $ saveWallet pool $
ZcashWallet ZcashWallet
t t
(ZcashNetDB $ zgb_net bI) (ZcashNetDB $ w_network state)
(PhraseDB sP) (PhraseDB sP)
(zgb_blocks bI) (w_startBlock state)
0 0
case r of case r of
Nothing -> Nothing ->
@ -516,6 +507,41 @@ zenithServer config = getinfo :<|> handleRPC
NewItemResponse (callId req) $ fromSqlKey $ entityKey r' NewItemResponse (callId req) $ fromSqlKey $ entityKey r'
_anyOtherParams -> _anyOtherParams ->
return $ ErrorResponse (callId req) (-32602) "Invalid params" 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) (-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"
authenticate :: Config -> BasicAuthCheck Bool authenticate :: Config -> BasicAuthCheck Bool
authenticate config = BasicAuthCheck check authenticate config = BasicAuthCheck check

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
import Control.Concurrent (forkIO, threadDelay) import Control.Concurrent (forkIO, threadDelay)
import Control.Exception (SomeException, try) import Control.Exception (SomeException, throwIO, try)
import Control.Monad (when) import Control.Monad (when)
import Data.Aeson import Data.Aeson
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
@ -12,12 +12,18 @@ import Network.HTTP.Simple
import Network.Wai.Handler.Warp (run) import Network.Wai.Handler.Warp (run)
import Servant import Servant
import System.Directory import System.Directory
import Test.HUnit import Test.HUnit hiding (State)
import Test.Hspec import Test.Hspec
import ZcashHaskell.Types (ZcashNet(..)) import ZcashHaskell.Types
( ZcashNet(..)
, ZebraGetBlockChainInfo(..)
, ZebraGetInfo(..)
)
import Zenith.Core (checkBlockChain, checkZebra)
import Zenith.DB (initDb) import Zenith.DB (initDb)
import Zenith.RPC import Zenith.RPC
( RpcCall(..) ( RpcCall(..)
, State(..)
, ZenithInfo(..) , ZenithInfo(..)
, ZenithMethod(..) , ZenithMethod(..)
, ZenithParams(..) , ZenithParams(..)
@ -26,7 +32,7 @@ import Zenith.RPC
, authenticate , authenticate
, zenithServer , zenithServer
) )
import Zenith.Types (Config(..), ZcashWalletAPI(..)) import Zenith.Types (Config(..), ZcashAccountAPI(..), ZcashWalletAPI(..))
main :: IO () main :: IO ()
main = do main = do
@ -176,7 +182,22 @@ main = do
ListAccounts ListAccounts
BlankParams BlankParams
res `shouldBe` Left "Invalid credentials" 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 <- res <-
makeZenithCall makeZenithCall
"127.0.0.1" "127.0.0.1"
@ -193,6 +214,76 @@ main = do
"zh" "zh"
(-32002) (-32002)
"No accounts available for this wallet. Please create one first" "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"
nodePort
nodeUser
nodePwd
ListAccounts
(AccountsParams 1)
case res of
Left e -> assertFailure e
Right r ->
r `shouldBe`
AccountListResponse "zh" [ZcashAccountAPI 1 1 "Personal"]
describe "Addresses" $ do describe "Addresses" $ do
describe "listaddresses" $ do describe "listaddresses" $ do
it "bad credentials" $ do it "bad credentials" $ do
@ -302,14 +393,36 @@ startAPI config = do
putStrLn "Starting test RPC server" putStrLn "Starting test RPC server"
checkDbFile <- doesFileExist "test.db" checkDbFile <- doesFileExist "test.db"
when checkDbFile $ removeFile "test.db" when checkDbFile $ removeFile "test.db"
_ <- initDb "test.db"
let ctx = authenticate config :. EmptyContext let ctx = authenticate config :. EmptyContext
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 $ forkIO $
run (c_zenithPort config) $ run (c_zenithPort config) $
serveWithContext serveWithContext
(Servant.Proxy :: Servant.Proxy ZenithRPC) (Servant.Proxy :: Servant.Proxy ZenithRPC)
ctx ctx
(zenithServer config) (zenithServer myState)
threadDelay 1000000 threadDelay 1000000
putStrLn "Test server is up!" putStrLn "Test server is up!"

View file

@ -190,7 +190,7 @@
"name": "getnewaccount", "name": "getnewaccount",
"summary": "Create a new account", "summary": "Create a new account",
"description": "Create a new account in the given wallet.", "description": "Create a new account in the given wallet.",
"tags": [{"$ref": "#/components/tags/draft"}, {"$ref": "#/components/tags/wip"}], "tags": [],
"params": [ "params": [
{ "$ref": "#/components/contentDescriptors/Name"}, { "$ref": "#/components/contentDescriptors/Name"},
{ "$ref": "#/components/contentDescriptors/WalletId"} { "$ref": "#/components/contentDescriptors/WalletId"}
@ -212,6 +212,11 @@
"name": "Account name", "name": "Account name",
"summary": "The user-friendly name for the Account", "summary": "The user-friendly name for the Account",
"value": "Personal" "value": "Personal"
},
{
"name": "Wallet Id",
"summary": "The internal index of the Wallet to use",
"value": 1
} }
], ],
"result": { "result": {
@ -222,7 +227,8 @@
], ],
"errors": [ "errors": [
{ "$ref": "#/components/errors/ZebraNotAvailable" }, { "$ref": "#/components/errors/ZebraNotAvailable" },
{ "$ref": "#/components/errors/DuplicateName" } { "$ref": "#/components/errors/DuplicateName" },
{ "$ref": "#/components/errors/InvalidWallet" }
] ]
}, },
{ {
@ -604,6 +610,10 @@
"InvalidWallet": { "InvalidWallet": {
"code": -32008, "code": -32008,
"message": "Wallet does not exist." "message": "Wallet does not exist."
},
"InternalError": {
"code": -32010,
"message": "Varies"
} }
} }
} }

View file

@ -67,6 +67,7 @@ library
, microlens-mtl , microlens-mtl
, microlens-th , microlens-th
, monad-logger , monad-logger
, transformers
, monomer , monomer
, mtl , mtl
, persistent , persistent