Merge branch 'rvv040' into rav001

This commit is contained in:
Rene Vergara 2024-03-15 10:11:27 -05:00
commit d5c50d58c5
Signed by: pitmutt
GPG Key ID: 65122AD495A7F5B2
5 changed files with 310 additions and 31 deletions

View File

@ -61,7 +61,8 @@ use zcash_address::{
use zcash_client_backend::keys::sapling::{
spending_key,
ExtendedFullViewingKey,
ExtendedSpendingKey
ExtendedSpendingKey,
DiversifiableFullViewingKey
};
use zcash_primitives::zip32::DiversifierIndex;
@ -676,6 +677,29 @@ pub extern "C" fn rust_wrapper_sapling_paymentaddress(
}
}
#[no_mangle]
pub extern "C" fn rust_wrapper_sapling_chgpaymentaddress(
extspk: *const u8,
extspk_len: usize,
out: *mut u8,
out_len: &mut usize
){
let vexspk: Vec<u8> = marshall_from_haskell_var(extspk, extspk_len, RW);
let vexspkp = &vexspk;
let extspku8 : &[u8] = &vexspkp;
let extspk = match ExtendedSpendingKey::from_bytes(&extspku8) {
Ok( k ) => k,
Err( e ) => {
// error recovering ExtendedSpendingKey
marshall_to_haskell_var(&vec![0], out, out_len, RW);
return
}
};
let dfvk = extspk.to_diversifiable_full_viewing_key();
let ( divIx, cPmtAddress ) = dfvk.change_address();
marshall_to_haskell_var(&cPmtAddress.to_bytes().to_vec(), out, out_len, RW);
}
#[no_mangle]
pub extern "C" fn rust_wrapper_derive_orchard_spending_key(
seed: *const u8,

View File

@ -151,6 +151,13 @@ import ZcashHaskell.Types
-> `()'
#}
{# fun unsafe rust_wrapper_sapling_chgpaymentaddress as rustWrapperSaplingChgPaymentAddress
{ toBorshVar* `BS.ByteString'&
, getVarBuffer `Buffer (BS.ByteString)'&
}
-> `()'
#}
{# fun unsafe rust_wrapper_derive_orchard_spending_key as rustWrapperGenOrchardSpendKey
{ toBorshVar* `BS.ByteString'&
, `Word32'

View File

@ -20,6 +20,7 @@ module ZcashHaskell.Sapling where
import C.Zcash
( rustWrapperIsShielded
, rustWrapperSaplingCheck
, rustWrapperSaplingChgPaymentAddress
, rustWrapperSaplingNoteDecode
, rustWrapperSaplingPaymentAddress
, rustWrapperSaplingSpendingkey
@ -124,4 +125,10 @@ genSaplingPaymentAddress i extspk =
-- | Generate an internal Sapling address
genSaplingInternalAddress :: SaplingSpendingKey -> Maybe SaplingReceiver
genSaplingInternalAddress sk = undefined
genSaplingInternalAddress sk =
if BS.length res > 0
then Just $ SaplingReceiver res
else Nothing
where
res =
withPureBorshVarBuffer (rustWrapperSaplingChgPaymentAddress $ getBytes sk)

View File

@ -17,28 +17,30 @@ module ZcashHaskell.Transparent where
import Control.Exception (throwIO)
import Crypto.Hash
import Crypto.Secp256k1
import qualified Data.ByteArray as BA
import qualified Data.ByteString as BS
import Data.ByteString.Base58 (bitcoinAlphabet, encodeBase58)
import Data.HexString
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import Data.Word
import Haskoin.Address (Address(..))
import qualified Haskoin.Crypto.Hash as H
import Haskoin.Crypto.Keys.Extended
import ZcashHaskell.Types
( AccountId
, CoinType(..)
, Scope(..)
, Seed(..)
, ToBytes(..)
, TransparentAddress(..)
, TransparentType(..)
, ZcashNet(..)
, getTransparentPrefix
, getValue
)
import Crypto.Secp256k1
import Data.HexString
import Data.Word
import Haskoin.Address (Address(..))
import qualified Haskoin.Crypto.Hash as H
import Haskoin.Crypto.Keys.Extended
encodeTransparent :: ZcashNet -> TransparentAddress -> T.Text
encodeTransparent zNet t =
encodeTransparent' (getTransparentPrefix zNet (ta_type t)) $
@ -53,19 +55,36 @@ encodeTransparent zNet t =
digest = BS.pack [a, b] <> h
checksum = sha256 $ sha256 digest
-- | Attempts to generate an Extended Private Key from a known HDSeed.
genTransparentPrvKey :: Seed -> AccountId -> IO XPrvKey
genTransparentPrvKey hdseed i = do
let prvKey = makeXPrvKey $ getBytes hdseed
-- | Generate an Extended Private Key from a known HDSeed.
genTransparentPrvKey :: Seed -> CoinType -> AccountId -> IO XPrvKey
genTransparentPrvKey hdseed ctype accid = do
let coin = getValue ctype
ioCtx <- createContext
return $ hardSubKey ioCtx prvKey (fromIntegral i)
let path = Deriv :| 44 :| coin :| fromIntegral accid :: DerivPath
let prvKey = makeXPrvKey $ getBytes hdseed
return $ derivePath ioCtx path prvKey
genTransparentPubKey :: XPrvKey -> IO XPubKey
genTransparentPubKey xPrvKey = do
ioCtx <- createContext
return $ deriveXPubKey ioCtx xPrvKey
genTransparentPubAddress :: XPubKey -> IO Address
genTransparentPubAddress xPubKey = do
ioCtx <- createContext
return $ xPubAddr ioCtx xPubKey
-- | Generate a transparent receiver
genTransparentReceiver :: Int -> XPrvKey -> IO TransparentAddress
genTransparentReceiver i xprvk = do
genTransparentReceiver :: Int -> Scope -> XPrvKey -> IO TransparentAddress
genTransparentReceiver i scope xprvk = do
ioCtx <- createContext
let rootPubKey = deriveXPubKey ioCtx xprvk
let childPubKey = pubSubKey ioCtx rootPubKey (fromIntegral i)
let s =
case scope of
External -> 0
Internal -> 1
let path = Deriv :/ s :/ fromIntegral i :: DerivPath
let childPrvKey = derivePath ioCtx path xprvk
let childPubKey = deriveXPubKey ioCtx childPrvKey
let x = xPubAddr ioCtx childPubKey
case x of
PubKeyAddress k -> return $ TransparentAddress P2PKH $ fromBinary k

View File

@ -33,7 +33,6 @@ import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import qualified Data.Text.Lazy.Encoding as LE
import qualified Data.Text.Lazy.IO as LTIO
import GHC.Float.RealFracMethods (properFractionDoubleInteger)
import Test.Hspec
import Test.Hspec.QuickCheck
@ -42,6 +41,7 @@ import ZcashHaskell.Keys (generateWalletSeedPhrase, getWalletSeed)
import ZcashHaskell.Orchard
import ZcashHaskell.Sapling
( decodeSaplingOutput
, genSaplingInternalAddress
, genSaplingPaymentAddress
, genSaplingSpendingKey
, getShieldedOutputs
@ -60,6 +60,7 @@ import ZcashHaskell.Types
, Phrase(..)
, RawData(..)
, RawTxResponse(..)
, SaplingReceiver(..)
, SaplingSpendingKey(..)
, Scope(..)
, Seed(..)
@ -503,7 +504,7 @@ main = do
maybe "No transparent" (encodeTransparent (ua_net u)) $
t_rec u
msg `shouldBe` "t1LPWuQnjCRH7JAeEErSXKixcUteLJRJjKD"
it "Recover UA from YWallet:" $
it "Recover UA from YWallet" $
ioProperty $ do
let p =
Phrase
@ -517,10 +518,10 @@ main = do
Just s' -> do
let oK = genOrchardSpendingKey s' MainNetCoin 0
let sK = genSaplingSpendingKey s' MainNetCoin 0
let tK = genTransparentPrvKey s' 0
let tK = genTransparentPrvKey s' MainNetCoin 0
let oR = genOrchardReceiver 0 External =<< oK
let sR = genSaplingPaymentAddress 0 =<< sK
tR <- genTransparentReceiver 0 =<< tK
tR <- genTransparentReceiver 0 External =<< tK
let newUA = UnifiedAddress MainNet oR sR $ Just tR
return $ Just newUA `shouldBe` targetUA
it "Recover UA from Zingo:" $
@ -537,12 +538,233 @@ main = do
Just s' -> do
let oK = genOrchardSpendingKey s' MainNetCoin 0
let sK = genSaplingSpendingKey s' MainNetCoin 0
let tK = genTransparentPrvKey s' 0
let tK = genTransparentPrvKey s' MainNetCoin 0
let oR = genOrchardReceiver 0 External =<< oK
let sR = genSaplingPaymentAddress 0 =<< sK
tR <- genTransparentReceiver 0 =<< tK
tR <- genTransparentReceiver 0 External =<< tK
let newUA = UnifiedAddress MainNet oR sR $ Just tR
return $ Just newUA `shouldBe` targetUA
describe "Sapling Change Payment Address generation test" $ do
it "Call genSaplingInternalAddress" $ do
let sk =
[ 3
, 183
, 26
, 151
, 89
, 0
, 0
, 0
, 128
, 199
, 189
, 33
, 169
, 114
, 194
, 50
, 0
, 139
, 140
, 162
, 100
, 100
, 35
, 58
, 226
, 6
, 47
, 232
, 34
, 214
, 11
, 173
, 142
, 40
, 45
, 163
, 190
, 207
, 49
, 130
, 158
, 113
, 232
, 251
, 79
, 98
, 77
, 195
, 196
, 40
, 42
, 113
, 133
, 35
, 211
, 68
, 146
, 104
, 5
, 56
, 244
, 162
, 55
, 239
, 55
, 112
, 37
, 38
, 189
, 183
, 121
, 201
, 1
, 60
, 158
, 151
, 141
, 123
, 250
, 95
, 169
, 123
, 208
, 56
, 103
, 74
, 85
, 49
, 152
, 207
, 245
, 216
, 58
, 37
, 0
, 127
, 186
, 245
, 234
, 47
, 68
, 11
, 78
, 76
, 12
, 171
, 37
, 63
, 172
, 90
, 111
, 94
, 88
, 152
, 211
, 53
, 243
, 142
, 16
, 195
, 142
, 50
, 14
, 13
, 32
, 91
, 5
, 82
, 182
, 121
, 136
, 109
, 125
, 165
, 125
, 123
, 226
, 54
, 60
, 34
, 62
, 111
, 167
, 88
, 254
, 113
, 204
, 47
, 181
, 97
, 18
, 220
, 46
, 51
, 160
, 62
, 16
, 199
, 143
, 184
, 200
, 209
, 124
, 154
, 175
, 29
, 216
, 48
, 201
] :: [Word8]
let cAdr =
[ 31
, 232
, 31
, 17
, 196
, 178
, 208
, 227
, 206
, 199
, 105
, 55
, 147
, 23
, 151
, 206
, 117
, 59
, 249
, 162
, 218
, 140
, 189
, 17
, 60
, 116
, 106
, 56
, 64
, 203
, 152
, 52
, 155
, 133
, 179
, 118
, 47
, 161
, 70
, 155
, 21
, 22
, 41
] :: [Word8]
let bscAdr = SaplingReceiver $ BS.pack cAdr
let ca = genSaplingInternalAddress (SaplingSpendingKey $ BS.pack sk)
fromMaybe (SaplingReceiver "") ca `shouldBe` bscAdr
-- | Properties
prop_PhraseLength :: Property
@ -604,18 +826,18 @@ prop_OrchardRecRepeated s c (NonNegative i) (NonNegative j) scope =
scope
(fromMaybe (OrchardSpendingKey "") $ genOrchardSpendingKey s c i)
prop_TransparentSpendingKey :: Seed -> NonNegative Int -> Property
prop_TransparentSpendingKey s (NonNegative i) =
prop_TransparentSpendingKey :: Seed -> CoinType -> NonNegative Int -> Property
prop_TransparentSpendingKey s coinType (NonNegative i) =
ioProperty $ do
k <- genTransparentPrvKey s i
k <- genTransparentPrvKey s coinType i
return $ xPrvChild k == fromIntegral i
prop_TransparentReceiver ::
Seed -> NonNegative Int -> NonNegative Int -> Property
prop_TransparentReceiver s (NonNegative i) (NonNegative j) =
Seed -> CoinType -> Scope -> NonNegative Int -> NonNegative Int -> Property
prop_TransparentReceiver s coinType scope (NonNegative i) (NonNegative j) =
ioProperty $ do
k <- genTransparentPrvKey s i
r <- genTransparentReceiver j k
k <- genTransparentPrvKey s coinType i
r <- genTransparentReceiver j scope k
return $ ta_type r == P2PKH
-- | Generators