Correct Sapling receiver generation #32
5 changed files with 67 additions and 145 deletions
|
@ -59,11 +59,12 @@ use zcash_address::{
|
|||
};
|
||||
|
||||
use zcash_client_backend::keys::sapling::{
|
||||
spending_key,
|
||||
ExtendedFullViewingKey,
|
||||
ExtendedSpendingKey
|
||||
};
|
||||
|
||||
use zcash_primitives::zip32::{ AccountId, DiversifierIndex };
|
||||
use zcash_primitives::zip32::DiversifierIndex;
|
||||
|
||||
use orchard::{
|
||||
Action,
|
||||
|
@ -627,23 +628,16 @@ pub extern "C" fn rust_wrapper_recover_seed(
|
|||
|
||||
#[no_mangle]
|
||||
pub extern "C" fn rust_wrapper_sapling_spendingkey(
|
||||
iseed: *const u8,
|
||||
iseed_len: usize,
|
||||
ix: u32,
|
||||
seed: *const u8,
|
||||
seed_len: usize,
|
||||
coin_type: u32,
|
||||
acc_id: u32,
|
||||
out: *mut u8,
|
||||
out_len: &mut usize
|
||||
){
|
||||
let seed: Vec<u8> = marshall_from_haskell_var(iseed, iseed_len, RW);
|
||||
let su8 = &seed;
|
||||
let seedu8 : &[u8] = &su8;
|
||||
let extsk: ExtendedSpendingKey = ExtendedSpendingKey::master(&seedu8);
|
||||
if ix == 0 {
|
||||
let extsk_bytes = extsk.to_bytes().to_vec();
|
||||
marshall_to_haskell_var(&extsk_bytes, out, out_len, RW);
|
||||
} else {
|
||||
let child_sk = extsk.derive_child(ChildIndex::from_index(ix + (1 << 31)));
|
||||
marshall_to_haskell_var(&child_sk.to_bytes().to_vec(), out, out_len, RW);
|
||||
}
|
||||
let s: Vec<u8> = marshall_from_haskell_var(seed, seed_len, RW);
|
||||
let sk = spending_key(&s, coin_type, zcash_primitives::zip32::AccountId::try_from(acc_id).unwrap());
|
||||
marshall_to_haskell_var(&sk.to_bytes().to_vec(), out, out_len, RW);
|
||||
}
|
||||
|
||||
#[no_mangle]
|
||||
|
|
|
@ -137,6 +137,7 @@ import ZcashHaskell.Types
|
|||
{# fun unsafe rust_wrapper_sapling_spendingkey as rustWrapperSaplingSpendingkey
|
||||
{ toBorshVar* `BS.ByteString'&
|
||||
, `Word32'
|
||||
, `Word32'
|
||||
, getVarBuffer `Buffer (BS.ByteString)'&
|
||||
}
|
||||
-> `()'
|
||||
|
|
|
@ -46,6 +46,7 @@ import ZcashHaskell.Types
|
|||
, Seed(..)
|
||||
, ShieldedOutput(..)
|
||||
, decodeHexText
|
||||
, getValue
|
||||
)
|
||||
import ZcashHaskell.Utils (decodeBech32)
|
||||
|
||||
|
@ -95,15 +96,18 @@ instance FromJSON RawTxResponse where
|
|||
pure $ RawTxResponse i h (getShieldedOutputs h) a ht c b
|
||||
|
||||
-- | Attempts to obtain a sapling SpendingKey using a HDSeed
|
||||
genSaplingSpendingKey :: Seed -> Int -> Maybe SaplingSpendingKey
|
||||
genSaplingSpendingKey seed i = do
|
||||
genSaplingSpendingKey :: Seed -> CoinType -> Int -> Maybe SaplingSpendingKey
|
||||
genSaplingSpendingKey seed c i = do
|
||||
if BS.length res == 169
|
||||
then Just res
|
||||
else Nothing
|
||||
where
|
||||
res =
|
||||
withPureBorshVarBuffer
|
||||
(rustWrapperSaplingSpendingkey seed (fromIntegral i))
|
||||
(rustWrapperSaplingSpendingkey
|
||||
seed
|
||||
(fromIntegral $ getValue c)
|
||||
(fromIntegral i))
|
||||
|
||||
-- | Attempts to generate a sapling Payment Address using an ExtendedSpendingKey and a Diversifier Index
|
||||
genSaplingPaymentAddress :: Int -> SaplingSpendingKey -> Maybe SaplingReceiver
|
||||
|
|
|
@ -23,7 +23,9 @@ import Data.ByteString.Base58 (bitcoinAlphabet, encodeBase58)
|
|||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as E
|
||||
import ZcashHaskell.Types
|
||||
( TransparentAddress(..)
|
||||
( AccountId
|
||||
, Seed
|
||||
, TransparentAddress(..)
|
||||
, TransparentType(..)
|
||||
, ZcashNet(..)
|
||||
, getTransparentPrefix
|
||||
|
@ -51,21 +53,19 @@ encodeTransparent zNet t =
|
|||
checksum = sha256 $ sha256 digest
|
||||
|
||||
-- | Attempts to generate an Extended Private Key from a known HDSeed.
|
||||
genTransparentPrvKey :: BS.ByteString -> XPrvKey
|
||||
genTransparentPrvKey hdseed = do
|
||||
makeXPrvKey hdseed
|
||||
|
||||
-- | Attempts to obtain an Extended Public Key from a known Extended Private Key
|
||||
genTransparentPubKey :: XPrvKey -> IO XPubKey
|
||||
genTransparentPubKey xpvk = do
|
||||
genTransparentPrvKey :: Seed -> AccountId -> IO XPrvKey
|
||||
genTransparentPrvKey hdseed i = do
|
||||
let prvKey = makeXPrvKey hdseed
|
||||
ioCtx <- createContext
|
||||
let xpubk = deriveXPubKey ioCtx xpvk
|
||||
return xpubk
|
||||
return $ hardSubKey ioCtx prvKey (fromIntegral i)
|
||||
|
||||
genTransparentReceiver :: XPubKey -> IO TransparentAddress
|
||||
genTransparentReceiver xpubk = do
|
||||
-- | Generate a transparent receiver
|
||||
genTransparentReceiver :: Int -> XPrvKey -> IO TransparentAddress
|
||||
genTransparentReceiver i xprvk = do
|
||||
ioCtx <- createContext
|
||||
let x = xPubAddr ioCtx xpubk
|
||||
let rootPubKey = deriveXPubKey ioCtx xprvk
|
||||
let childPubKey = pubSubKey ioCtx rootPubKey (fromIntegral i)
|
||||
let x = xPubAddr ioCtx childPubKey
|
||||
case x of
|
||||
PubKeyAddress k -> return $ TransparentAddress P2PKH $ fromBinary k
|
||||
ScriptAddress j -> return $ TransparentAddress P2SH $ fromBinary j
|
||||
|
|
151
test/Spec.hs
151
test/Spec.hs
|
@ -50,8 +50,6 @@ import ZcashHaskell.Sapling
|
|||
, matchSaplingAddress
|
||||
)
|
||||
import ZcashHaskell.Transparent
|
||||
--(encodeTransparent)
|
||||
|
||||
import ZcashHaskell.Types
|
||||
( AccountId
|
||||
, BlockResponse(..)
|
||||
|
@ -64,6 +62,8 @@ import ZcashHaskell.Types
|
|||
, RawTxResponse(..)
|
||||
, Seed(..)
|
||||
, ShieldedOutput(..)
|
||||
, TransparentAddress(..)
|
||||
, TransparentType(..)
|
||||
, UnifiedAddress(..)
|
||||
, UnifiedFullViewingKey(..)
|
||||
, ZcashNet(..)
|
||||
|
@ -471,104 +471,12 @@ main = do
|
|||
describe "Wallet seed phrase" $ do
|
||||
prop "Generated phrases are valid" $ again prop_PhraseLength
|
||||
prop "Derived seeds are valid" $ again prop_SeedLength
|
||||
describe "Transparent Private and Public Key Generation" $ do
|
||||
it "Obtain a transparent extended private key from HDSeed" $ do
|
||||
let hdseed =
|
||||
[ 206
|
||||
, 61
|
||||
, 120
|
||||
, 38
|
||||
, 206
|
||||
, 40
|
||||
, 201
|
||||
, 62
|
||||
, 83
|
||||
, 175
|
||||
, 151
|
||||
, 131
|
||||
, 218
|
||||
, 141
|
||||
, 206
|
||||
, 254
|
||||
, 28
|
||||
, 244
|
||||
, 172
|
||||
, 213
|
||||
, 128
|
||||
, 248
|
||||
, 156
|
||||
, 45
|
||||
, 204
|
||||
, 44
|
||||
, 169
|
||||
, 3
|
||||
, 162
|
||||
, 188
|
||||
, 16
|
||||
, 173
|
||||
, 192
|
||||
, 164
|
||||
, 96
|
||||
, 148
|
||||
, 91
|
||||
, 52
|
||||
, 244
|
||||
, 83
|
||||
, 149
|
||||
, 169
|
||||
, 82
|
||||
, 196
|
||||
, 199
|
||||
, 53
|
||||
, 177
|
||||
, 170
|
||||
, 1
|
||||
, 6
|
||||
, 0
|
||||
, 120
|
||||
, 170
|
||||
, 2
|
||||
, 238
|
||||
, 219
|
||||
, 241
|
||||
, 243
|
||||
, 172
|
||||
, 178
|
||||
, 104
|
||||
, 81
|
||||
, 159
|
||||
, 144
|
||||
] :: [Word8]
|
||||
let xtpvk = genTransparentPrvKey (BS.pack hdseed)
|
||||
let testpvk =
|
||||
XPrvKey
|
||||
0
|
||||
"0000000000"
|
||||
0
|
||||
"fb5b9b89d3e9dfdebeaabd15de8fbc7e9a140b7f2de2b4034c2573425d39aceb"
|
||||
"46aa0cd24a6e05709591426a4e682dd5406de4e75a39c0f410ee790403880943"
|
||||
xtpvk `shouldBe` testpvk
|
||||
it "Obtain a transparent extended public key from private key" $ do
|
||||
let testpvk =
|
||||
XPrvKey
|
||||
0
|
||||
"0000000000"
|
||||
0
|
||||
"fb5b9b89d3e9dfdebeaabd15de8fbc7e9a140b7f2de2b4034c2573425d39aceb"
|
||||
"46aa0cd24a6e05709591426a4e682dd5406de4e75a39c0f410ee790403880943"
|
||||
let testpbk =
|
||||
XPubKey
|
||||
0
|
||||
"00000000"
|
||||
0
|
||||
"fb5b9b89d3e9dfdebeaabd15de8fbc7e9a140b7f2de2b4034c2573425d39aceb"
|
||||
"279bda9c704f6da479cedb12c7cf773b3a348569dc1cfa6002526bad67674fd737b84a2bdb1199ecab1c9fed1b9a38aba5ba19259c1510d733a2376118515cd8"
|
||||
let xtpubkIO = genTransparentPubKey testpvk
|
||||
xtpubk <- xtpubkIO
|
||||
---print $ show xtpubk
|
||||
xtpubk `shouldBe` testpbk
|
||||
before getSeed $
|
||||
describe "Optimized spending key tests" $ do
|
||||
it "Transparent spending keys are valid" $ \s ->
|
||||
property $ prop_TransparentSpendingKey s
|
||||
it "Transparent receivers are valid" $ \s ->
|
||||
property $ prop_TransparentReceiver s
|
||||
it "Sapling spending keys are valid" $ \s ->
|
||||
property $ prop_SaplingSpendingKey s
|
||||
it "Sapling receivers are valid" $ \s ->
|
||||
|
@ -604,11 +512,11 @@ main = do
|
|||
Nothing -> return $ expectationFailure "Failed to generate seed"
|
||||
Just s' -> do
|
||||
let oK = genOrchardSpendingKey s' MainNetCoin 0
|
||||
let sK = genSaplingSpendingKey s' 0
|
||||
let tK = genTransparentPrvKey s'
|
||||
let sK = genSaplingSpendingKey s' MainNetCoin 0
|
||||
let tK = genTransparentPrvKey s' 0
|
||||
let oR = genOrchardReceiver 0 =<< oK
|
||||
let sR = genSaplingPaymentAddress 0 =<< sK
|
||||
tR <- genTransparentReceiver =<< genTransparentPubKey tK
|
||||
tR <- genTransparentReceiver 0 =<< tK
|
||||
let newUA = UnifiedAddress MainNet oR sR $ Just tR
|
||||
return $ Just newUA `shouldBe` targetUA
|
||||
it "Recover UA from Zingo" $
|
||||
|
@ -623,11 +531,11 @@ main = do
|
|||
Nothing -> return $ expectationFailure "Failed to generate seed"
|
||||
Just s' -> do
|
||||
let oK = genOrchardSpendingKey s' MainNetCoin 0
|
||||
let sK = genSaplingSpendingKey s' 0
|
||||
let tK = genTransparentPrvKey s'
|
||||
let sK = genSaplingSpendingKey s' MainNetCoin 0
|
||||
let tK = genTransparentPrvKey s' 0
|
||||
let oR = genOrchardReceiver 0 =<< oK
|
||||
let sR = genSaplingPaymentAddress 0 =<< sK
|
||||
tR <- genTransparentReceiver =<< genTransparentPubKey tK
|
||||
tR <- genTransparentReceiver 0 =<< tK
|
||||
let newUA = UnifiedAddress MainNet oR sR $ Just tR
|
||||
return $ Just newUA `shouldBe` targetUA
|
||||
|
||||
|
@ -654,19 +562,20 @@ prop_OrchardReceiver ::
|
|||
prop_OrchardReceiver s c (NonNegative i) (NonNegative j) =
|
||||
genOrchardReceiver j (fromMaybe "" $ genOrchardSpendingKey s c i) =/= Nothing
|
||||
|
||||
prop_SaplingSpendingKey :: Seed -> NonNegative Int -> Property
|
||||
prop_SaplingSpendingKey s (NonNegative i) =
|
||||
genSaplingSpendingKey s i =/= Nothing
|
||||
prop_SaplingSpendingKey :: Seed -> CoinType -> NonNegative Int -> Property
|
||||
prop_SaplingSpendingKey s c (NonNegative i) =
|
||||
genSaplingSpendingKey s c i =/= Nothing
|
||||
|
||||
prop_SaplingReceiver :: Seed -> NonNegative Int -> NonNegative Int -> Property
|
||||
prop_SaplingReceiver s (NonNegative i) (NonNegative j) =
|
||||
genSaplingPaymentAddress i (fromMaybe "" $ genSaplingSpendingKey s j) =/=
|
||||
prop_SaplingReceiver ::
|
||||
Seed -> CoinType -> NonNegative Int -> NonNegative Int -> Property
|
||||
prop_SaplingReceiver s c (NonNegative i) (NonNegative j) =
|
||||
genSaplingPaymentAddress i (fromMaybe "" $ genSaplingSpendingKey s c j) =/=
|
||||
Nothing
|
||||
|
||||
prop_SaplingRecRepeated :: Seed -> NonNegative Int -> Property
|
||||
prop_SaplingRecRepeated s (NonNegative i) =
|
||||
genSaplingPaymentAddress i (fromMaybe "" $ genSaplingSpendingKey s 1) =/=
|
||||
genSaplingPaymentAddress (i + 1) (fromMaybe "" $ genSaplingSpendingKey s 1)
|
||||
prop_SaplingRecRepeated :: Seed -> CoinType -> NonNegative Int -> Property
|
||||
prop_SaplingRecRepeated s c (NonNegative i) =
|
||||
genSaplingPaymentAddress i (fromMaybe "" $ genSaplingSpendingKey s c 1) =/=
|
||||
genSaplingPaymentAddress (i + 1) (fromMaybe "" $ genSaplingSpendingKey s c 1)
|
||||
|
||||
prop_OrchardRecRepeated ::
|
||||
Seed -> CoinType -> NonNegative Int -> NonNegative Int -> Property
|
||||
|
@ -674,6 +583,20 @@ prop_OrchardRecRepeated s c (NonNegative i) (NonNegative j) =
|
|||
genOrchardReceiver j (fromMaybe "" $ genOrchardSpendingKey s c i) =/=
|
||||
genOrchardReceiver (j + 1) (fromMaybe "" $ genOrchardSpendingKey s c i)
|
||||
|
||||
prop_TransparentSpendingKey :: Seed -> NonNegative Int -> Property
|
||||
prop_TransparentSpendingKey s (NonNegative i) =
|
||||
ioProperty $ do
|
||||
k <- genTransparentPrvKey s i
|
||||
return $ xPrvChild k == fromIntegral i
|
||||
|
||||
prop_TransparentReceiver ::
|
||||
Seed -> NonNegative Int -> NonNegative Int -> Property
|
||||
prop_TransparentReceiver s (NonNegative i) (NonNegative j) =
|
||||
ioProperty $ do
|
||||
k <- genTransparentPrvKey s i
|
||||
r <- genTransparentReceiver j k
|
||||
return $ ta_type r == P2PKH
|
||||
|
||||
-- | Generators
|
||||
genOrcArgs :: Gen (CoinType, Int, Int)
|
||||
genOrcArgs = do
|
||||
|
|
Loading…
Reference in a new issue