-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA module Test.ParameterTypeGet ( test_parameterTypeGetUnit ) where import Test.HUnit (Assertion, assertEqual, assertFailure) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (testCase) import Lorentz qualified as L import Morley.Client.RPC.Getters import Morley.Client.RPC.Types import Morley.Micheline import Morley.Michelson.TypeCheck.TypeCheck (SomeParamType, mkSomeParamType) import Morley.Michelson.Typed import Morley.Michelson.Untyped qualified as U import Morley.Tezos.Address import Morley.Tezos.Address.Alias import Morley.Tezos.Address.Kinds import Test.Util import TestM testContract :: L.NiceParameterFull param => L.Contract param () () testContract = L.defaultContract $ L.cdr L.# L.nil L.# L.pair buildSmartContractState :: ContractAlias -> L.Contract param () () -> AccountState 'AddressKindContract buildSmartContractState alias contract = AccountState { asCounter = 100500 , asAlias = alias , asAccountData = ContractData OriginationScript { osCode = toExpression contract, osStorage = toExpression $ toVal () } Nothing } contractHash1, contractHash2, contractHash3 :: ContractHash contractHash1 = mkContractHashHack "lol" contractHash2 = mkContractHashHack "kek" contractHash3 = mkContractHashHack "mda" smartContractAddr1, smartContractAddr2, smartContractAddr3 :: ContractAddress smartContractAddr1 = ContractAddress contractHash1 smartContractAddr2 = ContractAddress contractHash2 smartContractAddr3 = ContractAddress contractHash3 fakeStateWithSmartContracts :: FakeState fakeStateWithSmartContracts = defaultFakeState { fsContracts = fromList $ [ (smartContractAddr1, buildSmartContractState "lol" (testContract @Natural)) , (smartContractAddr2, buildSmartContractState "kek" (testContract @Bool)) ] , fsImplicits = fromList $ one $ genesisState @1 } test_parameterTypeGetUnit :: TestTree test_parameterTypeGetUnit = testGroup "Fake test big map getter" [ testCase "Only parameters for smart contracts are extracted" $ expectContractMap (runFakeTest chainOperationHandlers fakeStateWithSmartContracts $ getContractsParameterTypes [smartContractAddr1, smartContractAddr2] ) $ fromList [ (contractHash1, unsafe . mkSomeParamType $ U.ParameterType (U.Ty U.TNat U.noAnn) U.noAnn) , (contractHash2, unsafe . mkSomeParamType $ U.ParameterType (U.Ty U.TBool U.noAnn) U.noAnn) ] , testCase "Parameter type for nonexistent smart contract is not extracted" $ expectContractMap (runFakeTest chainOperationHandlers fakeStateWithSmartContracts $ getContractsParameterTypes [smartContractAddr3] ) mempty ] where expectContractMap :: Either SomeException (Map ContractHash SomeParamType) -> Map ContractHash SomeParamType -> Assertion expectContractMap (Right found) expected = assertEqual "unexpected smart contract map" found expected expectContractMap (Left e) _ = assertFailure $ displayException e