Skip to content

Commit

Permalink
One more test
Browse files Browse the repository at this point in the history
  • Loading branch information
Evgenii Akentev committed Nov 15, 2023
1 parent c00a58f commit 7bdde97
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 6 deletions.
2 changes: 1 addition & 1 deletion src/Chainweb/Utils/Serialization.hs
Original file line number Diff line number Diff line change
Expand Up @@ -171,7 +171,7 @@ putRawByteString :: B.ByteString -> Put
putRawByteString = coerce (Binary.putBuilder . Builder.fromByteString)

getRemainingLazyByteString :: Get BL.ByteString
getRemainingLazyByteString = coerce ( Binary.getRemainingLazyByteString)
getRemainingLazyByteString = coerce Binary.getRemainingLazyByteString

--------------------
-- Abstract encoders/decoders
Expand Down
34 changes: 29 additions & 5 deletions test/Chainweb/Test/Pact/SPV/Hyperlane.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}

module Chainweb.Test.Pact.SPV.Hyperlane
( -- * test suite
tests
Expand All @@ -24,7 +26,6 @@ import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck

import Test.QuickCheck
import Test.QuickCheck.Instances ()

import Chainweb.Test.Utils (prop_iso)
Expand Down Expand Up @@ -68,7 +69,8 @@ tests = testGroup "hyperlane"

, testCase "verifyFailure" hyperlaneVerifyFailure
, testCase "verifyFailureIncorrectValidator" hyperlaneVerifyFailureIncorrectValidator
, testCase "verifyFailureNotEnoughSignatures" hyperlaneVerifyFailureNotEnoughSignatures
, testCase "verifyFailureNotEnoughRecoveredSignatures" hyperlaneVerifyFailureNotEnoughRecoveredSignatures
, testCase "verifyFailureNotEnoughSignaturesToPassThreshold" hyperlaneVerifyFailureNotEnoughSignaturesToPassThreshold
]

hyperlaneEmptyObject :: Assertion
Expand Down Expand Up @@ -239,7 +241,7 @@ hyperlaneVerifyFailure = do
let
obj' = mkObject
[ ("message", tStr $ asString ("0x01000001450000027200000000000000000000000000000000006b622d746f6b656e2d726f757465720000000100000000000000000000000071c7656ec7ab88b098defb751b7401b5f6d8976f00000000000000000000000000000000000000000000000000000000000000400000000000000000000000000000000000000000000000008ac7230489e80000000000000000000000000000000000000000000000000000000000000000002a30783731433736353645433761623838623039386465664237353142373430314235663664383937364600000000000000000000000000000000000000000000" :: Text))
-- different validator
-- validators: incorrect
, ("validators", toTList tTyString def $ map (tStr . asString) [("0x5DD34992E0994E9d3c53c1CCfe5C2e38d907338e" :: Text)])
, ("metadata", tStr $ asString ("0x0000000000000000000000002e234dae75c793f67a35089c9d99245e1c58470b00000000000000000000000000000000000000000000000000000000000000ad0000000f0e1c8be19e9e2bd14665599b8e8ed1f3dbca562788e5844975770eb31380b3ae5de03487e89a1d3c42fad8aac486a06e1af6b3478ec0d148c0c8566c404537291b" :: Text))
, ("threshold", tLit $ LInteger 1)
Expand All @@ -255,6 +257,7 @@ hyperlaneVerifyFailureIncorrectValidator = do
let
obj' = mkObject
[ ("message", tStr $ asString ("0x01000001450000027200000000000000000000000000000000006b622d746f6b656e2d726f757465720000000100000000000000000000000071c7656ec7ab88b098defb751b7401b5f6d8976f00000000000000000000000000000000000000000000000000000000000000400000000000000000000000000000000000000000000000008ac7230489e80000000000000000000000000000000000000000000000000000000000000000002a30783731433736353645433761623838623039386465664237353142373430314235663664383937364600000000000000000000000000000000000000000000" :: Text))
-- validators: badly formatted
, ("validators", toTList tTyString def $ map (tStr . asString) [("badValidator" :: Text)])
, ("metadata", tStr $ asString ("0x0000000000000000000000002e234dae75c793f67a35089c9d99245e1c58470b00000000000000000000000000000000000000000000000000000000000000ad0000000f0e1c8be19e9e2bd14665599b8e8ed1f3dbca562788e5844975770eb31380b3ae5de03487e89a1d3c42fad8aac486a06e1af6b3478ec0d148c0c8566c404537291b" :: Text))
, ("threshold", tLit $ LInteger 1)
Expand All @@ -265,11 +268,12 @@ hyperlaneVerifyFailureIncorrectValidator = do
Left err -> assertEqual "Verification should fail" "Failed to decode a validator (badValidator):decodeHex: does not start with 0x" err
Right _ -> assertFailure "Should fail"

hyperlaneVerifyFailureNotEnoughSignatures :: Assertion
hyperlaneVerifyFailureNotEnoughSignatures = do
hyperlaneVerifyFailureNotEnoughRecoveredSignatures :: Assertion
hyperlaneVerifyFailureNotEnoughRecoveredSignatures = do
let
obj' = mkObject
[ ("message", tStr $ asString ("0x01000001450000027200000000000000000000000000000000006b622d746f6b656e2d726f757465720000000100000000000000000000000071c7656ec7ab88b098defb751b7401b5f6d8976f00000000000000000000000000000000000000000000000000000000000000400000000000000000000000000000000000000000000000008ac7230489e80000000000000000000000000000000000000000000000000000000000000000002a30783731433736353645433761623838623039386465664237353142373430314235663664383937364600000000000000000000000000000000000000000000" :: Text))
-- validators: incorrect
, ("validators", toTList tTyString def $ map (tStr . asString) [("0x5DD34992E0994E9d3c53c1CCfe5C2e38d907338e" :: Text)])
-- metadata without signatures
, ("metadata", tStr $ asString ("0x0000000000000000000000002e234dae75c793f67a35089c9d99245e1c58470b00000000000000000000000000000000000000000000000000000000000000ad0000000f" :: Text))
Expand All @@ -280,3 +284,23 @@ hyperlaneVerifyFailureNotEnoughSignatures = do
case res of
Left err -> assertEqual "Verification should fail" "The number of recovered addresses from the signatures is less than threshold: 1" err
Right _ -> assertFailure "Should fail"

-- | We pass 2 signatures, 1st one matches to the correct validator,
-- but there is no second valid validator for the 2nd signature, and the verification fails.
hyperlaneVerifyFailureNotEnoughSignaturesToPassThreshold :: Assertion
hyperlaneVerifyFailureNotEnoughSignaturesToPassThreshold = do
let
obj' = mkObject
[ ("message", tStr $ asString ("0x01000001450000027200000000000000000000000000000000006b622d746f6b656e2d726f757465720000000100000000000000000000000071c7656ec7ab88b098defb751b7401b5f6d8976f00000000000000000000000000000000000000000000000000000000000000400000000000000000000000000000000000000000000000008ac7230489e80000000000000000000000000000000000000000000000000000000000000000002a30783731433736353645433761623838623039386465664237353142373430314235663664383937364600000000000000000000000000000000000000000000" :: Text))
, ("validators", toTList tTyString def $ map (tStr . asString)
-- validators: incorrect, correct, incorrect
["0x5DD34992E0994E9d3c53c1CCfe5C2e38d907338e" :: Text, "0x4BD34992E0994E9d3c53c1CCfe5C2e38d907338e", "0x55D34992E0994E9d3c53c1CCfe5C2e38d907338e"])
-- metadata with the 2 same signatures
, ("metadata", tStr $ asString ("0x0000000000000000000000002e234dae75c793f67a35089c9d99245e1c58470b00000000000000000000000000000000000000000000000000000000000000ad0000000f0e1c8be19e9e2bd14665599b8e8ed1f3dbca562788e5844975770eb31380b3ae5de03487e89a1d3c42fad8aac486a06e1af6b3478ec0d148c0c8566c404537291b0e1c8be19e9e2bd14665599b8e8ed1f3dbca562788e5844975770eb31380b3ae5de03487e89a1d3c42fad8aac486a06e1af6b3478ec0d148c0c8566c404537291b" :: Text))
, ("threshold", tLit $ LInteger 2)
]
res <- runExceptT $ evalHyperlaneCommand obj'

case res of
Left err -> assertEqual "Verification should fail" "Verification failed" err
Right _ -> assertFailure "Should fail"

0 comments on commit 7bdde97

Please sign in to comment.