Skip to content

Commit

Permalink
Merge pull request #2075 from kadena-io/push-lswylwryrzot
Browse files Browse the repository at this point in the history
Add Pact5.RemotePactTest.invalidTxsTest
  • Loading branch information
edmundnoble authored Dec 18, 2024
2 parents 4454a46 + cd113eb commit 7b58aa2
Showing 1 changed file with 105 additions and 2 deletions.
107 changes: 105 additions & 2 deletions test/unit/Chainweb/Test/Pact5/RemotePactTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ import Chainweb.Utils
import Chainweb.Version
import Chainweb.WebPactExecutionService
import Control.Concurrent
import Control.Exception (Exception, AsyncException(..))
import Control.Exception (Exception, AsyncException(..), try)
import Control.Lens
import Control.Monad.Catch (throwM)
import Control.Monad.IO.Class (liftIO)
Expand All @@ -89,6 +89,12 @@ import Servant.Client
import Test.Tasty
import Test.Tasty.HUnit (assertEqual, testCase)
import qualified Pact.Types.Command as Pact4
import qualified Pact.Core.Command.Types as Pact5

Check warning on line 92 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, macos-latest, true)

The qualified import of ‘Pact.Core.Command.Types’ is redundant

Check warning on line 92 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, ubuntu-22.04, false)

The qualified import of ‘Pact.Core.Command.Types’ is redundant

Check warning on line 92 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.10.1, 3.12, ubuntu-22.04, false)

The qualified import of ‘Pact.Core.Command.Types’ is redundant

Check warning on line 92 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.6.6, 3.12, ubuntu-22.04, false)

The qualified import of ‘Pact.Core.Command.Types’ is redundant

Check warning on line 92 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, ubuntu-22.04, true)

The qualified import of ‘Pact.Core.Command.Types’ is redundant
import qualified Data.HashMap.Strict as HM

Check warning on line 93 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, macos-latest, true)

The qualified import of ‘Data.HashMap.Strict’ is redundant

Check warning on line 93 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, ubuntu-22.04, false)

The qualified import of ‘Data.HashMap.Strict’ is redundant

Check warning on line 93 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.10.1, 3.12, ubuntu-22.04, false)

The qualified import of ‘Data.HashMap.Strict’ is redundant

Check warning on line 93 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.6.6, 3.12, ubuntu-22.04, false)

The qualified import of ‘Data.HashMap.Strict’ is redundant

Check warning on line 93 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, ubuntu-22.04, true)

The qualified import of ‘Data.HashMap.Strict’ is redundant
import GHC.Stack (HasCallStack)

Check warning on line 94 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, macos-latest, true)

The import of ‘GHC.Stack’ is redundant

Check warning on line 94 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, ubuntu-22.04, false)

The import of ‘GHC.Stack’ is redundant

Check warning on line 94 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.10.1, 3.12, ubuntu-22.04, false)

The import of ‘GHC.Stack’ is redundant

Check warning on line 94 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.6.6, 3.12, ubuntu-22.04, false)

The import of ‘GHC.Stack’ is redundant

Check warning on line 94 in test/unit/Chainweb/Test/Pact5/RemotePactTest.hs

View workflow job for this annotation

GitHub Actions / Build (9.8.2, 3.12, ubuntu-22.04, true)

The import of ‘GHC.Stack’ is redundant
import Data.String (fromString)
import qualified Data.Text.Encoding as T
import qualified Data.Text as T

data Fixture = Fixture
{ _cutFixture :: CutFixture.Fixture
Expand Down Expand Up @@ -141,6 +147,7 @@ tests rdb = testGroup "Pact5 RemotePactTest"
[ testCase "pollingInvalidRequestKeyTest" (pollingInvalidRequestKeyTest rdb)
, testCase "pollingConfirmationDepthTest" (pollingConfirmationDepthTest rdb)
, testCase "spvTest" (spvTest rdb)
, testCase "invalidTxsTest" (invalidTxsTest rdb)
]

pollingInvalidRequestKeyTest :: RocksDb -> IO ()
Expand Down Expand Up @@ -285,6 +292,100 @@ spvTest baseRdb = runResourceT $ do

pure ()

fails :: Exception e => P.Prop e -> P.Prop (IO a)
fails p actual = try actual >>= \case
Left e -> p e
_ -> P.fail "a failed computation" actual

invalidTxsTest :: RocksDb -> IO ()
invalidTxsTest baseRdb = runResourceT $ do
let v = pact5InstantCpmTestVersion petersonChainGraph
fixture <- mkFixture v baseRdb
let clientEnv = fixture ^. serviceClientEnv

let cid = unsafeChainId 0

let assertExnContains expectedErrStr (SendingException actualErrStr)
| expectedErrStr `List.isInfixOf` actualErrStr = P.succeed actualErrStr
| otherwise =
P.fail ("Error containing: " <> fromString expectedErrStr) actualErrStr

let validationFailedPrefix cmd = "Validation failed for hash " <> sshow (_cmdHash cmd) <> ": "

liftIO $ do
cmdParseFailure <- buildTextCmd v
$ set cbChainId cid
$ set cbRPC (mkExec "(+ 1" PUnit)
$ defaultCmd
sending v cid clientEnv (NE.singleton cmdParseFailure)
& fails ? assertExnContains "Pact parse error"

cmdInvalidPayloadHash <- do
bareCmd <- buildTextCmd v
$ set cbChainId cid
$ set cbRPC (mkExec "(+ 1 2)" (mkKeySetData "sender00" [sender00]))
$ defaultCmd
pure $ bareCmd
{ _cmdHash = Pact5.hash "fakehash"
}
sending v cid clientEnv (NE.singleton cmdInvalidPayloadHash)
& fails ? assertExnContains (validationFailedPrefix cmdInvalidPayloadHash <> "Invalid transaction hash")

cmdSignersSigsLengthMismatch1 <- do
bareCmd <- buildTextCmd v
$ set cbSigners [mkEd25519Signer' sender00 []]
$ set cbChainId cid
$ set cbRPC (mkExec "(+ 1 2)" (mkKeySetData "sender00" [sender00]))
$ defaultCmd
pure $ bareCmd
{ _cmdSigs = []
}
sending v cid clientEnv (NE.singleton cmdSignersSigsLengthMismatch1)
& fails ? assertExnContains (validationFailedPrefix cmdSignersSigsLengthMismatch1 <> "Invalid transaction sigs")

cmdSignersSigsLengthMismatch2 <- liftIO $ do
bareCmd <- buildTextCmd v
$ set cbSigners []
$ set cbChainId cid
$ set cbRPC (mkExec "(+ 1 2)" (mkKeySetData "sender00" [sender00]))
$ defaultCmd
pure $ bareCmd
{ -- This is an invalid ED25519 signature, but length signers == length signatures is checked first
_cmdSigs = [ED25519Sig "fakeSig"]
}
sending v cid clientEnv (NE.singleton cmdSignersSigsLengthMismatch2)
& fails ? assertExnContains (validationFailedPrefix cmdSignersSigsLengthMismatch2 <> "Invalid transaction sigs")

cmdInvalidUserSig <- liftIO $ do
bareCmd <- buildTextCmd v
$ set cbSigners [mkEd25519Signer' sender00 []]
$ set cbChainId cid
$ set cbRPC (mkExec "(+ 1 2)" (mkKeySetData "sender00" [sender00]))
$ defaultCmd
pure $ bareCmd
{ _cmdSigs = [ED25519Sig "fakeSig"]
}

sending v cid clientEnv (NE.singleton cmdInvalidUserSig)
& fails ? assertExnContains (validationFailedPrefix cmdInvalidUserSig <> "Invalid transaction sigs")

cmdGood <- buildTextCmd v
$ set cbSigners [mkEd25519Signer' sender00 []]
$ set cbChainId cid
$ set cbRPC (mkExec "(+ 1 2)" (mkKeySetData "sender00" [sender00]))
$ defaultCmd
-- Test that [badCmd, goodCmd] fails on badCmd, and the batch is rejected.
-- We just re-use a previously built bad cmd.
sending v cid clientEnv (NE.fromList [cmdInvalidUserSig, cmdGood])
& fails ? assertExnContains (validationFailedPrefix cmdInvalidUserSig <> "Invalid transaction sigs")
-- Test that [goodCmd, badCmd] fails on badCmd, and the batch is rejected.
-- Order matters, and the error message also indicates the position of the
-- failing tx.
-- We just re-use a previously built bad cmd.
sending v cid clientEnv (NE.fromList [cmdGood, cmdInvalidUserSig])
& fails ? assertExnContains (validationFailedPrefix cmdInvalidUserSig <> "Invalid transaction sigs")


{-
recvPwos <- runCutWithTx v pacts targetMempoolRef blockDb $ \_n _bHeight _bHash bHeader -> do
buildCwCmd "transfer-crosschain" v
Expand Down Expand Up @@ -383,7 +484,9 @@ sending v cid clientEnv cmds = do
let batch = Pact4.SubmitBatch (NE.map toPact4Command cmds)
send <- runClientM (pactSendApiClient v cid batch) clientEnv
case send of
Left e -> do
Left (FailureResponse _req resp) -> do
throwM (SendingException (T.unpack $ T.decodeUtf8 $ BL.toStrict (responseBody resp)))
Left e ->
throwM (SendingException (show e))
Right (Pact4.RequestKeys response) -> do
return (NE.map toPact5RequestKey response)
Expand Down

0 comments on commit 7b58aa2

Please sign in to comment.