zcash-haskell/test/Spec.hs

947 lines
85 KiB
Haskell
Raw Normal View History

2023-12-20 20:03:42 +00:00
{- Copyright 2022-2024 Vergara Technologies LLC
This file is part of Zcash-Haskell.
Zcash-Haskell is free software: you can redistribute it and/or modify it
under the terms of the GNU Lesser General Public License as published by the Free
Software Foundation, either version 3 of the License, or (at your option) any
later version.
Zcash-Haskell is distributed in the hope that it will be useful, but WITHOUT
ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more
details.
You should have received a copy of the GNU Lesser General Public License along with
Zcash-Haskell. If not, see <https://www.gnu.org/licenses/>.
-}
2023-04-13 23:35:15 +00:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeSynonymInstances #-}
2023-04-13 23:35:15 +00:00
2024-01-12 15:46:26 +00:00
import C.Zcash (rustWrapperUADecode)
2024-03-11 20:23:29 +00:00
import Control.Exception (throwIO)
2024-03-05 21:09:35 +00:00
import Control.Monad.IO.Class (liftIO)
2023-08-21 14:57:45 +00:00
import Data.Aeson
import Data.Bool (Bool(True))
2023-04-13 23:35:15 +00:00
import qualified Data.ByteString as BS
import Data.Either (isRight)
import Data.Foldable (sequenceA_)
2024-02-06 19:10:06 +00:00
import Data.HexString
2024-01-12 15:46:26 +00:00
import Data.Maybe
2023-08-21 14:57:45 +00:00
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
2023-08-21 14:57:45 +00:00
import qualified Data.Text.Lazy.Encoding as LE
import qualified Data.Text.Lazy.IO as LTIO
import Data.Word
import Foreign.C.Types
import GHC.Float.RealFracMethods (properFractionDoubleInteger)
import Haskoin.Crypto.Hash (ripemd160)
import Haskoin.Crypto.Keys.Extended
import Haskoin.Transaction.Common
import Test.HUnit
import Test.Hspec
import Test.Hspec.QuickCheck
import Test.QuickCheck
import ZcashHaskell.Keys (generateWalletSeedPhrase, getWalletSeed)
import ZcashHaskell.Orchard
import ZcashHaskell.Sapling
2023-08-22 20:05:40 +00:00
( decodeSaplingOutput
, genSaplingInternalAddress
2024-03-10 12:47:26 +00:00
, genSaplingPaymentAddress
, genSaplingSpendingKey
2023-09-27 15:37:53 +00:00
, getShieldedOutputs
2023-08-22 20:05:40 +00:00
, isValidSaplingViewingKey
, isValidShieldedAddress
, matchSaplingAddress
)
2024-03-10 12:47:26 +00:00
import ZcashHaskell.Transparent
import ZcashHaskell.Types
2024-03-10 12:47:26 +00:00
( AccountId
, BlockResponse(..)
2024-03-05 21:09:35 +00:00
, CoinType(..)
2023-08-22 20:05:40 +00:00
, DecodedNote(..)
2023-08-21 14:57:45 +00:00
, OrchardAction(..)
2024-03-14 17:35:13 +00:00
, OrchardSpendingKey(..)
, Phrase(..)
, RawData(..)
, RawOutPoint(..)
, RawTBundle(..)
, RawTxIn(..)
, RawTxOut(..)
2023-08-21 14:57:45 +00:00
, RawTxResponse(..)
, RawZebraTx(..)
2024-03-15 15:11:27 +00:00
, SaplingReceiver(..)
, SaplingSpendingKey(..)
, Scope(..)
2024-03-11 20:23:29 +00:00
, Seed(..)
2023-08-23 20:20:01 +00:00
, ShieldedOutput(..)
, ToBytes(..)
, TransparentAddress(..)
, TransparentBundle(..)
, TransparentType(..)
2024-01-12 15:46:26 +00:00
, UnifiedAddress(..)
, UnifiedFullViewingKey(..)
, ZcashNet(..)
, ZebraTxResponse(..)
2023-08-21 20:58:12 +00:00
, decodeHexText
, fromRawOBundle
, fromRawSBundle
, fromRawTBundle
, getValue
)
import ZcashHaskell.Utils
2023-04-13 23:35:15 +00:00
2024-03-10 12:47:26 +00:00
m2bs :: Maybe BS.ByteString -> BS.ByteString
m2bs x = fromMaybe "" x
2023-04-13 23:35:15 +00:00
main :: IO ()
main = do
hspec $ do
2023-06-14 14:55:52 +00:00
describe "Bech32" $ do
2024-03-04 17:59:07 +00:00
let s = "abc14w46h2at4w46h2at4w46h2at4w46h2at958ngu"
2023-06-14 14:55:52 +00:00
let decodedString = decodeBech32 s
2024-03-04 17:59:07 +00:00
it "hrp matches" $ do hrp decodedString `shouldBe` "abc"
xit "data matches" $ do
2023-06-14 14:55:52 +00:00
bytes decodedString `shouldBe` BS.pack ([0x00, 0x01, 0x02] :: [Word8])
2024-03-04 17:59:07 +00:00
it "encoding works" $ do
encodeBech32m "abc" (bytes decodedString) `shouldBe`
E.decodeUtf8Lenient s
2023-04-13 23:35:15 +00:00
describe "F4Jumble" $ do
it "jumble a string" $ do
let input =
[ 0x5d
, 0x7a
, 0x8f
, 0x73
, 0x9a
, 0x2d
, 0x9e
, 0x94
, 0x5b
, 0x0c
, 0xe1
, 0x52
, 0xa8
, 0x04
, 0x9e
, 0x29
, 0x4c
, 0x4d
, 0x6e
, 0x66
, 0xb1
, 0x64
, 0x93
, 0x9d
, 0xaf
, 0xfa
, 0x2e
, 0xf6
, 0xee
, 0x69
, 0x21
, 0x48
, 0x1c
, 0xdd
, 0x86
, 0xb3
, 0xcc
, 0x43
, 0x18
, 0xd9
, 0x61
, 0x4f
, 0xc8
, 0x20
, 0x90
, 0x5d
, 0x04
, 0x2b
] :: [Word8]
let out =
[ 0x03
, 0x04
, 0xd0
, 0x29
, 0x14
, 0x1b
, 0x99
, 0x5d
, 0xa5
, 0x38
, 0x7c
, 0x12
, 0x59
, 0x70
, 0x67
, 0x35
, 0x04
, 0xd6
, 0xc7
, 0x64
, 0xd9
, 0x1e
, 0xa6
, 0xc0
, 0x82
, 0x12
, 0x37
, 0x70
, 0xc7
, 0x13
, 0x9c
, 0xcd
, 0x88
, 0xee
, 0x27
, 0x36
, 0x8c
, 0xd0
, 0xc0
, 0x92
, 0x1a
, 0x04
, 0x44
, 0xc8
, 0xe5
, 0x85
, 0x8d
, 0x22
] :: [Word8]
BS.pack out `shouldBe` f4Jumble (BS.pack input)
it "unjumble a string" $ do
let input =
[ 0x5d
, 0x7a
, 0x8f
, 0x73
, 0x9a
, 0x2d
, 0x9e
, 0x94
, 0x5b
, 0x0c
, 0xe1
, 0x52
, 0xa8
, 0x04
, 0x9e
, 0x29
, 0x4c
, 0x4d
, 0x6e
, 0x66
, 0xb1
, 0x64
, 0x93
, 0x9d
, 0xaf
, 0xfa
, 0x2e
, 0xf6
, 0xee
, 0x69
, 0x21
, 0x48
, 0x1c
, 0xdd
, 0x86
, 0xb3
, 0xcc
, 0x43
, 0x18
, 0xd9
, 0x61
, 0x4f
, 0xc8
, 0x20
, 0x90
, 0x5d
, 0x04
, 0x2b
] :: [Word8]
let out =
[ 0x03
, 0x04
, 0xd0
, 0x29
, 0x14
, 0x1b
, 0x99
, 0x5d
, 0xa5
, 0x38
, 0x7c
, 0x12
, 0x59
, 0x70
, 0x67
, 0x35
, 0x04
, 0xd6
, 0xc7
, 0x64
, 0xd9
, 0x1e
, 0xa6
, 0xc0
, 0x82
, 0x12
, 0x37
, 0x70
, 0xc7
, 0x13
, 0x9c
, 0xcd
, 0x88
, 0xee
, 0x27
, 0x36
, 0x8c
, 0xd0
, 0xc0
, 0x92
, 0x1a
, 0x04
, 0x44
, 0xc8
, 0xe5
, 0x85
, 0x8d
, 0x22
] :: [Word8]
f4UnJumble (BS.pack out) `shouldBe` BS.pack input
2023-08-21 14:57:45 +00:00
describe "JSON parsing" $ do
it "block response" $ do
j <- LTIO.readFile "block.json"
let p = eitherDecode $ LE.encodeUtf8 j :: Either String BlockResponse
case p of
Left s -> s `shouldBe` ""
Right x -> bl_height x `shouldBe` 2196277
it "raw transaction response" $ do
j <- LTIO.readFile "tx.json"
let t = eitherDecode $ LE.encodeUtf8 j :: Either String RawTxResponse
case t of
Left s -> s `shouldBe` ""
Right x ->
2024-02-06 19:10:06 +00:00
toText (rt_id x) `shouldBe`
2023-08-21 14:57:45 +00:00
"5242b51f22a7d6fe9dee237137271cde704d306a5fff6a862bffaebb6f0e7e56"
describe "Seeds" $ do
it "generate seed phrase" $ do
s <- generateWalletSeedPhrase
BS.length (getBytes s) `shouldNotBe` 0
it "get seed from phrase" $ do
s <- generateWalletSeedPhrase
let x = getWalletSeed s
let result =
case x of
Nothing -> False
Just s' -> True
result `shouldBe` True
2023-06-14 14:55:52 +00:00
describe "Sapling address" $ do
it "succeeds with valid address" $ do
let sa =
"zs17faa6l5ma55s55exq9rnr32tu0wl8nmqg7xp3e6tz0m5ajn2a6yxlc09t03mqdmvyphavvf3sl8"
isValidShieldedAddress sa `shouldBe` True
it "fails with invalid address" $ do
let sa =
"zs17faa6l5ma55s55exq9rnr32tu0wl8nmqg7xp3e6tz0m5ajn2a6yxlc09t03mqdmvyphavvffake"
isValidShieldedAddress sa `shouldBe` False
describe "Decode Sapling VK" $ do
let vk =
"zxviews1qdjagrrpqqqqpq8es75mlu6rref0qyrstchf8dxzeygtsejwfqu8ckhwl2qj5m8am7lmupxk3vkvdjm8pawjpmesjfapvsqw96pa46c2z0kk7letrxf7mkltwz54fwpxc7kc79mm5kce3rwn5ssl009zwsra2spppwgrx25s9k5hq65f69l4jz2tjmqgy0pl49qmtaj3nudk6wglwe2hpa327hydlchtyq9av6wjd6hu68e04ahwk9a9n2kt0kj3nj99nue65awtu5cwwcpjs"
let sa =
"zs1g2ne5w2r8kvalwzngsk3kfzppx3qcx5560pnfmw9rj5xfd3zfg9dkm7hyxnfyhc423fev5wuue4"
let sa' =
"zs17faa6l5ma55s55exq9rnr32tu0wl8nmqg7xp3e6tz0m5ajn2a6yxlc09t03mqdmvyphavvf3sl8"
2023-06-14 14:55:52 +00:00
let rawKey = decodeBech32 vk
let rawSa = decodeBech32 sa
let rawSa' = decodeBech32 sa'
2023-06-14 14:55:52 +00:00
it "is mainnet" $ do hrp rawKey `shouldBe` "zxviews"
2023-06-15 00:09:43 +00:00
it "is valid Sapling extended full viewing key" $ do
isValidSaplingViewingKey vk `shouldBe` True
it "matches the right Sapling address" $ do
matchSaplingAddress (bytes rawKey) (bytes rawSa) `shouldBe` True
it "doesn't match the wrong Sapling address" $ do
matchSaplingAddress (bytes rawKey) (bytes rawSa') `shouldBe` False
2023-06-14 14:55:52 +00:00
describe "Decode invalid Sapling VK" $ do
let vk =
"zxviews1qdjagrrpqqqqpq8es75mlu6rref0qyrstchf8dxzeygtsejwfqu8ckhwl2qj5m8am7lmupxk3vkvdjm8pawjpmesjfapvsqw96pa46c2z0kk7letrxf7mkltwz54fwpxc7kc79mm5kce3rwn5ssl009zwsra2spppwgrx25s9k5hq65f69l4jz2tjmqgy0pl49qmtaj3nudk6wglwe2hpa327hydlchtyq9av6wjd6hu68e04ahwk9a9n2kt0kj3nj99nue65awtu5cwwfake"
let rawKey = decodeBech32 vk
it "is not mainnet" $ do hrp rawKey `shouldBe` "fail"
2023-04-13 23:35:15 +00:00
describe "Unified address" $ do
it "succeeds with correct UA" $ do
let ua =
"u1salpdyefywvsg2dlmxg9589yznh0h9v6qjr478k80amtkqkws5pr408lxt2953dpprvu06mahxt99cv65fgsm7sw8hlchplfg5pl89ur"
2024-01-12 15:46:26 +00:00
isJust (isValidUnifiedAddress ua) `shouldBe` True
2023-04-13 23:35:15 +00:00
it "fails with incorrect UA" $ do
let ua =
"u1salpdyefbreakingtheaddressh0h9v6qjr478k80amtkqkws5pr408lxt2953dpprvu06mahxt99cv65fgsm7sw8hlchplfg5pl89ur"
2024-01-12 15:46:26 +00:00
isValidUnifiedAddress ua `shouldBe` Nothing
2024-03-04 17:59:07 +00:00
it "encodes UA correctly" $ do
let ua =
"u1salpdyefywvsg2dlmxg9589yznh0h9v6qjr478k80amtkqkws5pr408lxt2953dpprvu06mahxt99cv65fgsm7sw8hlchplfg5pl89ur"
(encodeUnifiedAddress <$> isValidUnifiedAddress ua) `shouldBe`
Just (E.decodeUtf8Lenient ua)
2023-05-04 14:23:05 +00:00
describe "Decode UVK from YWallet" $ do
let uvk =
"uview1u833rp8yykd7h4druwht6xp6k8krle45fx8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm"
let res = decodeUfvk uvk
it "is mainnet" $ do maybe 0 net res `shouldBe` 1
it "has Orchard key" $ do BS.length (maybe "" o_key res) `shouldBe` 96
it "has Sapling key" $ do BS.length (maybe "" s_key res) `shouldBe` 128
it "does not have Transparent key" $ do
BS.length (maybe "" t_key res) `shouldBe` 1
describe "Decode bad UVK" $ do
it "should fail" $ do
let fakeUvk =
"uview1u83changinga987bundchofch4ract3r5x8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm"
decodeUfvk fakeUvk `shouldBe` Nothing
describe "Check if UA and UVK match" $ do
let ua =
"u15hjz9v46azzmdept050heh8795qxzwy2pykg097lg69jpk4qzah90cj2q4amq0c07gta60x8qgw00qewcy3hg9kv9h6zjkh3jc66vr40u6uu2dxmqkqhypud95vm0gq7y5ga7c8psdqgthsrwvgd676a2pavpcd4euwwapgackxa3qhvga0wnl0k6vncskxlq94vqwjd7zepy3qd5jh"
let ua' =
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
let uvk =
"uview1u833rp8yykd7h4druwht6xp6k8krle45fx8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm"
it "succeeds with correct address" $ do
matchOrchardAddress uvk ua `shouldBe` True
it "fails with wrong address" $ do
matchOrchardAddress uvk ua' `shouldBe` False
2023-08-21 20:58:12 +00:00
describe "Decode Sapling tx" $ do
let svk =
"zxviews1qvapd723qqqqpqq09ldgykvyusthmkky2w062esx5xg3nz4m29qxcvndyx6grrhrdepu4ns88sjr3u6mfp2hhwj5hfd6y24r0f64uwq65vjrmsh9mr568kenk33fcumag6djcjywkm5v295egjuk3qdd47atprs0j33nhaaqep3uqspzp5kg4mthugvug0sc3gc83atkrgmguw9g7gkvh82tugrntf66lnvyeh6ufh4j2xt0xr2r4zujtm3qvrmd3vvnulycuwqtetg2jk384"
2023-08-23 20:20:01 +00:00
let badvk =
"zxviews1qvapd723ffakeqq09ldgykvyusthmkky2w062esx5xg3nz4m29qxcvndyx6grrhrdepu4ns88sjr3u6mfp2hhwj5hfd6y24r0f64uwq65vjrmsh9mr568kenk33fcumag6djcjywkm5v295egjuk3qdd47atprs0j33nhaaqep3uqspzp5kg4mthugvug0sc3gc83atkrgmguw9g7gkvh82tugrntf66lnvyeh6ufh4j2xt0xr2r4zujtm3qvrmd3vvnulycuwqtetg2jk384"
let rawKey = decodeBech32 svk
let badKey = decodeBech32 badvk
let rawTx =
2024-02-06 19:10:06 +00:00
fromText
2023-08-23 20:20:01 +00:00
"050000800a27a726b4d0d6c200000000ff8e210000000001146cc65bd6d252d09b8eb0a8ab0aab6d7a798325aefc1d3032fc6d31373a85a25a3a16b447a698f720ade1bc290a74d85574b5b20515391035a67f8d5883dc65ea3ba4a17b009d6f325d41072b3ce240270959a7ffd040e5f16c697d8148973c62ffe037fc83aded21e4c91722b52520a2395c23e9c1a896f4b0f12d32ae8e31833d9d95adae40f6ecf7aff52af184efd390a4c1aa76b5fb1cab6003b1a8a004016f385926661f56d38273ec2c3df7775210310a65fff5fa9ac5509f0784eefea28bdcc67b0ff69eef930335f3b9768529e2bfe733024492101f642f989de8cbf04dd66638e9317780bce47085079675b772664c8007e96597dba83ea9af22ddf07ff1c212983d4a902914431245357527294e69ea5616e720ef1e9215bbfa33ba108b8d07efff2bad1850525d7725c681761c9b8c844a5548afabf176863de7b4cde3901defc3e83d31086d3c6e6af9a5fcc3cfb38b52ac7de84f91df5e0587f7603773401a62eeef10cd3ccf4d927ef42402c32f32280abbeaac33e73ceda52089820a186e9a1adfea81453998c6bbaa0deb41bc4f94586bfee80bad25fc71abe7c6dd44bcb1a6929a0112c7e4f8fcadb9745bde9422b954f72954c4d22db48719de61f383d620935b647337f73d119d79fd208e1d5a92f0855447df5782cd4764ba91efa65d9e4ebaa34e2eccb7aac93a5b0efe0c7664f3cd9384b3ff706ad3019c907cdcfa084351c9f6a0bfa8c78c91272ca66ac86dd6e1d0d6ba9704ea7dc54f71a053dce91f844c1ca62b5ddfe6b53834f4a816b1b01460810d9b87517659f4915adf4b84783a60ecf3bd71569259f1ff90a91a0b314bd4c77976d7893bf42e5d6ad0f8df95eb6d6c69d41490be8e39b2452df3bebfc297d5b0fc97f081890390fb0727a96898585f0120a7da9a798f2032590553f724d8756c67c5b0d1c0d23301c4ed60fa283994fd712aab17ca6360256fd5aef0ebc48f0256e3eda5894b53981d0d46768aefdc85b48c1525b7f134dce5d4ec2d76c03c821513f1652d9671219d744bdce5e69b9a74ca0c7c837668f0d8ffffffffffff9534b3d594e1609b3bace18608750b35a066c57f85e291d194400cb351430bbbe212abba32be071e747b7310863bd5fd989855a6567a351b288144b6e9f838c6a517db94673246ef0010b65f9c0be8aca654f6f57b83d893663cfd389ab96ce50e8077fe588c16b1b5989c6cc262e6658efb9b88ac800e49e9e5999e2651b8fff28fa77071d63790df155ed8344e2581ac5205b31d4f17bd748fcf60e35a9d6048d23c94c7aca8d4e541fda497aa268df9c173af5877a5da56d8fa2a42166900c734b62e56792f6c8bed48e4f108a817e83d64d6a59e38cfdb55c0f8a89bc7507c89326266f7ac03a3941f448cb879bd792bb116d0be8876c0856a76ddec0f0c02e16f0338626013ee5f6037fc6a3c69fa291204039d04d17c11295ee3024aea8f5d381e9b7eb3f938b6f9182bf4f889f1e53e30f998b1cdd23f45cfaa20aaef058248cc2e1c487fcdf54a4bc22a68a17cb6fa7b2fbf333b99feb84643d321398b675634929602126b2fb40171e514769bf82f18c267ce9cda0c24300caa9a5a361144d3b7b9ab2243ee9811d9b2e72c8bb1d145cdfcf6b29994a969b41c47208f5dba8d6d871e490e9b970afec4d8bca40ba51825cdc78cc7cde6b6f235a4105b1d1b5e2765efd753095ce770f070b02cce3316721b9345680c146c2f428c0bbca90d5a8cd0a1c4c31cbfa8ec165ea9f9c71d2d05e3cf8bae5e779786f179c45a3cd8087d820cae812aded04f8acda9068af80ea834f79f1bd03bfd66f8a19074649a85ce877df1a621a867debb423ec0d19015b326fcf6f143aba34029c1da2fc7b099378a366c38c9609ef6a9d9e175e21b0c1ab94a84e28ee7f1a00e39cb6fb59f44e4567e9f85f8f98158263c52ec433c042397c784edb07c28d2bca036f59090e819157375d610acb1993a4107b48da13a371f5383429baee209b2c0cc150fcef79a042749668ba1f89ad24a8c746142191ed0e8fd63624a331d98d50daa84ccf9043076947cf5115b9f8787acd36000c5e72c8d783b29bb28a3e46036d0a592ce8a158ee5a7ac210be72d3a6185c13645d96a8446021b64043ab8b589a20091c152e7d5a993ba94770eea988e289e1536d0d81dbc7046ca9c6d918446bf970894f073c920006681ccf6d1a3f138519c68eba0296069e42dc60f2bcd0f17c400efe4f4e87de8606606dc4fdf31494df4d454d14a440b1d9db4265c7aa9bc8683c68cb149f2cc826427575e2af82e842199a9cb9fdc7243b3bc12f1a71c37eac5cf88ba830cb95728897fa4c177a290d6b2b3814173262da14db9b4ef39fc54f888a6ffef4221ae672fb03bc78ebef479360a682ddb12ea0369a428a6c2960ff8327e9a2f5e5d98ce1eae748db8f6a4631c789b4d751d6b99c97c149a813998d44a7b57ba06c8bcb8a6c73c6388cdcfeb1346cec8fee7bdebf2a2388d9722183eb2d2e0e183cdd092152ef640880f4514f3c5e836cc3a8249413500630aa8da85f9e3cd92bdadbb69a2bab8d71f0b3ec5832a7ddbddd67b34c33b2e12a0c8468e852e4a8f7df45657e9632088aa7c6c5048a2686019cfec33b27fc88e23759938dd55a5dff589c1c21a37da617609e9d8be37dbf9bd6e84ee160fe10268171d969e4611afe9d3482ed4b132dcdd11ee516f36d512a333da20266fd984caebf4937fdfd18ed07b4a45771cf5c8c16c6b258b289a07d136a22acc766011f366c420bafb8fc1a10e42219bede5a3d1166c525491ab60bbd1f973fd3fb2e94cea888e24
2023-09-27 15:37:53 +00:00
let x = getShieldedOutputs rawTx
describe "extract Shielded Output bytes" $ do
it "should have outputs" $ do null x `shouldBe` False
2023-08-23 20:20:01 +00:00
describe "succeeds with correct key" $ do
2023-09-27 15:37:53 +00:00
let a = decodeSaplingOutput (bytes rawKey) (head x)
2023-08-23 20:20:01 +00:00
it "amount should match" $ do maybe 0 a_value a `shouldBe` 10000
it "memo should match" $ do
maybe "" a_memo a `shouldBe` "Tx with Sapling and Orchard"
describe "fails with incorrect key" $ do
2023-09-27 15:37:53 +00:00
let a = decodeSaplingOutput (bytes badKey) (head x)
2023-08-23 20:20:01 +00:00
it "amount should not match" $ do maybe 0 a_value a `shouldNotBe` 10000
it "memo should not match" $ do
maybe "" a_memo a `shouldNotBe` "Tx with Sapling and Orchard"
describe "Decode Orchard tx" $ do
let uvk =
"uview1u833rp8yykd7h4druwht6xp6k8krle45fx8hqsw6vzw63n24atxpcatws82z092kryazuu6d7rayyut8m36wm4wpjy2z8r9hj48fx5pf49gw4sjrq8503qpz3vqj5hg0vg9vsqeasg5qjuyh94uyfm7v76udqcm2m0wfc25hcyqswcn56xxduq3xkgxkr0l73cjy88fdvf90eq5fda9g6x7yv7d0uckpevxg6540wc76xrc4axxvlt03ptaa2a0rektglmdy68656f3uzcdgqqyu0t7wk5cvwghyyvgqc0rp3vgu5ye4nd236ml57rjh083a2755qemf6dk6pw0qrnfm7246s8eg2hhzkzpf9h73chhng7xhmyem2sjh8rs2m9nhfcslsgenm"
let res = decodeUfvk uvk
let a =
OrchardAction
2024-02-06 19:10:06 +00:00
(fromText
"248b16d98dfa33f7ba69a0610a63b606699da76c288840b81d7691ee42764416")
2024-02-06 19:10:06 +00:00
(fromText
"17fcc27cce560733edaf91439a8020c4a029a4e7d5893ce024d5ff4b40bbd0a9")
2024-02-06 19:10:06 +00:00
(fromText
"34796d541864832acca43f083892e98a46c912802d5643672d3f25bea177c61c")
2024-02-06 19:10:06 +00:00
(fromText
"a6d2ca10e3fc7446e372266ef45ee3dc0ba373bd378e6bf3092519a7f272bd8c")
2024-02-06 19:10:06 +00:00
(fromText
"08beafdf59110b5d045e4acc13731ef1a27bfa3a9cabe1d575640c18f18ee6697fbb132d36e982ae3eadf5f37fd35f42c2bb07def14759deab1fbe2f98dc1d5913e4a6ef388b714e2cfd6d89ba2302800e02ab5f45e0e02e3895448518cd8afd2c37bb48a66d8b988a37de9d0838d92876894a311bb9f314ba842e5c18ff7a3d8c7f0ff1a7209e2d661595db8f4a4aa267b9593258914bf63c09286eeda7c9b27ddbb4646208c0d03a8fbdc5d96633335a5a65316f5b25189bdce735bdea7e900de56d3b475ae51b7c35eb7ae79ba104baeb0a5a09d1cd8bb347ab34fb26d62ddbf024f5394710626ec0a665b9c917e65b00256db635145164a0329db7bc5358f435d573b2662adf8a6128801825ec8fb7d8aeef567d35c875ddd784fceb7620355e3f056a648b39b4b2d29a1f5e7b7c4ec5fd2b1874ff1e832b308f8644e83878d90582b9a6fd6c293e19dd3e24dbe1b4c15c96608169843d46551900a8cb787b15f0f1696b736dd4c8ebacf1e3288b14e469bdc004fa8557d6b1395700eaba59334906bb012f876e4cd7acd2157719ebd2e28bd0cd4ab4ac458f8848e1c30e729803dd47102200fe703932a15c3618862ec83b40d3aa0ec2343641bcb9afbf931ab21aa4afdbe7e51deca24283c2ccab0eef6e07aac5a4bf3a775bf7d2ddfc8d8766c3bf8e35df1435cf515d93c3b9549477bd9f53d133f05dd256fbcc0b13a63e3e7f8cce6301ab4f19c114f5af079f8c581537458e861b553218a890ea3e77fb99781c7088cd43c67c155ec611c1148721cab5fd0168e4a5ec390b506ec44145474c")
2024-02-06 19:10:06 +00:00
(fromText
"1e40d33446d9f0f0fad40f8829c1ffe860c11c3439e2c15d37c6c40282f9e933dc01798c800e6c92edb4d20478b92559510eda67f3855f68f5ab22ca31e1885c7fa9d4c9ebfb62ceb5e73267bcad0ba7")
2024-02-06 19:10:06 +00:00
(fromText
"63d0d6e8e92691f700bf8af246dcd4ae1041b13e3969f7a9d819a06e0f9429bc")
2024-02-06 19:10:06 +00:00
(fromText
"fe362be160accf2794841c244e8d80bbeb80b9bc95bb653d297a98d32bddf5a05dd5f874891d55924a83f722f75f576f63796770c31074067694cffb2cce7a2a")
let b =
OrchardAction
2024-02-06 19:10:06 +00:00
(fromText
"8921446787f1bd28fa0e4cc5c945ea7fc71165a25f40cd2a325dae0c4467d12c")
2024-02-06 19:10:06 +00:00
(fromText
"240b08b7861aa78989c68cbedd0038af9b3e3456bdc7ff582d597df571d54da2")
2024-02-06 19:10:06 +00:00
(fromText
"e1bc8ccba69ab9f429bf735417aa005cf439d27500b0d3086dbf1be764b42a36")
2024-02-06 19:10:06 +00:00
(fromText
"c89c58ef8553e7d09ba4090654edd1a8c98763c44d3dfb9dad18286c7ef363ae")
2024-02-06 19:10:06 +00:00
(fromText
"0eee1ca5a3a4959cd4b8bc277e6e633f950680c4acb978c14ad8d944a784f46771c9d666a203ca3ac693943d79dd23f8b76a734a62e81932cbe98e8c851f47a11aaef50249e53151f38f88262a4bae8cf26f5f8b2db1d165aff9b57b64713a677c167608585c038e34ca7bbe468e5f86475ccec0a4a8b9a43b56e342e77a6bd09415787c9f4a1c6f20599f57545f1ac32c3a338d7a5bb2d35456adb880cb65c1455969e10df5d94b8c74b244e7093b1a88cc10697a7c2f4d34b6eae3296e64b820573b4d52e06b4427af5b8f5d6722d3a93fd85da615fceac732976ad2c1be4150b4821c149521f5419ea0746fb132d47f593cfc8a3aab6b2b4480c12fadf21280ccd3142e7188d9e5aef3fcd8c5dc0c066dc975bead023ef7f89a486b615b146110ae68b703a8349a5fc225b26a08b2adaf36fb44c9ad1be59d7ced134eb84e3f0b4aec19b71b2d26e910628a11446b97c5e6bbf97e1befa4e04b5947f83c65161b92f58088d28e57adc2a2873e27008e29772c5803502842045cb355d1ea5a9d27c2683dcb38cb49d26af39625ba99b1342f700387b939e7ff6c129417ca8836fe1e96331e35c8bc0763879e8c17cd4535fbcb27a2785c0a47294e07cb54837bb997df34882ce0bececc6adca365c76fc7533cf0503458937dcfb6058b016dbbd399b9f0cca44cbc881016f4957b5e10daada3393d5b2a4cb15ed983506d4d264f9855ce2ef87a7d4a1fc03293a22c28a53c4455447d546813fa33008e5d2d81848825fae2f437ab9575ba99c230e78f4b23e575e7647beff0e4c4e2b0a1f7320e9460")
2024-02-06 19:10:06 +00:00
(fromText
"d727aeec27bb0f7463c6ed4f5b3f4085cfd3e7218478db0dcebfca875e025320fb64bc4062251823859e963446cadd9924c559e5f981480df5a4f036daf5a8033d4c8241e128902aa1aeaf6adc149730")
2024-02-06 19:10:06 +00:00
(fromText
"98e72813aeb6ea05347798e35379bc881d9cf2b37d38850496ee956fbecd8eab")
2024-02-06 19:10:06 +00:00
(fromText
"cb9926f519041343c957a74f2f67900ed3d250c4dbcd26b9e2addd5247b841a9fde2219d2ef8c9ae8145fecc7792ca6770830c58c95648087f3c8a0a69369402")
2023-09-27 15:37:53 +00:00
let decryptedNote = (`decryptOrchardAction` a) =<< res
let decryptedNote2 = (`decryptOrchardAction` b) =<< res
describe "First action (sender)" $ do
it "Decryption fails " $ do decryptedNote `shouldBe` Nothing
describe "Second action (recipient)" $ do
it "Decryption succeeds" $ do decryptedNote2 `shouldNotBe` Nothing
it "Tx amount is validated" $ do
(a_value <$> decryptedNote2) `shouldBe` Just 3000
it "Memo is validated" $ do
let msg = maybe "" a_memo decryptedNote2
msg `shouldBe`
"Hello World!\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL"
describe "Wallet seed phrase:" $ do
2024-03-11 20:23:29 +00:00
prop "Generated phrases are valid" $ again prop_PhraseLength
prop "Derived seeds are valid" $ again prop_SeedLength
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
2024-03-11 20:23:29 +00:00
it "Sapling spending keys are valid" $ \s ->
property $ prop_SaplingSpendingKey s
it "Sapling receivers are valid" $ \s ->
property $ prop_SaplingReceiver s
it "Sapling receivers are distinct" $ \s ->
property $ prop_SaplingRecRepeated s
2024-03-11 20:23:29 +00:00
it "Orchard spending keys are valid" $ \s ->
property $ prop_OrchardSpendingKey s
it "Orchard receivers are valid" $ \s ->
property $ prop_OrchardReceiver s
it "Orchard receivers are distinct" $ \s ->
property $ prop_OrchardRecRepeated s
describe "Address tests:" $ do
2024-01-12 15:46:26 +00:00
it "Encode transparent" $ do
let ua =
"u17n7hpwaujyq7ux8f9jpyymtnk5urw7pyrf60smp5mawy7jgz325hfvz3jn3zsfya8yxryf9q7ldk8nu8df0emra5wne28zq9d9nm2pu4x6qwjha565av9aze0xgujgslz74ufkj0c0cylqwjyrh9msjfh7jzal6d3qzrnhkkqy3pqm8j63y07jxj7txqeac982778rmt64f32aum94x"
let msg =
case isValidUnifiedAddress ua of
Nothing -> "Bad UA"
Just u ->
maybe "No transparent" (encodeTransparent (ua_net u)) $
t_rec u
msg `shouldBe` "t1LPWuQnjCRH7JAeEErSXKixcUteLJRJjKD"
it "Recover UA from YWallet" $
ioProperty $ do
let p =
Phrase
"security expect junk hour people bind law hub between topic wink cliff spirit scissors auction idle figure option wide useful swift prison cushion round"
let targetUA =
isValidUnifiedAddress
"u1qsylqauvnhw8tsfe3cldcsj3mjrfqzgaf3mt8yzlkjuvsf5wzj223yvrt8q66qukfqcc80x3z0mk6ym6pm2f0hukzkp6t4wj78h85t6kfr2u9mqsfhdd73g3sc7ezy2ut3rtq5jmejatwv4xqqd6l8tt9fycer8kdw0gz6e607nkssqsc7kd7nk2yfz2hpvpqhdg39wxalpjzhe34j7"
let s = getWalletSeed p
case s of
Nothing -> return $ expectationFailure "Failed to generate seed"
Just s' -> do
let oK = genOrchardSpendingKey s' MainNetCoin 0
let sK = genSaplingSpendingKey s' MainNetCoin 0
2024-03-14 21:44:18 +00:00
let tK = genTransparentPrvKey s' MainNetCoin 0
let oR = genOrchardReceiver 0 External =<< oK
let sR = genSaplingPaymentAddress 0 =<< sK
2024-03-15 15:11:27 +00:00
tR <- genTransparentReceiver 0 External =<< tK
let newUA = UnifiedAddress MainNet oR sR $ Just tR
return $ Just newUA `shouldBe` targetUA
it "Recover UA from Zingo:" $
ioProperty $ do
let p =
Phrase
"cloth swing left trap random tornado have great onion element until make shy dad success art tuition canvas thunder apple decade elegant struggle invest"
let targetUA =
isValidUnifiedAddress
"u1trd8cvc6265ywwj4mmvuznsye5ghe2dhhn3zy8kcuyg4vx3svskw9r2dedp5hu6m740vylkqc34t4w9eqkl9fyu5uyzn3af72jg235440ke6tu5cf994eq85n97x69x9824hqejmwz3d8qqthtesrd6gerjupdymldhl9xccejjwfj0dhh9mt4rw4kytp325twlutsxd20rfqhzxu3m"
let s = getWalletSeed p
case s of
Nothing -> return $ expectationFailure "Failed to generate seed"
Just s' -> do
let oK = genOrchardSpendingKey s' MainNetCoin 0
let sK = genSaplingSpendingKey s' MainNetCoin 0
2024-03-14 21:44:18 +00:00
let tK = genTransparentPrvKey s' MainNetCoin 0
let oR = genOrchardReceiver 0 External =<< oK
let sR = genSaplingPaymentAddress 0 =<< sK
2024-03-15 15:11:27 +00:00
tR <- genTransparentReceiver 0 External =<< tK
let newUA = UnifiedAddress MainNet oR sR $ Just tR
return $ Just newUA `shouldBe` targetUA
2024-03-15 15:11:27 +00:00
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
describe "Zebra response processing: " $ do
it "Read block time" $ do
let blkdata =
"04000000c732575a3e94b7464c84b35935c2fca26e40d37b6f3278bda3d941877b192a0048cb59da8eeaf9f622d4537ec2a27918415f444d0bb143e8091b470a18a438c117fd96323fd1a9c775ed793154de0e8a2023b551431e89b5ce6f30ef047388f0bdbb0266fe81481f2c006046a8be3bca5b8819209d053a88184bb48753171accb807c38f46d00000fd400500b6a304cbc4e6caecc9b3a29ce42d71752bf5396944e28465e29d1bd7e7f3c680db3c4b85a1488d7c4e21a70c1cf50cfe4e7f70a4f1abb638f144afb90dfa69adfc7c981fd8792df19926da695356699ab76213094431bf6491b80572c310ab8e51c27cda39c771371dbf7adc60089ff5f9614577a92ce3a1e452d5d8280e3d970322e1fc5937c53369623d5e58e57672b48c2edc7a86f7d7de62e06668097547b782a01d3794a50f131695f7de3e4bf038b12abffd29b8eba618820e143ba0be57ccaa67f64511460027efb065c6ddff501376744c6b68ca01d884025e7f939521d230b1a46016d66ad3ab2262dbd477b38bbec234a19425b939dc0f1d868035c3ef99eee635c9dfd62235ede6d62f652fec499127a152e7be4f959a9bb7fcca9b335de98d14aee1330fe37f1ba28be26902a1cddbc3f67f2f6317093d3f278c1c0156e5319a0b35360e38719911b8012a8cc34893f05dc28a22787f3e0461836aef602110e621c8b9d78e991ccc0160deb8c8921f6fd13bd00d47a170b9d0b09ffd57e37467400c138823dce7c12027eb9f919b8d5f4072b331a042f6f5ebb814c6a903110cc97161787d1eb2716c8fb98d747abf321a0b079f3b6a1a0329337b4922a0d739886a03f0d475d41005733f26c675dd9694712d6ee07772a5e8f6b5871789ac14159beced65d3b2196725baa4ce04f059a7034ff0d7ce081e94d23e0115b9d8f0d99fa5b4f9771b4feaac881ac80f178c3575cc70858e40f53f1d0406253edba75e2bb6f40eb2ef4ece3df2b8dadbd3ac168b1743a0cfb68ba81ca4c838435002587852e81e0a0c3c77e11218df892ac0c2f343967b127fbb822712ceabc459ded7f3ca3e95ed5ddfe6cdfe5657da1b12ee47eb63af7a839cdbc1f52f51e349dbf2bd7d8529f814108723d97fcfda7563c4fbe3a24118352e4706f9f91406f11acde3a570e10a258fa6a5415f57a26988249a87e57f192d0408b6f56c2ef65d5e37597d144e8fe1014a4f552dc8c213b0a70b2ccff6747f6f1e0d598715d8cb0da37e0331c01da1f9e0505e9d1907628427d5d032a29fa0e14b75289b10c7d3109b590aec2a4debda9eabcbd3163f6df67efd92687d0c492a71d48b2995a658b34e96814e5674a62e3738efe53e0daf4bfe9d1031e45a246bd3b32c6d581b71c0b60ad711570bca3848c38ba5aed74d977a185d199db721c2677d4868e5afaa6cc2c7369898f58f93738681118d529194d41f0cb6103915d2e99422db387fb90046eae764a79dfe8733a7f68439d0f37e773d16ac7f0ba3a8ce0fd6746d038704b2a0a979659a859682581fee0be3fc50eed13e85e6b52f398d16b59f5f738c1eb289b3861d636b961d9220c1f76bf8a8be3ffd1e2472461202285aa1c5b7eac58564aaab0beedb65e1078517e031888aa3cb8843876aaf19311d5150529a10c9d9bce1538f7533aff126e518ef1ebd919f26aa3869ed1ced167cb1de6075897ad2dc461b9156922c4ee387f8e1635e95564d3964e47d39e6e82079e0220df00614ecd4fd31a5f3d13c9191fc65037ad3cd651f055cc795260f21bb0ba8acd7e3b65b5ff81d5a1b187a777c826f96637e00f8147c4bd43753fe9e0cd73564b53a0e9eab27745505ccd2e4a1a217307c66030ca115580ce6ecb9a8b043ca41bd2de15abd13838d130d3cfecd8d0e3bb6c982bf1f9cdc799c3256e2d722d3f13cd7acdb9d75d7e36483b2ae01e5dcb70db824eadd9c3955d79557d612a879fa6da1da479807640e37bf25a22091f1cf6fb5293e60e5616416fb2adb1d9892258e8ac6859978159338d3b6e2063b9d842a24d61d0616506d5088fe76025df35619febd57f92e30699a0df8731bdbad0775922bb12fb1697d9da833010400008085202f89010000000000000000000000000000000000000000000000000000000000000000ffffffff0603204c2a010cffffffff0480b2e60e000000001976a914278aff0c0f8734638ce81aaef4ab0afddd36552888ac286bee000000000017a9140c0bcca02f3cba01a5d7423ac3903d40586399eb8740787d010000000017a91471e1df05024288a00802de81e08c437859586c878738c94d010000000017a91493916098d2a161a91f3ddebab69dd5db9587b6248700000000204c2a000000000000000000000000"
getBlockTime (hexString blkdata) `shouldBe` 1711455165
describe "Raw transaction from faucet" $ do
let h =
hexString
"0400008085202f8900010829d200000000001976a91484ae5002305847e7176362d7c12c19c5bdbbaf8088ac0000000023392a00f02cd200000000000192331caef004cc758fb666bed1908e61daa82d5c9835c0544afd8369589d350b04a7488a9870983860779ca2e0079a286fe71f60d5c583c3427d24ff968bad3246c1c838b90f465becc1ddfea5839b730ec219d577ed182f6da8f493350b422c86943b7c8ff42de8aee0fe01f4b91c8bb204008f06f85c3dffdb622632d2d4e8b8f0c7457cfa0f4238c7ef4c8903a89559e9307c26e844747ccb9b8dd5e7e83637983746b2fec3de051312306eb8b15db4766b3ef5fe3086d53d388cf2b3b209389ff3644e47d6bfdbe2fafef1bc2311093ad0b49f4600925f55328da337e73f01f83097acd8f2aca7a85f28e75fb4efec6551e026a1ebb35c25efde455cc44002bb8cc79288ed738423432558ebb583874aa5c356abe5be794e1bfaeaf6a7eccf67e5d938751a3a351bc21d4422d2ff0f36f5b30759d79b1ef2d83618d9c1769694454002d2f2be74de3ac10d39829369c87a70e1e9769e7d5ae7c865282a04487a8ae4cf5beeecaea6a3be1c864bdd8d61df88f08a76ac49d28a3a069d2c0d02068a10e88674b39c9d03da49256d914319d267c0d1db08ee7777668e90a94c50a065977222ee620f2291f6ca3fa464fafe8fc3fedf64a836eef5a2ca16aaae5573ee082a77f046d388750fa4ce3853c846ae3f338741c7976f72db4ade4abd4211e8d335ec8c83309bc7d7140a99dfb64a29839b9acc74de4ac0949bcbec4e76be9096a45ab6ca19b165f4097e24ab92d7b58694b0897789c3cdcca2b3d4b0a9da153fafe68f940031b6548d3c37c1301faa9adcfc41c417e613c0838340e28801f72610289d7435910fd276ca243d119541e0a121d263fdda149ac40f293e6fee6d5ddc32532ad947548eb5d20a5bfea97543965fe09313f1a5a78ce51ecac9c36b54cb573780da15d197f5ffacf1fa0d2b5495057a29104d610936c1898d1058f6f7b90e614bc2e3ff56b1e75aa4708128e3782f602dbdd29ece268311965592ddd536ea63841ea953b20677e0dd911852d23b85a3382420d22cd276b216e81638540b04966210a9308e8f9fb46958c967e3c2e36ae081a95cec8865a87d85d5689f660fe6c616ebfc2dab0f6e41d3e8c2906405fb98a506d90a8e8c6201d520a0deaa65e92e91f965288128101427d58e0b1e3ad8a49526feed27f3bcc6d505591483e2e4cc4a9b678d63f3abc905f26f91083bc595b89ff0b6cc3caa9d93013127ab7b30fbe18fad6f7f380fd6d5668fb6c3fdea3771fdd3004994e5752275ff7b186f9ad95f9d7ff01263f1165de34c1ae867e8954d66186880a90d73eace4dc1b8b17c76815242342821b4fab93755c3dc24e60aafd1cd3e283a7414de3af18c61328d92e9141916b8bb816de024a5a047a66508340a3287f698a41804e297916ff04f2921a0eeb8fcc5690c7fc024f57ab1fb6c6bc9a0caf9bf9e0e9aad64ceb2634bedbda6716235e4b93b67cd07ae06fde6abd2893143b55628be83fd4b347ce407dabf28e288f99d23b031376bfc1b1552cac1557e4730b03be581a92feae7d39fa2cf1c565a6cbe59a83b64b90ef8fc73ff6f8b9562d77fae1221df8f5ddb029f12ae80c3f128b87e56f78224b875af54a2fa1434749bb2e1c7ad9331497a71015ae0fc63903f36023e7f34b97c6ec5976ba3740845e5870c85f1b2042cdca86620881e08595215332de7d5828844e9e44124e42e1c60f6821cb71640c6643b01681553c932d310632a8b21154445176eb1a9a3c87dff22508bdbe4f1500e19131a072c42ff1d106ade135722a9e37e95e7e93917378e7907aae4be92dab78b1cd5a771d6064f6e3afc26ff84943a84de7f6ca6b0ab5993d1013b061da4053d77398cbeb329a6ae16f76493f85df1164b4f1fdff69bf113c8f18274a4ce6a05dd4c1ccbacb8d2c3760210e312c3a344294b43b23d06b7ce7263d3178e4fd530ba5838dc0e517b7d6fff2a0d9c4d69105a8fdab3f0c51a219c1ec10337b7cf05f8f3b1fb0a09f600308e5c21ae6ae06d6f87a6766d29e3a34f331f520d80524d580bd54b25716b6b937534233b856e022d20e53779b3a4a3615a3d62d1824c2bfa906e7804d629cc6712a3aee8c3703e99ec807cdb2d381acf126d63b83a2ce1d8f5cb768270bf41ae5637976acbaad8a1fa52cfb7a2f012966f3d29867cf2c28e504043a09eeff91917f6e96dc35a7df124074da73a20b87c7c8e2196f344cc08bd4c2406daaf6064488b5f9983131d90141fba82b13b0b1ff60565be66d53c36df3a9b4c772bffd428b34f94060ad32c59c9c029eba5fabd7a01b4e7252406c0ce7bb93c831034b100cc71090b37a436f96ce902973e2dca9594886b602ed6142697413aa448652529fe688a2e62fa96f8031ade066bb2bdc682f0ae3a526c7ad3c5d01e243b999a58aa5f6816dcd7a0cdd49202e128b99436f71e7fb7033bf96d8e3930e39e024530ec4b7932d334e54a66bfc3630b472336b6719d5a38e6e9bed938f71fe49e0af0b20c5db5408cabb3227b1690e904ea3116ee568330f56a5a698b914570962da4d831f5f5acde9acb257d272d0cd14e3133c89307f2d1575e32b8cc1582d1e4a680d35a1a2cace6233dfb4b0a7fea26f41785e1ac6007dd20d8b6dc3bd6857fa487c52b39f86647a67931b33910b746331305199d20ecd2e4d3b454226a134240831ea5a35c1e2d603c48eea209868b839c79a9318b6fd1078bc0f2bb9b0e931b64d63fbbcbf22b41e3cf7bee5cecb3c0e7b3ae39cf736fce8645ab33becbc9586a9154e29dd88f42ec7d
let t = readZebraTransaction h
it "Transparent output is identified" $ do
case t of
Nothing -> assertFailure "Couldn't decode"
Just t' -> do
let a =
"utest13dq4u4dnf3yddw8lq2n6zdclshra6xsp8zgkc5ydyu6k20zrsscmuex46qa4vh84rgd78sqnlleapznnz7mnzx9wv0unts8pv32paj8se5ca3kves2u4a89uy6e8cf4hnarxydxh7hq2e9uu39punfmm53k5h45xn9k3dx35la8j7munh9td7774m8gkqgc4mn40t69w20uu2gtks7a"
let a' = isValidUnifiedAddress a
let tb = zt_tBundle t'
let myTb = fromRawTBundle tb
case a' of
Nothing -> assertFailure "Couldn't read address"
Just addr -> do
case myTb of
Nothing -> assertFailure "Couldn't read transparent bundle"
Just myTb' -> do
let pkHash =
BS.take 20 $
BS.drop 3 $
(\(TxOut v s) -> s) (head (tb_vout myTb'))
pkHash `shouldBe`
maybe "" (hexBytes . ta_bytes) (t_rec addr)
myTb `shouldNotBe` Nothing
it "Sapling component is read" $ do
case t of
Nothing -> assertFailure "Couldn't decode"
Just t' -> do
let sb = zt_sBundle t'
fromRawSBundle sb `shouldNotBe` Nothing
describe "Raw transaction with Orchard" $ do
let h =
hexString
"050000800a27a726b4d0d6c200000000ff8e210000000001146cc65bd6d252d09b8eb0a8ab0aab6d7a798325aefc1d3032fc6d31373a85a25a3a16b447a698f720ade1bc290a74d85574b5b20515391035a67f8d5883dc65ea3ba4a17b009d6f325d41072b3ce240270959a7ffd040e5f16c697d8148973c62ffe037fc83aded21e4c91722b52520a2395c23e9c1a896f4b0f12d32ae8e31833d9d95adae40f6ecf7aff52af184efd390a4c1aa76b5fb1cab6003b1a8a004016f385926661f56d38273ec2c3df7775210310a65fff5fa9ac5509f0784eefea28bdcc67b0ff69eef930335f3b9768529e2bfe733024492101f642f989de8cbf04dd66638e9317780bce47085079675b772664c8007e96597dba83ea9af22ddf07ff1c212983d4a902914431245357527294e69ea5616e720ef1e9215bbfa33ba108b8d07efff2bad1850525d7725c681761c9b8c844a5548afabf176863de7b4cde3901defc3e83d31086d3c6e6af9a5fcc3cfb38b52ac7de84f91df5e0587f7603773401a62eeef10cd3ccf4d927ef42402c32f32280abbeaac33e73ceda52089820a186e9a1adfea81453998c6bbaa0deb41bc4f94586bfee80bad25fc71abe7c6dd44bcb1a6929a0112c7e4f8fcadb9745bde9422b954f72954c4d22db48719de61f383d620935b647337f73d119d79fd208e1d5a92f0855447df5782cd4764ba91efa65d9e4ebaa34e2eccb7aac93a5b0efe0c7664f3cd9384b3ff706ad3019c907cdcfa084351c9f6a0bfa8c78c91272ca66ac86dd6e1d0d6ba9704ea7dc54f71a053dce91f844c1ca62b5ddfe6b53834f4a816b1b01460810d9b87517659f4915adf4b84783a60ecf3bd71569259f1ff90a91a0b314bd4c77976d7893bf42e5d6ad0f8df95eb6d6c69d41490be8e39b2452df3bebfc297d5b0fc97f081890390fb0727a96898585f0120a7da9a798f2032590553f724d8756c67c5b0d1c0d23301c4ed60fa283994fd712aab17ca6360256fd5aef0ebc48f0256e3eda5894b53981d0d46768aefdc85b48c1525b7f134dce5d4ec2d76c03c821513f1652d9671219d744bdce5e69b9a74ca0c7c837668f0d8ffffffffffff9534b3d594e1609b3bace18608750b35a066c57f85e291d194400cb351430bbbe212abba32be071e747b7310863bd5fd989855a6567a351b288144b6e9f838c6a517db94673246ef0010b65f9c0be8aca654f6f57b83d893663cfd389ab96ce50e8077fe588c16b1b5989c6cc262e6658efb9b88ac800e49e9e5999e2651b8fff28fa77071d63790df155ed8344e2581ac5205b31d4f17bd748fcf60e35a9d6048d23c94c7aca8d4e541fda497aa268df9c173af5877a5da56d8fa2a42166900c734b62e56792f6c8bed48e4f108a817e83d64d6a59e38cfdb55c0f8a89bc7507c89326266f7ac03a3941f448cb879bd792bb116d0be8876c0856a76ddec0f0c02e16f0338626013ee5f6037fc6a3c69fa291204039d04d17c11295ee3024aea8f5d381e9b7eb3f938b6f9182bf4f889f1e53e30f998b1cdd23f45cfaa20aaef058248cc2e1c487fcdf54a4bc22a68a17cb6fa7b2fbf333b99feb84643d321398b675634929602126b2fb40171e514769bf82f18c267ce9cda0c24300caa9a5a361144d3b7b9ab2243ee9811d9b2e72c8bb1d145cdfcf6b29994a969b41c47208f5dba8d6d871e490e9b970afec4d8bca40ba51825cdc78cc7cde6b6f235a4105b1d1b5e2765efd753095ce770f070b02cce3316721b9345680c146c2f428c0bbca90d5a8cd0a1c4c31cbfa8ec165ea9f9c71d2d05e3cf8bae5e779786f179c45a3cd8087d820cae812aded04f8acda9068af80ea834f79f1bd03bfd66f8a19074649a85ce877df1a621a867debb423ec0d19015b326fcf6f143aba34029c1da2fc7b099378a366c38c9609ef6a9d9e175e21b0c1ab94a84e28ee7f1a00e39cb6fb59f44e4567e9f85f8f98158263c52ec433c042397c784edb07c28d2bca036f59090e819157375d610acb1993a4107b48da13a371f5383429baee209b2c0cc150fcef79a042749668ba1f89ad24a8c746142191ed0e8fd63624a331d98d50daa84ccf9043076947cf5115b9f8787acd36000c5e72c8d783b29bb28a3e46036d0a592ce8a158ee5a7ac210be72d3a6185c13645d96a8446021b64043ab8b589a20091c152e7d5a993ba94770eea988e289e1536d0d81dbc7046ca9c6d918446bf970894f073c920006681ccf6d1a3f138519c68eba0296069e42dc60f2bcd0f17c400efe4f4e87de8606606dc4fdf31494df4d454d14a440b1d9db4265c7aa9bc8683c68cb149f2cc826427575e2af82e842199a9cb9fdc7243b3bc12f1a71c37eac5cf88ba830cb95728897fa4c177a290d6b2b3814173262da14db9b4ef39fc54f888a6ffef4221ae672fb03bc78ebef479360a682ddb12ea0369a428a6c2960ff8327e9a2f5e5d98ce1eae748db8f6a4631c789b4d751d6b99c97c149a813998d44a7b57ba06c8bcb8a6c73c6388cdcfeb1346cec8fee7bdebf2a2388d9722183eb2d2e0e183cdd092152ef640880f4514f3c5e836cc3a8249413500630aa8da85f9e3cd92bdadbb69a2bab8d71f0b3ec5832a7ddbddd67b34c33b2e12a0c8468e852e4a8f7df45657e9632088aa7c6c5048a2686019cfec33b27fc88e23759938dd55a5dff589c1c21a37da617609e9d8be37dbf9bd6e84ee160fe10268171d969e4611afe9d3482ed4b132dcdd11ee516f36d512a333da20266fd984caebf4937fdfd18ed07b4a45771cf5c8c16c6b258b289a07d136a22acc766011f366c420bafb8fc1a10e42219bede5a3d1166c525491ab60bbd1f973fd3fb2e94cea888e
let t = readZebraTransaction h
it "Sapling component is read" $ do
case t of
Nothing -> assertFailure "Couldn't decode"
Just t' -> do
let sb = zt_sBundle t'
fromRawSBundle sb `shouldNotBe` Nothing
it "Orchard component is read" $ do
case t of
Nothing -> assertFailure "Couldn't decode"
Just t' -> do
let ob = zt_oBundle t'
fromRawOBundle ob `shouldNotBe` Nothing
describe "Raw transaction with Transparent inputs" $ do
let h =
hexString
"0400008085202f89014b6ded3d2ee43e54135c04f9a305b473d7d741bbe6f383aa636e03e948705e0d01000000fdfd0000483045022100b34ca0fb34959230b95a48e9de95521dc4c013bdc0e6bd2a77a67b373fadea42022030a1b13f16993ab212d9f674b7b8dd3c6723137c183dbd41a9bbfcf66d7811c40147304402200f0bd12663a52ccb5e6211ec633932bbc7f0151ab51194038534abf88f689025022051fe62591dfa11a96095b4aeee2114c77a0d773242939f7ac2fa8e5262ff0865014c6952210231ee0c161e846bc133ad41d295f560d7e24829415afc78ead24d4b10198bb7342103b0b11f2dd10611d06cd6232233678dce736ce2b2141c62bdf0b4fe6f79d736da21029cbeda22b05352f66a338561604cbe11e8332f836385f16abf5088045c39d4dd53aefdffffff02b63500000000000017a91499a8b5b1f3d3a1a12e92dd4f3d94bee8fc34c527873362fa020000000017a914d75fe4791fcd50f2874f1b7457fca5833293b3a38700000000000000000000000000000000000000"
let t = readZebraTransaction h
it "TxIn parsing" $ do
case t of
Nothing -> assertFailure "Couldn't decode"
Just t' -> do
let tb = zt_tBundle t'
print tb
show tb `shouldNotBe` ""
-- | Properties
2024-03-11 20:23:29 +00:00
prop_PhraseLength :: Property
prop_PhraseLength =
ioProperty $ do
p <- generateWalletSeedPhrase
return $ BS.length (getBytes p) >= 95
2024-03-11 20:23:29 +00:00
prop_SeedLength :: Property
prop_SeedLength =
ioProperty $ do
p <- generateWalletSeedPhrase
let s = getWalletSeed p
return $ maybe 0 (BS.length . getBytes) s === 64
2024-03-11 20:23:29 +00:00
prop_OrchardSpendingKey :: Seed -> CoinType -> NonNegative Int -> Property
prop_OrchardSpendingKey s c (NonNegative i) =
genOrchardSpendingKey s c i =/= Nothing
2024-03-11 20:23:29 +00:00
prop_OrchardReceiver ::
Seed -> CoinType -> NonNegative Int -> NonNegative Int -> Scope -> Property
prop_OrchardReceiver s c (NonNegative i) (NonNegative j) scope =
2024-03-14 17:35:13 +00:00
genOrchardReceiver
j
scope
(fromMaybe (OrchardSpendingKey "") $ genOrchardSpendingKey s c i) =/=
Nothing
prop_SaplingSpendingKey :: Seed -> CoinType -> NonNegative Int -> Property
prop_SaplingSpendingKey s c (NonNegative i) =
genSaplingSpendingKey s c i =/= Nothing
2024-03-11 20:23:29 +00:00
prop_SaplingReceiver ::
Seed -> CoinType -> NonNegative Int -> NonNegative Int -> Property
prop_SaplingReceiver s c (NonNegative i) (NonNegative j) =
genSaplingPaymentAddress
i
(fromMaybe (SaplingSpendingKey "") $ genSaplingSpendingKey s c j) =/=
2024-03-11 20:23:29 +00:00
Nothing
2024-03-10 12:47:26 +00:00
prop_SaplingRecRepeated :: Seed -> CoinType -> NonNegative Int -> Property
prop_SaplingRecRepeated s c (NonNegative i) =
genSaplingPaymentAddress
i
(fromMaybe (SaplingSpendingKey "") $ genSaplingSpendingKey s c 1) =/=
genSaplingPaymentAddress
(i + 1)
(fromMaybe (SaplingSpendingKey "") $ genSaplingSpendingKey s c 1)
prop_OrchardRecRepeated ::
Seed -> CoinType -> NonNegative Int -> NonNegative Int -> Scope -> Property
prop_OrchardRecRepeated s c (NonNegative i) (NonNegative j) scope =
2024-03-14 17:35:13 +00:00
genOrchardReceiver
j
scope
(fromMaybe (OrchardSpendingKey "") $ genOrchardSpendingKey s c i) =/=
genOrchardReceiver
(j + 1)
scope
(fromMaybe (OrchardSpendingKey "") $ genOrchardSpendingKey s c i)
2024-03-15 15:11:27 +00:00
prop_TransparentSpendingKey :: Seed -> CoinType -> NonNegative Int -> Property
prop_TransparentSpendingKey s coinType (NonNegative i) =
ioProperty $ do
2024-03-15 15:11:27 +00:00
k <- genTransparentPrvKey s coinType i
return $ xPrvChild k == fromIntegral i
prop_TransparentReceiver ::
2024-03-15 15:11:27 +00:00
Seed -> CoinType -> Scope -> NonNegative Int -> NonNegative Int -> Property
prop_TransparentReceiver s coinType scope (NonNegative i) (NonNegative j) =
ioProperty $ do
2024-03-15 15:11:27 +00:00
k <- genTransparentPrvKey s coinType i
r <- genTransparentReceiver j scope k
return $ ta_type r == P2PKH
-- | Generators
genOrcArgs :: Gen (CoinType, Int, Int)
genOrcArgs = do
i <- arbitrarySizedNatural
j <- arbitrarySizedNatural
c <- elements [MainNetCoin, TestNetCoin, RegTestNetCoin]
return (c, i, j)
2024-03-10 12:47:26 +00:00
genSapArgs :: Gen Int
genSapArgs = choose (1, 50)
2024-03-11 20:23:29 +00:00
getSeed :: IO Seed
getSeed = do
p <- generateWalletSeedPhrase
let s = getWalletSeed p
case s of
Nothing -> throwIO $ userError "Couldn't generate seed"
Just s' -> return s'
-- | Arbitrary instances
2024-03-11 20:23:29 +00:00
instance Arbitrary CoinType where
arbitrary = elements [MainNetCoin, TestNetCoin, RegTestNetCoin]
instance Arbitrary Scope where
arbitrary = elements [External, Internal]