Skip to content

Commit

Permalink
Introduce unit test causing the entrypoint name issue
Browse files Browse the repository at this point in the history
# Conflicts:
#	concordium-consensus/tests/scheduler/Spec.hs
  • Loading branch information
limemloh authored and td202 committed Sep 25, 2024
1 parent 89bae7f commit b0217ca
Show file tree
Hide file tree
Showing 2 changed files with 120 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,118 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-- | This module tests calling a contract from a contract and inspecting the return
-- message. Concretely it invokes a counter contract that maintains a 64-bit
-- counter in its state.
module SchedulerTests.SmartContracts.V1.Caller (tests) where

import Control.Monad
import qualified Data.ByteString.Short as BSS
import Data.Serialize (putByteString, putWord16le, putWord64le, runPut, putWord32le)
import Test.Hspec

import qualified Concordium.Crypto.SignatureScheme as SigScheme
import qualified Concordium.GlobalState.Persistent.BlockState as BS
import qualified Concordium.ID.Types as ID
import Concordium.Scheduler.DummyData
import Concordium.Scheduler.Runner
import qualified Concordium.Scheduler.Types as Types
import Concordium.Wasm
import qualified SchedulerTests.Helpers as Helpers

initialBlockState ::
(Types.IsProtocolVersion pv) =>
Helpers.PersistentBSM pv (BS.HashedPersistentBlockState pv)
initialBlockState =
Helpers.createTestBlockStateWithAccountsM
[Helpers.makeTestAccountFromSeed 100_000_000 0]

accountAddress0 :: ID.AccountAddress
accountAddress0 = Helpers.accountAddressFromSeed 0

keyPair0 :: SigScheme.KeyPair
keyPair0 = Helpers.keyPairFromSeed 0

contractSourceFile :: FilePath
contractSourceFile = "../concordium-base/smart-contracts/testdata/contracts/v1/caller.wasm"

-- Tests in this module use version 1, creating V1 instances.
wasmModVersion :: WasmVersion
wasmModVersion = V1

test1 ::
forall pv.
(Types.IsProtocolVersion pv) =>
Types.SProtocolVersion pv ->
String ->
Spec
test1 spv pvString =
when (Types.supportsV1Contracts spv) $
specify (pvString ++ ": Calling another smart contract using entrypoint name containing '<>' fails.") $
Helpers.runSchedulerTestAssertIntermediateStates
@pv
Helpers.defaultTestConfig
initialBlockState
transactionsAndAssertions
where
transactionsAndAssertions :: [Helpers.TransactionAndAssertion pv]
transactionsAndAssertions =
[ Helpers.TransactionAndAssertion
{ taaTransaction =
TJSON
{ payload = DeployModule wasmModVersion contractSourceFile,
metadata = makeDummyHeader accountAddress0 1 100_000,
keys = [(0, [(0, keyPair0)])]
},
taaAssertion = \result _ ->
return $ do
Helpers.assertSuccess result
Helpers.assertUsedEnergyDeploymentV1 contractSourceFile result
},
Helpers.TransactionAndAssertion
{ taaTransaction =
TJSON
{ payload = InitContract 0 wasmModVersion contractSourceFile "init_caller" "",
metadata = makeDummyHeader accountAddress0 2 100_000,
keys = [(0, [(0, keyPair0)])]
},
taaAssertion = \result _ -> do
return $ do
Helpers.assertSuccess result
Helpers.assertUsedEnergyInitialization
(Types.protocolVersion @pv)
contractSourceFile
(InitName "init_caller")
(Parameter "")
Nothing
result
},
Helpers.TransactionAndAssertion
{ taaTransaction =
TJSON
{ payload = Update 0 (Types.ContractAddress 0 0) "caller.call" callArgs,
metadata = makeDummyHeader accountAddress0 3 700_000,
keys = [(0, [(0, keyPair0)])]
},
taaAssertion = \result _ -> do
return $ do
Helpers.assertSuccess result
}
]
callArgs = BSS.toShort $ runPut $ do
putWord32le 1 -- invoke instruction (call to contract)
putWord64le 0 -- contract index
putWord64le 0 -- contract subindex
putWord16le 0 -- length of parameter
putWord16le (fromIntegral (BSS.length "<String>"))
putByteString "<String>" -- entrypoint name
putWord64le 0 -- amount

tests :: Spec
tests =
describe "V1: Calling other smart contracts" $
sequence_ $
Helpers.forEveryProtocolVersion test1
2 changes: 2 additions & 0 deletions concordium-consensus/tests/scheduler/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ import qualified SchedulerTests.SmartContracts.V1.TransfersPersistent (tests)
import qualified SchedulerTests.SmartContracts.V1.Upgrading (tests)
import qualified SchedulerTests.SmartContracts.V1.UpgradingPersistent (tests)
import qualified SchedulerTests.SmartContracts.V1.ValidInvalidModules (tests)
import qualified SchedulerTests.SmartContracts.V1.Caller (tests)

import Test.Hspec

Expand Down Expand Up @@ -103,3 +104,4 @@ main = hspec $ do
SchedulerTests.SmartContracts.V1.P6WasmFeatures.tests
SchedulerTests.SmartContracts.V1.CustomSectionSize.tests
SchedulerTests.SmartContracts.V1.AccountSignatureChecks.tests
SchedulerTests.SmartContracts.V1.Caller.tests

0 comments on commit b0217ca

Please sign in to comment.