Correct Sapling receiver generation #32
2 changed files with 37 additions and 115 deletions
|
@ -23,7 +23,9 @@ import Data.ByteString.Base58 (bitcoinAlphabet, encodeBase58)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as E
|
import qualified Data.Text.Encoding as E
|
||||||
import ZcashHaskell.Types
|
import ZcashHaskell.Types
|
||||||
( TransparentAddress(..)
|
( AccountId
|
||||||
|
, Seed
|
||||||
|
, TransparentAddress(..)
|
||||||
, TransparentType(..)
|
, TransparentType(..)
|
||||||
, ZcashNet(..)
|
, ZcashNet(..)
|
||||||
, getTransparentPrefix
|
, getTransparentPrefix
|
||||||
|
@ -51,21 +53,19 @@ encodeTransparent zNet t =
|
||||||
checksum = sha256 $ sha256 digest
|
checksum = sha256 $ sha256 digest
|
||||||
|
|
||||||
-- | Attempts to generate an Extended Private Key from a known HDSeed.
|
-- | Attempts to generate an Extended Private Key from a known HDSeed.
|
||||||
genTransparentPrvKey :: BS.ByteString -> XPrvKey
|
genTransparentPrvKey :: Seed -> AccountId -> IO XPrvKey
|
||||||
genTransparentPrvKey hdseed = do
|
genTransparentPrvKey hdseed i = do
|
||||||
makeXPrvKey hdseed
|
let prvKey = makeXPrvKey hdseed
|
||||||
|
|
||||||
-- | Attempts to obtain an Extended Public Key from a known Extended Private Key
|
|
||||||
genTransparentPubKey :: XPrvKey -> IO XPubKey
|
|
||||||
genTransparentPubKey xpvk = do
|
|
||||||
ioCtx <- createContext
|
ioCtx <- createContext
|
||||||
let xpubk = deriveXPubKey ioCtx xpvk
|
return $ hardSubKey ioCtx prvKey (fromIntegral i)
|
||||||
return xpubk
|
|
||||||
|
|
||||||
genTransparentReceiver :: XPubKey -> IO TransparentAddress
|
-- | Generate a transparent receiver
|
||||||
genTransparentReceiver xpubk = do
|
genTransparentReceiver :: Int -> XPrvKey -> IO TransparentAddress
|
||||||
|
genTransparentReceiver i xprvk = do
|
||||||
ioCtx <- createContext
|
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
|
case x of
|
||||||
PubKeyAddress k -> return $ TransparentAddress P2PKH $ fromBinary k
|
PubKeyAddress k -> return $ TransparentAddress P2PKH $ fromBinary k
|
||||||
ScriptAddress j -> return $ TransparentAddress P2SH $ fromBinary j
|
ScriptAddress j -> return $ TransparentAddress P2SH $ fromBinary j
|
||||||
|
|
126
test/Spec.hs
126
test/Spec.hs
|
@ -50,8 +50,6 @@ import ZcashHaskell.Sapling
|
||||||
, matchSaplingAddress
|
, matchSaplingAddress
|
||||||
)
|
)
|
||||||
import ZcashHaskell.Transparent
|
import ZcashHaskell.Transparent
|
||||||
--(encodeTransparent)
|
|
||||||
|
|
||||||
import ZcashHaskell.Types
|
import ZcashHaskell.Types
|
||||||
( AccountId
|
( AccountId
|
||||||
, BlockResponse(..)
|
, BlockResponse(..)
|
||||||
|
@ -64,6 +62,8 @@ import ZcashHaskell.Types
|
||||||
, RawTxResponse(..)
|
, RawTxResponse(..)
|
||||||
, Seed(..)
|
, Seed(..)
|
||||||
, ShieldedOutput(..)
|
, ShieldedOutput(..)
|
||||||
|
, TransparentAddress(..)
|
||||||
|
, TransparentType(..)
|
||||||
, UnifiedAddress(..)
|
, UnifiedAddress(..)
|
||||||
, UnifiedFullViewingKey(..)
|
, UnifiedFullViewingKey(..)
|
||||||
, ZcashNet(..)
|
, ZcashNet(..)
|
||||||
|
@ -471,104 +471,12 @@ main = do
|
||||||
describe "Wallet seed phrase" $ do
|
describe "Wallet seed phrase" $ do
|
||||||
prop "Generated phrases are valid" $ again prop_PhraseLength
|
prop "Generated phrases are valid" $ again prop_PhraseLength
|
||||||
prop "Derived seeds are valid" $ again prop_SeedLength
|
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 $
|
before getSeed $
|
||||||
describe "Optimized spending key tests" $ do
|
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 ->
|
it "Sapling spending keys are valid" $ \s ->
|
||||||
property $ prop_SaplingSpendingKey s
|
property $ prop_SaplingSpendingKey s
|
||||||
it "Sapling receivers are valid" $ \s ->
|
it "Sapling receivers are valid" $ \s ->
|
||||||
|
@ -605,10 +513,10 @@ main = do
|
||||||
Just s' -> do
|
Just s' -> do
|
||||||
let oK = genOrchardSpendingKey s' MainNetCoin 0
|
let oK = genOrchardSpendingKey s' MainNetCoin 0
|
||||||
let sK = genSaplingSpendingKey s' MainNetCoin 0
|
let sK = genSaplingSpendingKey s' MainNetCoin 0
|
||||||
let tK = genTransparentPrvKey s'
|
let tK = genTransparentPrvKey s' 0
|
||||||
let oR = genOrchardReceiver 0 =<< oK
|
let oR = genOrchardReceiver 0 =<< oK
|
||||||
let sR = genSaplingPaymentAddress 0 =<< sK
|
let sR = genSaplingPaymentAddress 0 =<< sK
|
||||||
tR <- genTransparentReceiver =<< genTransparentPubKey tK
|
tR <- genTransparentReceiver 0 =<< tK
|
||||||
let newUA = UnifiedAddress MainNet oR sR $ Just tR
|
let newUA = UnifiedAddress MainNet oR sR $ Just tR
|
||||||
return $ Just newUA `shouldBe` targetUA
|
return $ Just newUA `shouldBe` targetUA
|
||||||
it "Recover UA from Zingo" $
|
it "Recover UA from Zingo" $
|
||||||
|
@ -624,10 +532,10 @@ main = do
|
||||||
Just s' -> do
|
Just s' -> do
|
||||||
let oK = genOrchardSpendingKey s' MainNetCoin 0
|
let oK = genOrchardSpendingKey s' MainNetCoin 0
|
||||||
let sK = genSaplingSpendingKey s' MainNetCoin 0
|
let sK = genSaplingSpendingKey s' MainNetCoin 0
|
||||||
let tK = genTransparentPrvKey s'
|
let tK = genTransparentPrvKey s' 0
|
||||||
let oR = genOrchardReceiver 0 =<< oK
|
let oR = genOrchardReceiver 0 =<< oK
|
||||||
let sR = genSaplingPaymentAddress 0 =<< sK
|
let sR = genSaplingPaymentAddress 0 =<< sK
|
||||||
tR <- genTransparentReceiver =<< genTransparentPubKey tK
|
tR <- genTransparentReceiver 0 =<< tK
|
||||||
let newUA = UnifiedAddress MainNet oR sR $ Just tR
|
let newUA = UnifiedAddress MainNet oR sR $ Just tR
|
||||||
return $ Just newUA `shouldBe` targetUA
|
return $ Just newUA `shouldBe` targetUA
|
||||||
|
|
||||||
|
@ -675,6 +583,20 @@ prop_OrchardRecRepeated s c (NonNegative i) (NonNegative j) =
|
||||||
genOrchardReceiver j (fromMaybe "" $ genOrchardSpendingKey s c i) =/=
|
genOrchardReceiver j (fromMaybe "" $ genOrchardSpendingKey s c i) =/=
|
||||||
genOrchardReceiver (j + 1) (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
|
-- | Generators
|
||||||
genOrcArgs :: Gen (CoinType, Int, Int)
|
genOrcArgs :: Gen (CoinType, Int, Int)
|
||||||
genOrcArgs = do
|
genOrcArgs = do
|
||||||
|
|
Loading…
Reference in a new issue