feat(rpc): implement deshieldfunds
This commit is contained in:
parent
9226dea598
commit
a303ca9fed
7 changed files with 164 additions and 78 deletions
|
@ -1285,45 +1285,23 @@ appEvent (BT.VtyEvent e) = do
|
|||
Just (_j, w1) -> return w1
|
||||
Just (_k, w) -> return w
|
||||
fs1 <- BT.zoom deshieldForm $ BT.gets formState
|
||||
let tAddrMaybe =
|
||||
Transparent <$>
|
||||
((decodeTransparentAddress .
|
||||
E.encodeUtf8 .
|
||||
encodeTransparentReceiver (s ^. network)) =<<
|
||||
(t_rec =<<
|
||||
(isValidUnifiedAddress .
|
||||
E.encodeUtf8 .
|
||||
getUA . walletAddressUAddress)
|
||||
(entityVal selAddr)))
|
||||
bl <-
|
||||
liftIO $
|
||||
getChainTip (s ^. zebraHost) (s ^. zebraPort)
|
||||
case tAddrMaybe of
|
||||
Nothing -> do
|
||||
BT.modify $
|
||||
set
|
||||
msg
|
||||
"Failed to obtain transparent address"
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
BT.modify $ set dialogBox Blank
|
||||
Just tAddr -> do
|
||||
_ <-
|
||||
liftIO $
|
||||
forkIO $
|
||||
deshieldTransaction
|
||||
pool
|
||||
(s ^. eventDispatch)
|
||||
(s ^. zebraHost)
|
||||
(s ^. zebraPort)
|
||||
(s ^. network)
|
||||
(entityKey selAcc)
|
||||
bl
|
||||
(ProposedNote
|
||||
(ValidAddressAPI tAddr)
|
||||
(fs1 ^. shAmt)
|
||||
Nothing)
|
||||
BT.modify $ set displayBox SendDisplay
|
||||
BT.modify $ set dialogBox Blank
|
||||
_ <-
|
||||
liftIO $
|
||||
forkIO $
|
||||
deshieldTransaction
|
||||
pool
|
||||
(s ^. eventDispatch)
|
||||
(s ^. zebraHost)
|
||||
(s ^. zebraPort)
|
||||
(s ^. network)
|
||||
(entityKey selAcc)
|
||||
bl
|
||||
(fs1 ^. shAmt)
|
||||
BT.modify $ set displayBox SendDisplay
|
||||
BT.modify $ set dialogBox Blank
|
||||
else do
|
||||
BT.modify $ set msg "Invalid inputs"
|
||||
BT.modify $ set displayBox MsgDisplay
|
||||
|
@ -2075,7 +2053,7 @@ deshieldTransaction ::
|
|||
-> ZcashNet
|
||||
-> ZcashAccountId
|
||||
-> Int
|
||||
-> ProposedNote
|
||||
-> Scientific
|
||||
-> IO ()
|
||||
deshieldTransaction pool chan zHost zPort znet accId bl pnote = do
|
||||
BC.writeBChan chan $ TickMsg "Deshielding funds..."
|
||||
|
|
|
@ -44,6 +44,7 @@ import ZcashHaskell.Orchard
|
|||
, getOrchardTreeParts
|
||||
, getOrchardWitness
|
||||
, isValidUnifiedAddress
|
||||
, parseAddress
|
||||
, updateOrchardCommitmentTree
|
||||
, updateOrchardWitness
|
||||
)
|
||||
|
@ -86,6 +87,7 @@ import Zenith.Types
|
|||
, ZenithStatus(..)
|
||||
, ZenithUuid(..)
|
||||
)
|
||||
import Zenith.Utils (getTransparentFromUA)
|
||||
|
||||
-- * Zebra Node interaction
|
||||
-- | Checks the status of the `zebrad` node
|
||||
|
@ -751,14 +753,37 @@ deshieldNotes ::
|
|||
-> ZcashNet
|
||||
-> ZcashAccountId
|
||||
-> Int
|
||||
-> ProposedNote
|
||||
-> Scientific
|
||||
-> NoLoggingT IO (Either TxError HexString)
|
||||
deshieldNotes pool zebraHost zebraPort znet za bh pnote = do
|
||||
bal <- liftIO $ getShieldedBalance pool za
|
||||
let zats = pn_amt pnote * scientific 1 8
|
||||
if fromInteger bal > (scientific 2 4 + zats)
|
||||
then prepareTxV2 pool zebraHost zebraPort znet za bh [pnote] Low
|
||||
else return $ Left InsufficientFunds
|
||||
addrs <- getAddresses pool za
|
||||
let defAddr =
|
||||
parseAddress $
|
||||
E.encodeUtf8 $ getUA $ walletAddressUAddress $ entityVal $ head addrs
|
||||
case defAddr of
|
||||
Nothing -> return $ Left ZHError
|
||||
Just (Unified x) -> do
|
||||
case getTransparentFromUA x of
|
||||
Nothing -> return $ Left ZHError
|
||||
Just ta -> do
|
||||
let zats = pnote * scientific 1 8
|
||||
if fromInteger bal > (scientific 2 4 + zats)
|
||||
then prepareTxV2
|
||||
pool
|
||||
zebraHost
|
||||
zebraPort
|
||||
znet
|
||||
za
|
||||
bh
|
||||
[ ProposedNote
|
||||
(ValidAddressAPI $ Transparent ta)
|
||||
pnote
|
||||
Nothing
|
||||
]
|
||||
Low
|
||||
else return $ Left InsufficientFunds
|
||||
_anyOther -> return $ Left ZHError
|
||||
|
||||
shieldTransparentNotes ::
|
||||
ConnectionPool
|
||||
|
|
|
@ -630,6 +630,7 @@ getAddresses pool a =
|
|||
addrs <- from $ table @WalletAddress
|
||||
where_ (addrs ^. WalletAddressAccId ==. val a)
|
||||
where_ (addrs ^. WalletAddressScope ==. val (ScopeDB External))
|
||||
orderBy [asc $ addrs ^. WalletAddressId]
|
||||
pure addrs
|
||||
|
||||
getAddressById ::
|
||||
|
|
|
@ -1784,40 +1784,20 @@ deshieldTransaction config znet accId addR pnote sendMsg = do
|
|||
let zPort = c_zebraPort config
|
||||
pool <- runNoLoggingT $ initPool dbPath
|
||||
bl <- getChainTip zHost zPort
|
||||
let tAddrMaybe =
|
||||
Transparent <$>
|
||||
((decodeTransparentAddress .
|
||||
E.encodeUtf8 . encodeTransparentReceiver znet) =<<
|
||||
(t_rec =<<
|
||||
(isValidUnifiedAddress .
|
||||
E.encodeUtf8 . getUA . walletAddressUAddress)
|
||||
(entityVal addr)))
|
||||
case tAddrMaybe of
|
||||
Nothing -> sendMsg $ ShowError "No transparent address available"
|
||||
Just tAddr -> do
|
||||
res <-
|
||||
runNoLoggingT $
|
||||
deshieldNotes
|
||||
pool
|
||||
res <- runNoLoggingT $ deshieldNotes pool zHost zPort znet accId bl pnote
|
||||
case res of
|
||||
Left e -> sendMsg $ ShowError $ T.pack (show e)
|
||||
Right rawTx -> do
|
||||
sendMsg $ ShowModal "Transaction ready, sending to Zebra..."
|
||||
resp <-
|
||||
makeZebraCall
|
||||
zHost
|
||||
zPort
|
||||
znet
|
||||
accId
|
||||
bl
|
||||
(ProposedNote (ValidAddressAPI tAddr) pnote Nothing)
|
||||
case res of
|
||||
Left e -> sendMsg $ ShowError $ T.pack (show e)
|
||||
Right rawTx -> do
|
||||
sendMsg $ ShowModal "Transaction ready, sending to Zebra..."
|
||||
resp <-
|
||||
makeZebraCall
|
||||
zHost
|
||||
zPort
|
||||
"sendrawtransaction"
|
||||
[Data.Aeson.String $ toText rawTx]
|
||||
case resp of
|
||||
Left e1 -> sendMsg $ ShowError $ "Zebra error: " <> showt e1
|
||||
Right txId -> sendMsg $ ShowTxId txId
|
||||
"sendrawtransaction"
|
||||
[Data.Aeson.String $ toText rawTx]
|
||||
case resp of
|
||||
Left e1 -> sendMsg $ ShowError $ "Zebra error: " <> showt e1
|
||||
Right txId -> sendMsg $ ShowTxId txId
|
||||
|
||||
sendTransaction ::
|
||||
Config
|
||||
|
|
|
@ -20,7 +20,7 @@ import Control.Monad.Logger (runFileLoggingT, runNoLoggingT, runStderrLoggingT)
|
|||
import Data.Aeson
|
||||
import qualified Data.HexString as H
|
||||
import Data.Int
|
||||
import Data.Scientific (floatingOrInteger)
|
||||
import Data.Scientific (Scientific(..), floatingOrInteger)
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as E
|
||||
import Data.Time.Clock (getCurrentTime)
|
||||
|
@ -50,6 +50,7 @@ import Zenith.Core
|
|||
( checkBlockChain
|
||||
, createCustomWalletAddress
|
||||
, createZcashAccount
|
||||
, deshieldNotes
|
||||
, prepareTxV2
|
||||
, shieldTransparentNotes
|
||||
, syncWallet
|
||||
|
@ -123,6 +124,7 @@ data ZenithMethod
|
|||
| GetOperationStatus
|
||||
| SendMany
|
||||
| ShieldNotes
|
||||
| DeshieldFunds
|
||||
| UnknownMethod
|
||||
deriving (Eq, Prelude.Show)
|
||||
|
||||
|
@ -139,6 +141,7 @@ instance ToJSON ZenithMethod where
|
|||
toJSON GetOperationStatus = Data.Aeson.String "getoperationstatus"
|
||||
toJSON SendMany = Data.Aeson.String "sendmany"
|
||||
toJSON ShieldNotes = Data.Aeson.String "shieldnotes"
|
||||
toJSON DeshieldFunds = Data.Aeson.String "deshieldfunds"
|
||||
toJSON UnknownMethod = Data.Aeson.Null
|
||||
|
||||
instance FromJSON ZenithMethod where
|
||||
|
@ -156,6 +159,7 @@ instance FromJSON ZenithMethod where
|
|||
"getoperationstatus" -> pure GetOperationStatus
|
||||
"sendmany" -> pure SendMany
|
||||
"shieldnotes" -> pure ShieldNotes
|
||||
"deshieldfunds" -> pure DeshieldFunds
|
||||
_ -> pure UnknownMethod
|
||||
|
||||
data ZenithParams
|
||||
|
@ -172,6 +176,7 @@ data ZenithParams
|
|||
| SendParams !Int ![ProposedNote] !PrivacyPolicy
|
||||
| TestParams !T.Text
|
||||
| ShieldNotesParams !Int
|
||||
| DeshieldParams !Int !Scientific
|
||||
deriving (Eq, Prelude.Show)
|
||||
|
||||
instance ToJSON ZenithParams where
|
||||
|
@ -197,6 +202,8 @@ instance ToJSON ZenithParams where
|
|||
toJSON (SendParams i ns p) =
|
||||
Data.Aeson.Array $ V.fromList [jsonNumber i, toJSON ns, toJSON p]
|
||||
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]
|
||||
|
||||
data ZenithResponse
|
||||
= InfoResponse !T.Text !ZenithInfo
|
||||
|
@ -510,6 +517,17 @@ instance FromJSON RpcCall where
|
|||
pure $ RpcCall v i ShieldNotes (ShieldNotesParams x)
|
||||
else pure $ RpcCall v i ShieldNotes BadParams
|
||||
_anyOther -> pure $ RpcCall v i ShieldNotes BadParams
|
||||
DeshieldFunds -> 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 DeshieldFunds (DeshieldParams x y)
|
||||
else pure $ RpcCall v i DeshieldFunds BadParams
|
||||
_anyOther -> pure $ RpcCall v i DeshieldFunds BadParams
|
||||
|
||||
type ZenithRPC
|
||||
= "status" :> Get '[ JSON] Value :<|> BasicAuth "zenith-realm" Bool :> ReqBody
|
||||
|
@ -942,6 +960,87 @@ zenithServer state = getinfo :<|> handleRPC
|
|||
"Account does not exist."
|
||||
_anyOtherParams ->
|
||||
return $ ErrorResponse (callId req) (-32602) "Invalid params"
|
||||
DeshieldFunds -> do
|
||||
case parameters req of
|
||||
DeshieldParams i k -> do
|
||||
let dbPath = w_dbPath state
|
||||
let net = w_network state
|
||||
let zHost = w_host state
|
||||
let zPort = w_port state
|
||||
pool <- liftIO $ runNoLoggingT $ initPool dbPath
|
||||
syncChk <- liftIO $ isSyncing pool
|
||||
if syncChk
|
||||
then return $
|
||||
ErrorResponse
|
||||
(callId req)
|
||||
(-32012)
|
||||
"The Zenith server is syncing, please try again later."
|
||||
else do
|
||||
opid <- liftIO nextRandom
|
||||
startTime <- liftIO getCurrentTime
|
||||
opkey <-
|
||||
liftIO $
|
||||
saveOperation pool $
|
||||
Operation
|
||||
(ZenithUuid opid)
|
||||
startTime
|
||||
Nothing
|
||||
Processing
|
||||
Nothing
|
||||
case opkey of
|
||||
Nothing ->
|
||||
return $
|
||||
ErrorResponse (callId req) (-32010) "Internal Error"
|
||||
Just opkey' -> do
|
||||
acc <-
|
||||
liftIO $ getAccountById pool $ toSqlKey $ fromIntegral i
|
||||
case acc of
|
||||
Just acc' -> do
|
||||
bl <-
|
||||
liftIO $
|
||||
getLastSyncBlock
|
||||
pool
|
||||
(zcashAccountWalletId $ entityVal acc')
|
||||
_ <-
|
||||
liftIO $
|
||||
forkIO $ do
|
||||
res <-
|
||||
runNoLoggingT $
|
||||
deshieldNotes
|
||||
pool
|
||||
zHost
|
||||
zPort
|
||||
net
|
||||
(entityKey acc')
|
||||
bl
|
||||
k
|
||||
case res of
|
||||
Left e ->
|
||||
finalizeOperation pool opkey' Failed $
|
||||
T.pack $ show e
|
||||
Right rawTx -> do
|
||||
zebraRes <-
|
||||
makeZebraCall
|
||||
zHost
|
||||
zPort
|
||||
"sendrawtransaction"
|
||||
[Data.Aeson.String $ H.toText rawTx]
|
||||
case zebraRes of
|
||||
Left e1 ->
|
||||
finalizeOperation pool opkey' Failed $
|
||||
T.pack $ show e1
|
||||
Right txId ->
|
||||
finalizeOperation pool opkey' Successful $
|
||||
"Tx ID: " <> H.toText txId
|
||||
return $ SendResponse (callId req) opid
|
||||
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
|
||||
|
|
|
@ -235,7 +235,7 @@ isValidString c = do
|
|||
|
||||
padWithZero :: Int -> String -> String
|
||||
padWithZero n s
|
||||
| (length s) >= n = s
|
||||
| length s >= n = s
|
||||
| otherwise = padWithZero n ("0" ++ s)
|
||||
|
||||
isEmpty :: [a] -> Bool
|
||||
|
@ -248,3 +248,6 @@ getChainTip zHost zPort = do
|
|||
case r of
|
||||
Left e1 -> pure 0
|
||||
Right i -> pure i
|
||||
|
||||
getTransparentFromUA :: UnifiedAddress -> Maybe TransparentAddress
|
||||
getTransparentFromUA ua = TransparentAddress (ua_net ua) <$> t_rec ua
|
||||
|
|
|
@ -732,8 +732,8 @@
|
|||
{
|
||||
"name": "deshieldfunds",
|
||||
"summary": "De-shield the given amount of ZEC from the given account",
|
||||
"description": "Creates a new internal transaction with the requested amount of ZEC to the transparent pool.",
|
||||
"tags": [{ "$ref": "#/components/tags/draft"}, { "$ref": "#/components/tags/wip"}],
|
||||
"description": "Creates a new internal transaction with the requested amount of ZEC to the transparent pool. The fee is not included in the given amount.",
|
||||
"tags": [],
|
||||
"params": [
|
||||
{ "$ref": "#/components/contentDescriptors/AccountId"},
|
||||
{ "$ref": "#/components/contentDescriptors/Amount"}
|
||||
|
|
Loading…
Reference in a new issue