Skip to content

Commit

Permalink
Add unit test to make sure balance queries preserve state.
Browse files Browse the repository at this point in the history
  • Loading branch information
abizjak committed Nov 11, 2022
1 parent 3a3ff23 commit 1bfc9e6
Show file tree
Hide file tree
Showing 4 changed files with 139 additions and 0 deletions.
Binary file not shown.
39 changes: 39 additions & 0 deletions concordium-consensus/testdata/contracts/v1/queries-cases.wat
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
(module

;; Imports
(import "concordium" "get_parameter_section" (func $host_get_parameter_section (param $index i32) (param $write_location i32) (param $length i32) (param $offset i32) (result i32)))

(import "concordium" "invoke" (func $host_invoke (param $tag i32) (param $start i32) (param $length i32) (result i64)))
(import "concordium" "state_create_entry" (func $state_create_entry (param $key_start i32) (param $key_length i32) (result i64)))
(import "concordium" "state_entry_write" (func $state_entry_write (param $entry i64) (param $read_location i32) (param $length i32) (param $offset i32) (result i32)))


;; Initialize contract.
(func $init (export "init_contract") (param i64) (result i32)
(return (i32.const 0))) ;; Successful init

(func (export "contract.query_account") (param $amount i64) (result i32)
;; Read account address (32 bytes), an amount (8 bytes) used for transfer and a flag (1 byte) from the parameter into memory. Setting the flag to: 0 means do not update the state, 1 means update the state before invoking transfer, 2 means update the state after invoking transfer.
;; 0 means do not update the state, 1 means do
(call $host_get_parameter_section
(i32.const 0) ;; index.
(i32.const 0) ;; starting write offset in memory.
(i32.const 33) ;; number of bytes to read.
(i32.const 0)) ;; starting offset in parameter.
(if (i32.eq (i32.const 1) (i32.load8_u (i32.const 32)))
;; update the state now
(then (call $state_entry_write (call $state_create_entry (i32.const 0) (i32.const 32)) (i32.const 0) (i32.const 32) (i32.const 0))
drop
)
)
;; query
(call $host_invoke (i32.const 2) (i32.const 0) (i32.const 32))

(if (i32.eq (i32.const 2) (i32.load8_u (i32.const 32)))
(then (call $state_entry_write (call $state_create_entry (i32.const 0) (i32.const 32)) (i32.const 0) (i32.const 32) (i32.const 0))
drop
)
)
;; Return signal to succeed
(return (i32.const 0)))
(memory 1))
Original file line number Diff line number Diff line change
@@ -0,0 +1,98 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

-- |Tests that make sure that doing chain queries in smart contracts
-- correctly handles state changes.
module SchedulerTests.SmartContracts.V1.QueriesPersistent (tests) where

import Test.HUnit (Assertion, assertEqual, assertFailure)
import Test.Hspec

import Control.Monad.RWS.Strict
import qualified Data.ByteString as BS
import qualified Data.ByteString.Short as BSS
import qualified Data.Serialize as S
import Data.Word

import qualified Concordium.Scheduler.Types as Types

import Concordium.GlobalState.BlockState
import qualified Concordium.Scheduler.Runner as SchedTest
import Concordium.Types.Execution
import qualified Concordium.Wasm as Wasm
import qualified Concordium.GlobalState.ContractStateV1 as StateV1
import qualified Concordium.GlobalState.Persistent.Instances as Instances

import Concordium.Crypto.DummyData
import Concordium.Scheduler.DummyData
import Concordium.Types.DummyData

import SchedulerTests.SmartContracts.V1.PersistentStateHelpers

-- The module which supports transfers and state updates.
testModuleSourceFile :: FilePath
testModuleSourceFile = "./testdata/contracts/v1/queries-cases.wasm"

-- Construct a basic upgrade test case.
-- Deploy two modules, initialize an instance from the module that supports an upgrade,
-- and then do the upgrade.
-- The Word8 should be 0 for no state changes, 1 for a state change **before** the upgrade,
-- and 2 for a state change **after** the upgrade
testCase :: Word8 -> [SchedTest.TransactionJSON]
testCase changeState =
[ SchedTest.TJSON
{ payload = SchedTest.DeployModule Wasm.V1 testModuleSourceFile
, metadata = makeDummyHeader alesAccount 1 1_000
, keys = [(0, [(0, alesKP)])]
}
, SchedTest.TJSON
{ payload = SchedTest.InitContract 1_000 Wasm.V1 testModuleSourceFile "init_contract" ""
, metadata = makeDummyHeader alesAccount 2 1_000
, keys = [(0, [(0, alesKP)])]
}
, SchedTest.TJSON
{ payload = SchedTest.Update 0 (Types.ContractAddress 0 0) "contract.query_account" upgradeParameters
, metadata = makeDummyHeader alesAccount 3 10_000
, keys = [(0, [(0, alesKP)])]
}
]
where
-- the upgrade parameters are the address to send to, the amount, and the tag stating whether the state should or should not be updated
upgradeParameters = BSS.toShort (S.runPut (S.put alesAccount <> S.putWord8 changeState))

-- Run the transfer tests in different scenarios. The Word8 indicates how the state should be changed.
-- 0 for no change, 1 for change before transfer, 2 for change after transfer.
-- The boolean indicates whether to reload the state before querying the final value.
runQueryTests :: Word8 -> Bool -> Assertion
runQueryTests changeState reloadState = do
(outcomes, (bal, newState)) <- runTest (testCase changeState) reloadState $ \ubs ->
bsoGetInstance ubs (Types.ContractAddress 0 0) >>= \case
Nothing -> error "Missing instance."
Just (InstanceInfoV0 _) -> error "Expected V1 instance, but got V0."
Just (InstanceInfoV1 ii) -> do
let Instances.InstanceStateV1 s = iiState ii
bs <- StateV1.toByteString s
return (iiBalance ii, bs)
forM_ outcomes $ \(_, summary) -> do
case tsResult summary of
TxSuccess{} -> return ()
TxReject{..} -> assertFailure $ "Transaction rejected: " ++ show vrRejectReason
assertEqual "Amount was not" 1_000 bal
if changeState /= 0 then
assertEqual "State was updated" 1 (BS.index newState 0) -- non-empty state serialization starts with a 1 tag.
else
assertEqual "State was not updated" (BS.singleton 0) newState -- empty state serialization just puts a 0 tag.

tests :: Spec
tests = describe "Upgrade contract cases with persistent state" $ do
specify "V1: Just query" $ runQueryTests 0 False
specify "V1: Query + state update before" $ runQueryTests 1 False
specify "V1: Query + state update after" $ runQueryTests 2 False
specify "V1: Reload: Just query" $ runQueryTests 0 True
specify "V1: Reload: Query + state update before" $ runQueryTests 1 True
specify "V1: Reload: Query + state update after" $ runQueryTests 2 True
2 changes: 2 additions & 0 deletions concordium-consensus/tests/scheduler/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ import qualified SchedulerTests.SmartContracts.V1.Queries (tests)
import qualified SchedulerTests.SmartContracts.V1.RelaxedRestrictions (tests)
import qualified SchedulerTests.SmartContracts.V1.UpgradingPersistent (tests)
import qualified SchedulerTests.SmartContracts.V1.TransfersPersistent (tests)
import qualified SchedulerTests.SmartContracts.V1.QueriesPersistent (tests)

import Test.Hspec

Expand Down Expand Up @@ -93,5 +94,6 @@ main = hspec $ do
SchedulerTests.SmartContracts.V1.RelaxedRestrictions.tests
SchedulerTests.SmartContracts.V1.UpgradingPersistent.tests
SchedulerTests.SmartContracts.V1.TransfersPersistent.tests
SchedulerTests.SmartContracts.V1.QueriesPersistent.tests
SchedulerTests.Payday.tests
SchedulerTests.Delegation.tests

0 comments on commit 1bfc9e6

Please sign in to comment.