-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ {-# LANGUAGE DeriveAnyClass #-} -- | Tests for Lorentz compilation which uses 'LorentzCompilationWay'. module Test.EntryPoints ( test_EpAddress , test_ParamNotes , test_ParamEpError ) where import Prelude hiding (or) import Data.Default (def) import Fmt (pretty) import Test.HUnit (assertBool, (@?=)) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (testCase) import Michelson.Test.Util (runGen) import Michelson.Typed import Michelson.Untyped (ann, noAnn, unsafeBuildEpName) import Tezos.Address import Test.Util.Hedgehog test_EpAddress :: [TestTree] test_EpAddress = [ testGroup "Parsing" $ [ testCase "Simple entrypoint" $ parseEpAddress (formatAddress addr <> "%ab") @?= Right (EpAddress addr (unsafeBuildEpName "ab")) , testCase "No entrypoint" $ parseEpAddress (formatAddress addr) @?= Right (EpAddress addr def) , testCase "Weird entrypoint" $ parseEpAddress (formatAddress addr <> "%a%b") @?= Right (EpAddress addr (unsafeBuildEpName "a%b")) ] , testGroup "parse . format = pure" [ roundtripTreeSTB genEpAddress formatEpAddress parseEpAddress ] ] where addr = runGen 20 123 genAddress test_ParamNotes :: [TestTree] test_ParamNotes = [ testGroup "Duplications are handled" $ [ testCase "One duplicated entrypoint" $ mkParamNotes (or "a" "a" prim prim) noAnn @?= Left (ParamEpDuplicatedNames (unsafeBuildEpName "a" :| [])) , testCase "Several duplicated entrypoint" $ mkParamNotes (or "" "" (or "a" "b" prim prim) (or "b" "a" prim prim)) noAnn @?= Left (ParamEpDuplicatedNames (unsafeBuildEpName "a" :| [unsafeBuildEpName "b"])) , testCase "Duplicated default entrypoint" $ mkParamNotes (or "default" "default" prim prim) noAnn @?= Left (ParamEpDuplicatedNames (DefEpName :| [])) ] , testGroup "All entrypoints callable check" $ [ testCase "Non-callable entrypoint is detected in simple case" $ mkParamNotes (or "default" "" prim (or "" "q" prim prim)) noAnn @?= Left (ParamEpUncallableArm [AcRight, AcLeft]) , testCase "Non-callable entrypoint is detected in complex case" $ mkParamNotes (or "a" "" prim (or "" "default" (or "b" "" prim prim) prim)) noAnn @?= Left (ParamEpUncallableArm [AcRight, AcLeft, AcRight]) , testCase "Having all leaves named is enough for callability" $ mkParamNotes (or "default" "" prim (or "q" "" prim (or "a" "b" prim prim))) noAnn & assertBool "All arms should've considered callable" . isRight , testCase "Having all leaves named is enough for callability" $ mkParamNotes (or "default" "a" prim (or "" "" prim (or "" "" prim prim))) noAnn & assertBool "All arms should've considered callable" . isRight ] ] where or a1 a2 = NTOr noAnn (ann a1) (ann a2) prim = NTKey noAnn test_ParamEpError :: [TestTree] test_ParamEpError = [ testGroup "Buildable instance" [ testCase "Duplicated entrypoints error" $ pretty @_ @Text (ParamEpDuplicatedNames $ unsafeBuildEpName "a" :| [DefEpName]) @?= "Duplicated entrypoint names: 'a', ''" , testCase "Uncallable arms error" $ pretty @_ @Text (ParamEpUncallableArm [AcLeft, AcRight]) @?= "Due to presence of 'default' entrypoint, one of contract \"arms\" \ \cannot be called: \"left - right\" (in top-to-bottom order)" ] ]