Compare commits

..

No commits in common. "0b1d9e09203ef214b61104de01412250fa2e5fd5" and "3cc0e96c448b41d3fc44c682546e121220e76e3b" have entirely different histories.

7 changed files with 13 additions and 67 deletions

View file

@ -55,7 +55,7 @@ rsFolder = "librustzcash-wrapper"
execCargo :: Verbosity -> String -> [String] -> IO () execCargo :: Verbosity -> String -> [String] -> IO ()
execCargo verbosity command args = do execCargo verbosity command args = do
cargoPath <- cargoPath <-
findProgramOnSearchPath Verbosity.normal defaultProgramSearchPath "cargo" findProgramOnSearchPath Verbosity.silent defaultProgramSearchPath "cargo"
dir <- getCurrentDirectory dir <- getCurrentDirectory
let cargoExec = let cargoExec =
case cargoPath of case cargoPath of

View file

@ -326,8 +326,8 @@ pub extern "C" fn rust_wrapper_bech32decode(
out_len: &mut usize out_len: &mut usize
) { ) {
let input: String = marshall_from_haskell_var(input, input_len, RW); let input: String = marshall_from_haskell_var(input, input_len, RW);
let decoded_bytes = bech32::decode(&input); let decodedBytes = bech32::decode(&input);
match decoded_bytes { match decodedBytes {
Ok((hrp, bytes)) => { Ok((hrp, bytes)) => {
let rd = RawData {hrp: hrp.as_bytes().to_vec(), bytes}; let rd = RawData {hrp: hrp.as_bytes().to_vec(), bytes};
marshall_to_haskell_var(&rd, out, out_len, RW); marshall_to_haskell_var(&rd, out, out_len, RW);

View file

@ -38,14 +38,6 @@ import ZcashHaskell.Types
-> `()' -> `()'
#} #}
{# fun unsafe rust_wrapper_bech32_encode as rustWrapperBech32Encode
{ toBorshVar* `BS.ByteString'&
, toBorshVar* `BS.ByteString'&
, getVarBuffer `Buffer (T.Text)'&
}
-> `()'
#}
{# fun unsafe rust_wrapper_f4jumble as rustWrapperF4Jumble {# fun unsafe rust_wrapper_f4jumble as rustWrapperF4Jumble
{ toBorshVar* `BS.ByteString'& { toBorshVar* `BS.ByteString'&
, getVarBuffer `Buffer (BS.ByteString)'& , getVarBuffer `Buffer (BS.ByteString)'&

View file

@ -1,5 +1,3 @@
{-# LANGUAGE OverloadedStrings #-}
-- Copyright 2022-2024 Vergara Technologies LLC -- Copyright 2022-2024 Vergara Technologies LLC
-- --
-- This file is part of Zcash-Haskell. -- This file is part of Zcash-Haskell.
@ -24,13 +22,8 @@ import C.Zcash
, rustWrapperUfvkDecode , rustWrapperUfvkDecode
) )
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import Data.Word
import Foreign.Rust.Marshall.Variable import Foreign.Rust.Marshall.Variable
import ZcashHaskell.Types import ZcashHaskell.Types
import ZcashHaskell.Utils (encodeBech32m, f4Jumble)
-- | Checks if given bytestring is a valid encoded unified address -- | Checks if given bytestring is a valid encoded unified address
isValidUnifiedAddress :: BS.ByteString -> Maybe UnifiedAddress isValidUnifiedAddress :: BS.ByteString -> Maybe UnifiedAddress
@ -56,33 +49,6 @@ isValidUnifiedAddress str =
then Just $ TransparentAddress P2SH whichNet (raw_to x) then Just $ TransparentAddress P2SH whichNet (raw_to x)
else Nothing) else Nothing)
-- | Encode a 'UnifiedAddress' per [ZIP-316](https://zips.z.cash/zip-0316)
encodeUnifiedAddress :: UnifiedAddress -> T.Text
encodeUnifiedAddress ua = encodeBech32m (E.encodeUtf8 hr) b
where
hr =
case ua_net ua of
MainNet -> "u"
TestNet -> "utest"
b = f4Jumble $ tReceiver <> sReceiver <> oReceiver <> padding
tReceiver =
case t_rec ua of
Nothing -> BS.empty
Just t ->
case ta_type t of
P2SH -> packReceiver 0x01 $ ta_bytes t
P2PKH -> packReceiver 0x00 $ ta_bytes t
sReceiver = packReceiver 0x02 $ s_rec ua
oReceiver = packReceiver 0x03 $ o_rec ua
padding = E.encodeUtf8 $ T.justifyLeft 16 '\NUL' hr
packReceiver :: Word8 -> BS.ByteString -> BS.ByteString
packReceiver typeCode receiver =
if BS.length receiver > 1
then BS.singleton typeCode `BS.append`
(BS.singleton . toEnum . BS.length) receiver `BS.append`
receiver
else BS.empty
-- | Attempts to decode the given bytestring into a Unified Full Viewing Key -- | Attempts to decode the given bytestring into a Unified Full Viewing Key
decodeUfvk :: BS.ByteString -> Maybe UnifiedFullViewingKey decodeUfvk :: BS.ByteString -> Maybe UnifiedFullViewingKey
decodeUfvk str = decodeUfvk str =

View file

@ -186,12 +186,12 @@ data TransparentAddress = TransparentAddress
-- * Sapling -- * Sapling
-- | Type to represent a Sapling Shielded Output as provided by the @getrawtransaction@ RPC method of @zcashd@. -- | Type to represent a Sapling Shielded Output as provided by the @getrawtransaction@ RPC method of @zcashd@.
data ShieldedOutput = ShieldedOutput data ShieldedOutput = ShieldedOutput
{ s_cv :: !HexString -- ^ Value commitment to the input note { s_cv :: HexString -- ^ Value commitment to the input note
, s_cmu :: !HexString -- ^ The u-coordinate of the note commitment for the output note , s_cmu :: HexString -- ^ The u-coordinate of the note commitment for the output note
, s_ephKey :: !HexString -- ^ Ephemeral Jubjub public key , s_ephKey :: HexString -- ^ Ephemeral Jubjub public key
, s_encCipherText :: !HexString -- ^ The output note encrypted to the recipient , s_encCipherText :: HexString -- ^ The output note encrypted to the recipient
, s_outCipherText :: !HexString -- ^ A ciphertext enabling the sender to recover the output note , s_outCipherText :: HexString -- ^ A ciphertext enabling the sender to recover the output note
, s_proof :: !HexString -- ^ Zero-knowledge proof using the Sapling Output circuit , s_proof :: HexString -- ^ Zero-knowledge proof using the Sapling Output circuit
} deriving stock (Eq, Prelude.Show, GHC.Generic) } deriving stock (Eq, Prelude.Show, GHC.Generic)
deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
deriving anyclass (Data.Structured.Show) deriving anyclass (Data.Structured.Show)

View file

@ -19,7 +19,6 @@ module ZcashHaskell.Utils where
import C.Zcash import C.Zcash
( rustWrapperBech32Decode ( rustWrapperBech32Decode
, rustWrapperBech32Encode
, rustWrapperF4Jumble , rustWrapperF4Jumble
, rustWrapperF4UnJumble , rustWrapperF4UnJumble
) )
@ -36,10 +35,6 @@ import ZcashHaskell.Types
decodeBech32 :: BS.ByteString -> RawData decodeBech32 :: BS.ByteString -> RawData
decodeBech32 = withPureBorshVarBuffer . rustWrapperBech32Decode decodeBech32 = withPureBorshVarBuffer . rustWrapperBech32Decode
-- | Encode the given Human Readable Part and bytestring as a Bech32m string
encodeBech32m :: BS.ByteString -> BS.ByteString -> T.Text
encodeBech32m h d = withPureBorshVarBuffer $ rustWrapperBech32Encode h d
-- | Apply the F4Jumble transformation to the given bytestring -- | Apply the F4Jumble transformation to the given bytestring
f4Jumble :: BS.ByteString -> BS.ByteString f4Jumble :: BS.ByteString -> BS.ByteString
f4Jumble = withPureBorshVarBuffer . rustWrapperF4Jumble f4Jumble = withPureBorshVarBuffer . rustWrapperF4Jumble

View file

@ -60,14 +60,11 @@ main :: IO ()
main = do main = do
hspec $ do hspec $ do
describe "Bech32" $ do describe "Bech32" $ do
let s = "abc14w46h2at4w46h2at4w46h2at4w46h2at958ngu" let s = "bech321qqqsyrhqy2a"
let decodedString = decodeBech32 s let decodedString = decodeBech32 s
it "hrp matches" $ do hrp decodedString `shouldBe` "abc" it "hrp matches" $ do hrp decodedString `shouldBe` "bech32"
xit "data matches" $ do it "data matches" $ do
bytes decodedString `shouldBe` BS.pack ([0x00, 0x01, 0x02] :: [Word8]) bytes decodedString `shouldBe` BS.pack ([0x00, 0x01, 0x02] :: [Word8])
it "encoding works" $ do
encodeBech32m "abc" (bytes decodedString) `shouldBe`
E.decodeUtf8Lenient s
describe "F4Jumble" $ do describe "F4Jumble" $ do
it "jumble a string" $ do it "jumble a string" $ do
let input = let input =
@ -340,11 +337,6 @@ main = do
let ua = let ua =
"u1salpdyefbreakingtheaddressh0h9v6qjr478k80amtkqkws5pr408lxt2953dpprvu06mahxt99cv65fgsm7sw8hlchplfg5pl89ur" "u1salpdyefbreakingtheaddressh0h9v6qjr478k80amtkqkws5pr408lxt2953dpprvu06mahxt99cv65fgsm7sw8hlchplfg5pl89ur"
isValidUnifiedAddress ua `shouldBe` Nothing isValidUnifiedAddress ua `shouldBe` Nothing
it "encodes UA correctly" $ do
let ua =
"u1salpdyefywvsg2dlmxg9589yznh0h9v6qjr478k80amtkqkws5pr408lxt2953dpprvu06mahxt99cv65fgsm7sw8hlchplfg5pl89ur"
(encodeUnifiedAddress <$> isValidUnifiedAddress ua) `shouldBe`
Just (E.decodeUtf8Lenient ua)
describe "Decode UVK from YWallet" $ do describe "Decode UVK from YWallet" $ do
let uvk = let uvk =
"uview1u833rp8yykd7h4druwht6xp6k8krle45fx8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm" "uview1u833rp8yykd7h4druwht6xp6k8krle45fx8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm"
@ -448,6 +440,7 @@ main = do
describe "Wallet seed phrase" $ do describe "Wallet seed phrase" $ do
it "Generate phrase" $ do it "Generate phrase" $ do
p <- generateWalletSeedPhrase p <- generateWalletSeedPhrase
print p
BS.length p `shouldNotBe` 0 BS.length p `shouldNotBe` 0
it "Derive seed" $ do it "Derive seed" $ do
p <- generateWalletSeedPhrase p <- generateWalletSeedPhrase