Compare commits

..

12 commits

10 changed files with 439 additions and 58 deletions

View file

@ -20,6 +20,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- `getnewaccount` RPC method
- `getnewaddress` RPC method
- `getoperationstatus` RPC method
- Function `prepareTxV2` implementing `PrivacyPolicy`
### Changed
@ -27,6 +28,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- Block tracking for chain re-org detection
- Refactored `ZcashPool`
## [0.6.0.0-beta]
### Added

View file

@ -18,6 +18,7 @@ import Brick.Forms
, handleFormEvent
, invalidFormInputAttr
, newForm
, radioField
, renderForm
, setFieldValid
, updateFormState
@ -98,6 +99,7 @@ import Zenith.Types
( Config(..)
, HexStringDB(..)
, PhraseDB(..)
, PrivacyPolicy(..)
, UnifiedAddressDB(..)
, ZcashNetDB(..)
)
@ -106,7 +108,7 @@ import Zenith.Utils
, displayZec
, isRecipientValid
, jsonNumber
, parseAddress
, parseAddressUA
, showAddress
, validBarValue
)
@ -125,6 +127,10 @@ data Name
| ABList
| DescripField
| AddressField
| PrivacyNoneField
| PrivacyLowField
| PrivacyMediumField
| PrivacyFullField
deriving (Eq, Show, Ord)
data DialogInput = DialogInput
@ -137,6 +143,7 @@ data SendInput = SendInput
{ _sendTo :: !T.Text
, _sendAmt :: !Float
, _sendMemo :: !T.Text
, _policyField :: !PrivacyPolicy
} deriving (Show)
makeLenses ''SendInput
@ -177,6 +184,9 @@ data Tick
| TickMsg !String
| TickTx !HexString
data DropDownItem =
DropdownItem String
data State = State
{ _network :: !ZcashNet
, _wallets :: !(L.List Name (Entity ZcashWallet))
@ -609,7 +619,15 @@ mkInputForm =
mkSendForm :: Integer -> SendInput -> Form SendInput e Name
mkSendForm bal =
newForm
[ label "To: " @@= editTextField sendTo RecField (Just 1)
[ label "Privacy Level :" @@=
radioField
policyField
[ (Full, PrivacyFullField, "Full")
, (Medium, PrivacyMediumField, "Medium")
, (Low, PrivacyLowField, "Low")
, (None, PrivacyNoneField, "None")
]
, label "To: " @@= editTextField sendTo RecField (Just 1)
, label "Amount: " @@=
editShowableFieldWithValidate sendAmt AmtField (isAmountValid bal)
, label "Memo: " @@= editTextField sendMemo MemoField (Just 1)
@ -737,7 +755,11 @@ scanZebra dbP zHost zPort b eChan znet = do
logDebugN $
"dbBlock: " <>
T.pack (show dbBlock) <> " chkBlock: " <> T.pack (show chkBlock)
let sb = max dbBlock b
when (chkBlock /= dbBlock) $ liftIO $ rewindWalletData pool chkBlock
let sb =
if chkBlock == dbBlock
then max dbBlock b
else max chkBlock b
if sb > zgb_blocks bStatus || sb < 1
then do
liftIO $ BC.writeBChan eChan $ TickMsg "Invalid starting block for scan"
@ -1144,7 +1166,8 @@ appEvent (BT.VtyEvent e) = do
(SendInput
(addressBookAbaddress (entityVal a))
0.0
"")
""
Full)
BT.modify $ set dialogBox SendTx
_ -> do
BT.modify $
@ -1316,7 +1339,7 @@ appEvent (BT.VtyEvent e) = do
V.EvKey (V.KChar 's') [] -> do
BT.modify $
set txForm $
mkSendForm (s ^. balance) (SendInput "" 0.0 "")
mkSendForm (s ^. balance) (SendInput "" 0.0 "" Full)
BT.modify $ set dialogBox SendTx
V.EvKey (V.KChar 'b') [] ->
BT.modify $ set dialogBox AdrBook
@ -1383,6 +1406,7 @@ runZenithTUI config = do
Left e1 -> throwIO e1
Right chainInfo -> do
x <- initDb dbFilePath
_ <- upgradeQrTable pool
case x of
Left e2 -> throwIO $ userError e2
Right x' -> do
@ -1451,7 +1475,7 @@ runZenithTUI config = do
1.0
eventChan
0
(mkSendForm 0 $ SendInput "" 0.0 "")
(mkSendForm 0 $ SendInput "" 0.0 "" Full)
(L.list ABList (Vec.fromList abookList) 1)
(mkNewABForm (AdrBookEntry "" ""))
""
@ -1673,7 +1697,7 @@ sendTransaction ::
-> IO ()
sendTransaction pool chan zHost zPort znet accId bl amt ua memo = do
BC.writeBChan chan $ TickMsg "Preparing transaction..."
case parseAddress ua znet of
case parseAddressUA ua znet of
Nothing -> BC.writeBChan chan $ TickMsg "Incorrect address"
Just outUA -> do
res <-

View file

@ -44,6 +44,7 @@ import ZcashHaskell.Orchard
, encodeUnifiedAddress
, genOrchardReceiver
, genOrchardSpendingKey
, getOrchardFrontier
, getOrchardNotePosition
, getOrchardWitness
, isValidUnifiedAddress
@ -372,13 +373,16 @@ findOrchardActions config b znet za = do
pool <- runNoLoggingT $ initPool dbPath
tList <- getOrchardActions pool b znet
trees <- getCommitmentTrees zebraHost zebraPort (b - 1)
let sT = OrchardCommitmentTree $ ztiOrchard trees
decryptNotes sT zn pool tList
let sT = getOrchardFrontier $ OrchardCommitmentTree $ ztiOrchard trees
case sT of
Nothing -> throwIO $ userError "Failed to read Orchard commitment tree"
Just sT' -> do
decryptNotes sT' zn pool tList
orchNotes <- getWalletOrchNotes pool (entityKey za)
findOrchSpends pool (entityKey za) orchNotes
where
decryptNotes ::
OrchardCommitmentTree
OrchardFrontier
-> ZcashNet
-> ConnectionPool
-> [(Entity ZcashTransaction, Entity OrchAction)]
@ -901,7 +905,7 @@ prepareTxV2 pool zebraHost zebraPort zn za bh amt va memo policy = do
None ->
return $
Left $
PrivacyPolicyError "Recipient not allowed by privacy policy"
PrivacyPolicyError "Receiver not compatible with privacy policy"
_anyOther -> do
let chgRcvr =
fromJust $

View file

@ -19,7 +19,7 @@
module Zenith.DB where
import Control.Exception (SomeException(..), throw, throwIO, try)
import Control.Monad (when)
import Control.Monad (unless, when)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Logger (NoLoggingT, runNoLoggingT)
import qualified Data.ByteString as BS
@ -448,8 +448,10 @@ initDb dbName = do
(Either SomeException [T.Text])
case m of
Left e2 -> return $ Left $ "Failed to migrate data tables" ++ show e2
Right _ -> return $ Right True
Right _ -> return $ Right False
Right _ -> do
return $ Right True
Right _ -> do
return $ Right False
initPool :: T.Text -> NoLoggingT IO ConnectionPool
initPool dbPath = do
@ -839,6 +841,32 @@ getQrCode pool zp wId = do
return qrs
return $ entityVal <$> r
upgradeQrTable :: ConnectionPool -> IO ()
upgradeQrTable pool = do
r <-
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $
selectOne $ do
qrs <- from $ table @QrCode
where_ $ qrs ^. QrCodeVersion ==. val OrchardPool
return countRows
unless (maybe 0 (\(Value x) -> x) r > (0 :: Int)) $ do
_ <-
runNoLoggingT $
PS.retryOnBusy $
flip PS.runSqlPool pool $ do
rawExecute
"update qr_code set version = ? where version = ?"
[PersistText "OrchardPool", PersistText "Orchard"]
rawExecute
"update qr_code set version = ? where version = ?"
[PersistText "SaplingPool", PersistText "Sapling"]
rawExecute
"update qr_code set version = ? where version = ?"
[PersistText "TransparentPool", PersistText "Transparent"]
return ()
-- * Wallet
-- | Get the block of the last transaction known to the wallet
getMaxWalletBlock ::

View file

@ -32,7 +32,11 @@ import Text.Printf
import Text.Wrap (FillScope(..), FillStrategy(..), WrapSettings(..), wrapText)
import TextShow hiding (toText)
import ZcashHaskell.Keys (generateWalletSeedPhrase)
import ZcashHaskell.Orchard (getSaplingFromUA, isValidUnifiedAddress)
import ZcashHaskell.Orchard
( getSaplingFromUA
, isValidUnifiedAddress
, parseAddress
)
import ZcashHaskell.Transparent (encodeTransparentReceiver)
import ZcashHaskell.Types
( BlockResponse(..)
@ -51,11 +55,11 @@ import Zenith.Scanner (checkIntegrity, processTx, rescanZebra, updateConfs)
import Zenith.Types hiding (ZcashAddress(..))
import Zenith.Utils
( displayAmount
, isRecipientValid
, isRecipientValidGUI
, isValidString
, isZecAddressValid
, jsonNumber
, padWithZero
, parseAddress
, showAddress
, validBarValue
)
@ -121,6 +125,7 @@ data AppEvent
| CopyABAdress !T.Text
| DeleteABEntry !T.Text
| UpdateABDescrip !T.Text !T.Text
| ResetRecipientValid
deriving (Eq, Show)
data AppModel = AppModel
@ -173,6 +178,7 @@ data AppModel = AppModel
, _msgAB :: !(Maybe T.Text)
, _showABAddress :: !Bool
, _updateABAddress :: !Bool
, _privacyChoice :: !PrivacyPolicy
} deriving (Eq, Show)
makeLenses ''AppModel
@ -601,7 +607,28 @@ buildUI wenv model = widgetTree
, separatorLine `styleBasic` [fgColor btnColor]
, spacer
, hstack
[ label "To:" `styleBasic` [width 50]
[ label "Privacy Level:" `styleBasic`
[width 70, textFont "Bold"]
, spacer
, label "Full " `styleBasic` [width 40]
, radio Full privacyChoice
, spacer
, label "Medium " `styleBasic` [width 40]
, radio Medium privacyChoice
]
, hstack
[ label " " `styleBasic`
[width 70, textFont "Bold"]
, spacer
, label "Low " `styleBasic` [width 40]
, radio Low privacyChoice
, spacer
, label "None " `styleBasic` [width 40]
, radio None privacyChoice
]
, spacer
, hstack
[ label "To:" `styleBasic` [width 50, textFont "Bold"]
, spacer
, textField_ sendRecipient [onChange CheckRecipient] `styleBasic`
[ width 150
@ -611,7 +638,8 @@ buildUI wenv model = widgetTree
]
]
, hstack
[ label "Amount:" `styleBasic` [width 50]
[ label "Amount:" `styleBasic`
[width 50, textFont "Bold"]
, spacer
, numericField_
sendAmount
@ -629,12 +657,14 @@ buildUI wenv model = widgetTree
]
]
, hstack
[ label "Memo:" `styleBasic` [width 50]
[ label "Memo:" `styleBasic`
[width 50, textFont "Bold"]
, spacer
, textArea sendMemo `styleBasic`
[width 150, height 40]
]
, spacer
-- Radio button group for privacy level
, box_
[alignMiddle]
(hstack
@ -1053,7 +1083,11 @@ handleEvent wenv node model evt =
]
ConfirmCancel -> [Model $ model & confirmTitle .~ Nothing & mainInput .~ ""]
ShowSeed -> [Model $ model & showSeed .~ True & menuPopup .~ False]
ShowSend -> [Model $ model & openSend .~ True]
ShowSend ->
[ Model $
model & openSend .~ True & privacyChoice .~ Full & recipientValid .~
False
]
SendTx ->
case currentAccount of
Nothing -> [Event $ ShowError "No account available", Event CancelSend]
@ -1071,6 +1105,7 @@ handleEvent wenv node model evt =
(model ^. sendAmount)
(model ^. sendRecipient)
(model ^. sendMemo)
(model ^. privacyChoice)
, Event CancelSend
]
CancelSend ->
@ -1236,7 +1271,11 @@ handleEvent wenv node model evt =
("Wallet Sync: " <>
T.pack (printf "%.2f%%" (model ^. barValue * 100)))
]
CheckRecipient a -> [Model $ model & recipientValid .~ isRecipientValid a]
ResetRecipientValid -> [Model $ model & recipientValid .~ False]
CheckRecipient a ->
[ Model $
model & recipientValid .~ isRecipientValidGUI (model ^. privacyChoice) a
]
CheckAmount i ->
[ Model $
model & amountValid .~
@ -1247,7 +1286,7 @@ handleEvent wenv node model evt =
-- | Address Book Events
-- |
CheckValidAddress a ->
[Model $ model & abAddressValid .~ isRecipientValid a]
[Model $ model & abAddressValid .~ isZecAddressValid a]
CheckValidDescrip a -> [Model $ model & abDescripValid .~ isValidString a]
ShowAdrBook ->
if null (model ^. abaddressList)
@ -1436,6 +1475,7 @@ handleEvent wenv node model evt =
res <- liftIO $ updateAdrsInAdrBook pool d a a
return $ ShowMessage "Address Book entry updated!!"
-- model & recipientValid .~ ((model ^. privacyChoice) == Low) ]
scanZebra :: T.Text -> T.Text -> Int -> ZcashNet -> (AppEvent -> IO ()) -> IO ()
scanZebra dbPath zHost zPort net sendMsg = do
bStatus <- liftIO $ checkBlockChain zHost zPort
@ -1504,20 +1544,21 @@ sendTransaction ::
-> Float
-> T.Text
-> T.Text
-> PrivacyPolicy
-> (AppEvent -> IO ())
-> IO ()
sendTransaction config znet accId bl amt ua memo sendMsg = do
sendTransaction config znet accId bl amt ua memo policy sendMsg = do
sendMsg $ ShowModal "Preparing transaction..."
case parseAddress ua znet of
case parseAddress (E.encodeUtf8 ua) of
Nothing -> sendMsg $ ShowError "Incorrect address"
Just outUA -> do
Just addr -> do
let dbPath = c_dbPath config
let zHost = c_zebraHost config
let zPort = c_zebraPort config
pool <- runNoLoggingT $ initPool dbPath
res <-
runFileLoggingT "zenith.log" $
prepareTx pool zHost zPort znet accId bl amt outUA memo
prepareTxV2 pool zHost zPort znet accId bl amt addr memo policy
case res of
Left e -> sendMsg $ ShowError $ T.pack $ show e
Right rawTx -> do
@ -1564,6 +1605,7 @@ runZenithGUI config = do
Left e1 -> throwIO e1
Right chainInfo -> do
x <- initDb dbFilePath
_ <- upgradeQrTable pool
case x of
Left e2 -> throwIO $ userError e2
Right x' -> do
@ -1654,6 +1696,7 @@ runZenithGUI config = do
Nothing
False
False
Full
startApp model handleEvent buildUI (params hD)
Left _e -> print "Zebra not available"
where

View file

@ -48,6 +48,7 @@ import Zenith.DB
, saveConfs
, saveTransaction
, updateWalletSync
, upgradeQrTable
)
import Zenith.Types (Config(..), HexStringDB(..), ZcashNetDB(..))
import Zenith.Utils (jsonNumber)
@ -69,6 +70,8 @@ rescanZebra host port dbFilePath = do
pool1 <- runNoLoggingT $ initPool dbFilePath
{-pool2 <- runNoLoggingT $ initPool dbFilePath-}
{-pool3 <- runNoLoggingT $ initPool dbFilePath-}
_ <- initDb dbFilePath
upgradeQrTable pool1
clearWalletTransactions pool1
clearWalletData pool1
dbBlock <- getMaxBlock pool1 znet
@ -211,6 +214,7 @@ clearSync config = do
Left e1 -> throwIO e1
Right chainInfo -> do
x <- initDb dbPath
_ <- upgradeQrTable pool
case x of
Left e2 -> throwIO $ userError e2
Right x' -> do

View file

@ -13,7 +13,7 @@ import qualified Data.Text.Encoding as E
import System.Directory
import System.Process (createProcess_, shell)
import Text.Regex.Posix
import ZcashHaskell.Orchard (encodeUnifiedAddress, isValidUnifiedAddress)
import ZcashHaskell.Orchard (encodeUnifiedAddress, isValidUnifiedAddress, parseAddress)
import ZcashHaskell.Sapling (decodeSaplingAddress, isValidShieldedAddress)
import ZcashHaskell.Transparent
( decodeExchangeAddress
@ -24,12 +24,15 @@ import ZcashHaskell.Types
, TransparentAddress(..)
, UnifiedAddress(..)
, ZcashNet(..)
, ValidAddress(..)
, ExchangeAddress(..)
)
import Zenith.Types
( AddressGroup(..)
, UnifiedAddressDB(..)
, ZcashAddress(..)
, ZcashPool(..)
, PrivacyPolicy(..)
)
-- | Helper function to convert numbers into JSON
@ -110,7 +113,7 @@ validBarValue :: Float -> Float
validBarValue = clamp (0, 1)
isRecipientValid :: T.Text -> Bool
isRecipientValid a =
isRecipientValid a = do
case isValidUnifiedAddress (E.encodeUtf8 a) of
Just _a1 -> True
Nothing ->
@ -122,8 +125,78 @@ isRecipientValid a =
Just _a4 -> True
Nothing -> False)
parseAddress :: T.Text -> ZcashNet -> Maybe UnifiedAddress
parseAddress a znet =
isUnifiedAddressValid :: T.Text -> Bool
isUnifiedAddressValid ua =
case isValidUnifiedAddress (E.encodeUtf8 ua) of
Just _a1 -> True
Nothing -> False
isSaplingAddressValid :: T.Text -> Bool
isSaplingAddressValid sa = isValidShieldedAddress (E.encodeUtf8 sa)
isTransparentAddressValid :: T.Text -> Bool
isTransparentAddressValid ta =
case decodeTransparentAddress (E.encodeUtf8 ta) of
Just _a3 -> True
Nothing -> False
isExchangeAddressValid :: T.Text -> Bool
isExchangeAddressValid xa =
case decodeExchangeAddress (E.encodeUtf8 xa) of
Just _a4 -> True
Nothing -> False
isRecipientValidGUI :: PrivacyPolicy -> T.Text -> Bool
isRecipientValidGUI p a = do
let adr = parseAddress (E.encodeUtf8 a)
case p of
Full -> case adr of
Just a ->
case a of
Unified ua -> True
Sapling sa -> True
_ -> False
Nothing -> False
Medium -> case adr of
Just a ->
case a of
Unified ua -> True
Sapling sa -> True
_ -> False
Nothing -> False
Low -> case adr of
Just a ->
case a of
Unified ua -> True
Sapling sa -> True
Transparent ta -> True
Exchange ea -> True
_ -> False
Nothing -> False
None -> case adr of
Just a ->
case a of
Transparent ta -> True
Exchange ea -> True
_ -> False
Nothing -> False
isZecAddressValid :: T.Text -> Bool
isZecAddressValid a = do
case isValidUnifiedAddress (E.encodeUtf8 a) of
Just _a1 -> True
Nothing ->
isValidShieldedAddress (E.encodeUtf8 a) ||
(case decodeTransparentAddress (E.encodeUtf8 a) of
Just _a3 -> True
Nothing ->
case decodeExchangeAddress (E.encodeUtf8 a) of
Just _a4 -> True
Nothing -> False)
parseAddressUA :: T.Text -> ZcashNet -> Maybe UnifiedAddress
parseAddressUA a znet =
case isValidUnifiedAddress (E.encodeUtf8 a) of
Just a1 -> Just a1
Nothing ->

View file

@ -32,6 +32,7 @@ import ZcashHaskell.Types
, SaplingSpendingKey(..)
, Scope(..)
, ShieldedOutput(..)
, TxError(..)
, ZcashNet(..)
)
import Zenith.Core
@ -235,15 +236,15 @@ main = do
Just
"ztestsapling1tgjr4zppwk4ne8xy6gdq4z2gwq7dmf5jq8z2ctpn8nlmtse0a74fa5z0m8z383gmpgqz6q6duu4"
describe "Notes" $ do
it "Check Orchard notes" $ do
xit "Check Orchard notes" $ do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
oNotes <- getWalletUnspentOrchNotes pool (toSqlKey 1)
oNotes `shouldBe` []
it "Check Sapling notes" $ do
xit "Check Sapling notes" $ do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
oNotes <- getWalletUnspentSapNotes pool (toSqlKey 4)
oNotes `shouldBe` []
it "Check transparent notes" $ do
xit "Check transparent notes" $ do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
oNotes <- getWalletUnspentTrNotes pool (toSqlKey 1)
oNotes `shouldBe` []
@ -265,7 +266,7 @@ main = do
18232
TestNet
(toSqlKey 1)
3001230
3001331
0.005
(fromJust uaRead)
"Sending memo to orchard"
@ -289,7 +290,7 @@ main = do
18232
TestNet
(toSqlKey 4)
3001230
3001331
0.005
(fromJust uaRead)
"Sending memo to sapling"
@ -297,8 +298,30 @@ main = do
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")
it "To Transparent" $ do
let uaRead = parseAddress "tmAmSa4AauSFuJieeanRBjkfnah45ysGtgZ"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 4)
3001331
0.005
(fromJust uaRead)
""
Full
tx `shouldBe`
Left
(PrivacyPolicyError "Receiver not capable of Full privacy")
describe "Medium" $ do
xit "To Orchard" $ do
it "To Orchard" $ do
let uaRead =
parseAddress
"utest1dl54utt6prjj5e0dnlknwumnxq9hycdjpkfr0sy6e6h522remqee8axe9zax0wsjrwpj76v555pdhvj9rnargpfyycs0vpkapq98xcdhem99gc4wchzn0ggepq3y6nz3a9sscwgqxgsh9vzhcad402y3x9szfregck5gslkya3c79d86xx0l33tpk8gnn7ew9vw37w43zh22u8dgdax"
@ -314,7 +337,7 @@ main = do
18232
TestNet
(toSqlKey 1)
3000789
3001372
0.005
(fromJust uaRead)
"Sending memo to orchard"
@ -322,7 +345,7 @@ main = do
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")
xit "To Sapling" $ do
it "To Sapling" $ do
let uaRead =
parseAddress
"ztestsapling136jp8z89v2jh6kqd5rs4dtvlxym90m43svzdwzxaplyvc5ttzppytpvx80ncllcsqzpmukxjl3y"
@ -338,7 +361,7 @@ main = do
18232
TestNet
(toSqlKey 1)
3000789
3001372
0.005
(fromJust uaRead)
"Sending memo to orchard"
@ -346,3 +369,169 @@ main = do
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")
it "To Transparent" $ do
let uaRead = parseAddress "tmAmSa4AauSFuJieeanRBjkfnah45ysGtgZ"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 4)
3001331
0.005
(fromJust uaRead)
""
Medium
tx `shouldBe`
Left
(PrivacyPolicyError "Receiver not capable of Medium privacy")
describe "Low" $ do
it "To Orchard" $ do
let uaRead =
parseAddress
"utest1dl54utt6prjj5e0dnlknwumnxq9hycdjpkfr0sy6e6h522remqee8axe9zax0wsjrwpj76v555pdhvj9rnargpfyycs0vpkapq98xcdhem99gc4wchzn0ggepq3y6nz3a9sscwgqxgsh9vzhcad402y3x9szfregck5gslkya3c79d86xx0l33tpk8gnn7ew9vw37w43zh22u8dgdax"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 1)
3001372
0.005
(fromJust uaRead)
"Sending memo to orchard"
Low
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")
it "To Sapling" $ do
let uaRead =
parseAddress
"ztestsapling136jp8z89v2jh6kqd5rs4dtvlxym90m43svzdwzxaplyvc5ttzppytpvx80ncllcsqzpmukxjl3y"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 1)
3001372
0.005
(fromJust uaRead)
"Sending memo to orchard"
Low
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")
it "To Transparent" $ do
let uaRead = parseAddress "tmAmSa4AauSFuJieeanRBjkfnah45ysGtgZ"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 1)
3001372
0.005
(fromJust uaRead)
""
Low
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")
describe "None" $ do
it "To Orchard" $ do
let uaRead =
parseAddress
"utest1dl54utt6prjj5e0dnlknwumnxq9hycdjpkfr0sy6e6h522remqee8axe9zax0wsjrwpj76v555pdhvj9rnargpfyycs0vpkapq98xcdhem99gc4wchzn0ggepq3y6nz3a9sscwgqxgsh9vzhcad402y3x9szfregck5gslkya3c79d86xx0l33tpk8gnn7ew9vw37w43zh22u8dgdax"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 1)
3001372
0.005
(fromJust uaRead)
"Sending memo to orchard"
None
tx `shouldBe`
Left
(PrivacyPolicyError
"Receiver not compatible with privacy policy")
it "To Sapling" $ do
let uaRead =
parseAddress
"ztestsapling136jp8z89v2jh6kqd5rs4dtvlxym90m43svzdwzxaplyvc5ttzppytpvx80ncllcsqzpmukxjl3y"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 1)
3001372
0.005
(fromJust uaRead)
"Sending memo to orchard"
None
tx `shouldBe`
Left
(PrivacyPolicyError
"Receiver not compatible with privacy policy")
it "To Transparent" $ do
let uaRead = parseAddress "tmAmSa4AauSFuJieeanRBjkfnah45ysGtgZ"
case uaRead of
Nothing -> assertFailure "wrong address"
Just ua -> do
pool <- runNoLoggingT $ initPool "/home/rav/Zenith/zenith.db"
tx <-
runFileLoggingT "zenith.log" $
prepareTxV2
pool
"localhost"
18232
TestNet
(toSqlKey 1)
3001372
0.005
(fromJust uaRead)
""
None
case tx of
Left e -> assertFailure $ show e
Right h -> h `shouldNotBe` (hexString "deadbeef")

@ -1 +1 @@
Subproject commit 12296026a0ebb9a5afe0904b251c5d31080eab18
Subproject commit 003293cc3f978c146824d0695c5c458cf2cc9bb5

View file

@ -593,11 +593,12 @@
{
"name": "sendmany",
"summary": "Send transaction(s)",
"description": "Send one or more transactions by specifying the source account, the recipient address, the amount, the shielded memo (optional) and the privacy policy (optional).",
"description": "Send one transaction by specifying the source account, the privacy policy (optional, default 'Full') and an array of proposed outputs. Each output needs a recipient address, an amount and an optional shielded memo.",
"tags": [{"$ref": "#/components/tags/draft"},{"$ref": "#/components/tags/wip"}],
"params": [
{ "$ref": "#/components/contentDescriptors/AccountId"},
{ "$ref": "#/components/contentDescriptors/TxRequestArray"}
{ "$ref": "#/components/contentDescriptors/TxRequestArray"},
{ "$ref": "#/components/contentDescriptors/PrivacyPolicy"}
],
"paramStructure": "by-position",
"result": {
@ -628,7 +629,11 @@
"memo": "Simple transaction"
}
]
}
},
{
"name": "Privacy Policy",
"summary": "The selected privacy policy",
"value": "Full"
],
"result": {
"name": "SendMany result",
@ -736,6 +741,16 @@
"type": "array",
"items": { "$ref": "#/components/schemas/TxRequest"}
}
},
"PrivacyPolicy": {
"name": "Privacy Policy",
"summary": "The chosen privacy policy to use for the transaction",
"description": "The privacy policy to use for the transaction. `Full` policy allows shielded funds to be transferred within their shielded pools. `Medium` policy allows shielded funds to cross shielded pools. `Low` allows deshielding transactions into transparent receivers. `None` allows for transparent funds to be spent to transparent addresses.",
"required": false,
"schema": {
"type": "string",
"enum": ["None", "Low", "Medium", "Full"]
}
}
},
"schemas": {
@ -814,8 +829,7 @@
"properties": {
"address": { "type": "string", "description": "Recipient's address (unified, Sapling or transparent)" },
"amount": { "type": "number", "description": "The amount to send in ZEC"},
"memo": { "type": "string", "description": "The shielded memo to include, if applicable"},
"privacy": { "type": "string", "enum": ["None", "Low", "Medium", "Full"], "description": "The privacy policy to use for the transaction. `Full` policy allows shielded funds to be transferred within their shielded pools. `Medium` policy allows shielded funds to cross shielded pools and deshielding transactions. `Low` allows to spend transparent funds into shielded pools. `None` allows for transparent funds to be spent to transparent addresses."}
"memo": { "type": "string", "description": "The shielded memo to include, if applicable"}
}
}
},