diff --git a/plutus-ledger-api/src/PlutusLedgerApi/Common/ProtocolVersions.hs b/plutus-ledger-api/src/PlutusLedgerApi/Common/ProtocolVersions.hs index d0c3e900bb7..4e189ba2982 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/Common/ProtocolVersions.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/Common/ProtocolVersions.hs @@ -8,8 +8,8 @@ module PlutusLedgerApi.Common.ProtocolVersions , alonzoPV , vasilPV , valentinePV - , conwayPV - , conwayPlus1PV + , changPV + , changPlus1PV , knownPVs , futurePV ) where @@ -55,22 +55,23 @@ maryPV = MajorProtocolVersion 4 alonzoPV :: MajorProtocolVersion alonzoPV = MajorProtocolVersion 5 --- | Vasil era was introduced in protocol version 7.0 +-- | The Vasil HF introduced the Babbage era and Plutus V2 vasilPV :: MajorProtocolVersion vasilPV = MajorProtocolVersion 7 --- | Protocol version 8.0 was the Valentine intra-era HF +-- | Valentine was an intra-era HF where builtin functions @VerifyEcdsaSecp256k1Signature@ and +-- @VerifySchnorrSecp256k1Signature@ were enabled. valentinePV :: MajorProtocolVersion valentinePV = MajorProtocolVersion 8 --- | Conway era was introduced in protocol version 9.0 -conwayPV :: MajorProtocolVersion -conwayPV = MajorProtocolVersion 9 +-- | The Chang HF introduced the Conway era and Plutus V3 +changPV :: MajorProtocolVersion +changPV = MajorProtocolVersion 9 --- | The next HF after Conway. It doesn't yet have a name, and it's not --- yet known whether it will be an intra-era HF or introduce a new era. -conwayPlus1PV :: MajorProtocolVersion -conwayPlus1PV = MajorProtocolVersion 10 +-- | The Chang+1 HF will be an intra-era HF where some new builtin functions +-- are introduced in Plutus V2 and V3. +changPlus1PV :: MajorProtocolVersion +changPlus1PV = MajorProtocolVersion 10 -- | The set of protocol versions that are "known", i.e. that have been released -- and have actual differences associated with them. @@ -83,8 +84,8 @@ knownPVs = , alonzoPV , vasilPV , valentinePV - , conwayPV - , conwayPlus1PV + , changPV + , changPlus1PV ] -- | This is a placeholder for when we don't yet know what protocol version will diff --git a/plutus-ledger-api/src/PlutusLedgerApi/Common/Versions.hs b/plutus-ledger-api/src/PlutusLedgerApi/Common/Versions.hs index bf350e32e89..51c7b0be31a 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/Common/Versions.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/Common/Versions.hs @@ -107,10 +107,10 @@ builtinsIntroducedIn = Map.fromList [ ((PlutusV2, valentinePV), Set.fromList [ VerifyEcdsaSecp256k1Signature, VerifySchnorrSecp256k1Signature ]), - ((PlutusV2, conwayPlus1PV), Set.fromList [ + ((PlutusV2, changPlus1PV), Set.fromList [ IntegerToByteString, ByteStringToInteger ]), - ((PlutusV3, conwayPV), Set.fromList [ + ((PlutusV3, changPV), Set.fromList [ Bls12_381_G1_add, Bls12_381_G1_neg, Bls12_381_G1_scalarMul, Bls12_381_G1_equal, Bls12_381_G1_hashToGroup, Bls12_381_G1_compress, Bls12_381_G1_uncompress, @@ -137,7 +137,7 @@ See Note [New builtins/language versions and protocol versions] plcVersionsIntroducedIn :: Map.Map (PlutusLedgerLanguage, MajorProtocolVersion) (Set.Set Version) plcVersionsIntroducedIn = Map.fromList [ ((PlutusV1, alonzoPV), Set.fromList [ plcVersion100 ]), - ((PlutusV3, conwayPV), Set.fromList [ plcVersion110 ]) + ((PlutusV3, changPV), Set.fromList [ plcVersion110 ]) ] {-| Query the protocol version that a specific Plutus ledger language was first introduced in. @@ -146,7 +146,7 @@ ledgerLanguageIntroducedIn :: PlutusLedgerLanguage -> MajorProtocolVersion ledgerLanguageIntroducedIn = \case PlutusV1 -> alonzoPV PlutusV2 -> vasilPV - PlutusV3 -> conwayPV + PlutusV3 -> changPV {-| Which Plutus language versions are available in the given 'MajorProtocolVersion'? diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V1/EvaluationContext.hs b/plutus-ledger-api/src/PlutusLedgerApi/V1/EvaluationContext.hs index 03fcad8cfe4..cc5f7dfd20e 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V1/EvaluationContext.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V1/EvaluationContext.hs @@ -10,7 +10,7 @@ module PlutusLedgerApi.V1.EvaluationContext ) where import PlutusLedgerApi.Common -import PlutusLedgerApi.Common.Versions (conwayPV) +import PlutusLedgerApi.Common.Versions (changPV) import PlutusLedgerApi.V1.ParamName as V1 import PlutusCore.Default (BuiltinSemanticsVariant (DefaultFunSemanticsVariantA, DefaultFunSemanticsVariantB)) @@ -41,6 +41,6 @@ mkEvaluationContext = PlutusV1 [DefaultFunSemanticsVariantA, DefaultFunSemanticsVariantB] -- See Note [Mapping of protocol versions and ledger languages to semantics variants]. - (\pv -> if pv < conwayPV + (\pv -> if pv < changPV then DefaultFunSemanticsVariantA else DefaultFunSemanticsVariantB) diff --git a/plutus-ledger-api/src/PlutusLedgerApi/V2/EvaluationContext.hs b/plutus-ledger-api/src/PlutusLedgerApi/V2/EvaluationContext.hs index 8f0c43cb068..054883d3e49 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/V2/EvaluationContext.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/V2/EvaluationContext.hs @@ -10,7 +10,7 @@ module PlutusLedgerApi.V2.EvaluationContext ) where import PlutusLedgerApi.Common -import PlutusLedgerApi.Common.Versions (conwayPV) +import PlutusLedgerApi.Common.Versions (changPV) import PlutusLedgerApi.V2.ParamName as V2 import PlutusCore.Default (BuiltinSemanticsVariant (DefaultFunSemanticsVariantA, DefaultFunSemanticsVariantB)) @@ -41,6 +41,6 @@ mkEvaluationContext = PlutusV2 [DefaultFunSemanticsVariantA, DefaultFunSemanticsVariantB] -- See Note [Mapping of protocol versions and ledger languages to semantics variants]. - (\pv -> if pv < conwayPV + (\pv -> if pv < changPV then DefaultFunSemanticsVariantA else DefaultFunSemanticsVariantB) diff --git a/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V1.hs b/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V1.hs index 619727868b8..7603a95594b 100644 --- a/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V1.hs +++ b/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V1.hs @@ -53,8 +53,8 @@ expectSuccess name code arg = testCase name $ case res of Right _ -> pure () where sScript = serialiseCompiledCode code - script = either (error . show) id $ V1.deserialiseScript conwayPV sScript - (_, res) = V1.evaluateScriptCounting conwayPV V1.Quiet evalCtx script [arg] + script = either (error . show) id $ V1.deserialiseScript changPV sScript + (_, res) = V1.evaluateScriptCounting changPV V1.Quiet evalCtx script [arg] good :: CompiledCode (BuiltinData -> BuiltinUnit) good = diff --git a/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V2.hs b/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V2.hs index a86aaa5a9f5..de9169260f2 100644 --- a/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V2.hs +++ b/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V2.hs @@ -53,8 +53,8 @@ expectSuccess name code arg = testCase name $ case res of Right _ -> pure () where sScript = serialiseCompiledCode code - script = either (error . show) id $ V2.deserialiseScript conwayPV sScript - (_, res) = V2.evaluateScriptCounting conwayPV V2.Quiet evalCtx script [arg] + script = either (error . show) id $ V2.deserialiseScript changPV sScript + (_, res) = V2.evaluateScriptCounting changPV V2.Quiet evalCtx script [arg] good :: CompiledCode (BuiltinData -> BuiltinUnit) good = diff --git a/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V3.hs b/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V3.hs index 6572db090ef..3c221560c28 100644 --- a/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V3.hs +++ b/plutus-ledger-api/test-plugin/Spec/ReturnUnit/V3.hs @@ -52,8 +52,8 @@ expectSuccess name code arg = testCase name $ case res of Right _ -> pure () where sScript = serialiseCompiledCode code - script = either (error . show) id $ V3.deserialiseScript conwayPV sScript - (_, res) = V3.evaluateScriptCounting conwayPV V3.Quiet evalCtx script arg + script = either (error . show) id $ V3.deserialiseScript changPV sScript + (_, res) = V3.evaluateScriptCounting changPV V3.Quiet evalCtx script arg expectFailure :: forall a. @@ -68,8 +68,8 @@ expectFailure name code arg = testCase name $ case res of Right _ -> assertFailure "evaluation succeeded" where sScript = serialiseCompiledCode code - script = either (error . show) id $ V3.deserialiseScript conwayPV sScript - (_, res) = V3.evaluateScriptCounting conwayPV V3.Quiet evalCtx script arg + script = either (error . show) id $ V3.deserialiseScript changPV sScript + (_, res) = V3.evaluateScriptCounting changPV V3.Quiet evalCtx script arg good :: CompiledCode (BuiltinData -> BuiltinUnit) good = diff --git a/plutus-ledger-api/test/Spec.hs b/plutus-ledger-api/test/Spec.hs index ec9cf5dce1c..772faf953f5 100644 --- a/plutus-ledger-api/test/Spec.hs +++ b/plutus-ledger-api/test/Spec.hs @@ -65,8 +65,8 @@ availableBuiltins = testCase "builtins are available after Alonzo" $ integerToByteStringExceedsBudget :: TestTree integerToByteStringExceedsBudget = testCase "integerToByteString should exceed budget" $ - let script = either (error . show) id $ V3.deserialiseScript conwayPV integerToByteStringFunction - (_, res) = V3.evaluateScriptCounting conwayPV V3.Quiet v3_evalCtxTooFewParams script (I 1) + let script = either (error . show) id $ V3.deserialiseScript changPV integerToByteStringFunction + (_, res) = V3.evaluateScriptCounting changPV V3.Quiet v3_evalCtxTooFewParams script (I 1) in case res of Left _ -> assertFailure "fails" Right (ExBudget cpu _mem) -> assertBool "did not exceed budget" (cpu >= fromIntegral (maxBound :: Int64)) diff --git a/plutus-ledger-api/test/Spec/Data/Versions.hs b/plutus-ledger-api/test/Spec/Data/Versions.hs index 9eb99da7be9..ef2e2584f73 100644 --- a/plutus-ledger-api/test/Spec/Data/Versions.hs +++ b/plutus-ledger-api/test/Spec/Data/Versions.hs @@ -39,7 +39,7 @@ testLedgerLanguages :: TestTree testLedgerLanguages = testGroup "ledger languages" [ testProperty "v1 not before but after" $ prop_notBeforeButAfter V1.deserialiseScript alonzoPV , testProperty "v2 not before but after" $ prop_notBeforeButAfter V2.deserialiseScript vasilPV - , testProperty "v3 not before but after" $ prop_notBeforeButAfter V3.deserialiseScript conwayPV + , testProperty "v3 not before but after" $ prop_notBeforeButAfter V3.deserialiseScript changPV , testProperty "protocol-versions can add but not remove ledger languages" $ \pvA pvB -> pvA < pvB ==> ledgerLanguagesAvailableIn pvA `Set.isSubsetOf` ledgerLanguagesAvailableIn pvB ] @@ -90,13 +90,13 @@ testRmdr = testGroup "rmdr" [ testCase "remdr" $ do assertBool "remdr1" $ isRight $ V1.deserialiseScript valentinePV $ errorScript <> "remdr1" assertBool "remdr2" $ isRight $ V2.deserialiseScript valentinePV $ errorScript <> "remdr2" - assertBool "remdr1c" $ isRight $ V1.deserialiseScript conwayPV $ errorScript <> "remdr1" - assertBool "remdr2c" $ isRight $ V2.deserialiseScript conwayPV $ errorScript <> "remdr2" - assertEqual "remdr3" (RemainderError "remdr3") $ fromLeft (Prelude.error "Expected Reft, got Right") $ V3.deserialiseScript conwayPV $ errorScript <> "remdr3" + assertBool "remdr1c" $ isRight $ V1.deserialiseScript changPV $ errorScript <> "remdr1" + assertBool "remdr2c" $ isRight $ V2.deserialiseScript changPV $ errorScript <> "remdr2" + assertEqual "remdr3" (RemainderError "remdr3") $ fromLeft (Prelude.error "Expected Reft, got Right") $ V3.deserialiseScript changPV $ errorScript <> "remdr3" , testProperty "remdr1gen"$ \remdr -> isRight $ V1.deserialiseScript valentinePV $ errorScript <> BSS.pack remdr , testProperty "remdr2gen"$ \remdr -> isRight $ V2.deserialiseScript valentinePV $ errorScript <> BSS.pack remdr - , testProperty "remdr1genc"$ \remdr -> isRight $ V1.deserialiseScript conwayPV $ errorScript <> BSS.pack remdr - , testProperty "remdr2genc"$ \remdr -> isRight $ V2.deserialiseScript conwayPV $ errorScript <> BSS.pack remdr + , testProperty "remdr1genc"$ \remdr -> isRight $ V1.deserialiseScript changPV $ errorScript <> BSS.pack remdr + , testProperty "remdr2genc"$ \remdr -> isRight $ V2.deserialiseScript changPV $ errorScript <> BSS.pack remdr -- we cannot make the same property as above for remdr3gen because it may generate valid bytestring append extensions to the original script -- a more sophisticated one could work though ] @@ -108,12 +108,12 @@ testLanguageVersions = testGroup "Plutus Core language versions" -- `LedgerLanguageNotAvailableError` is checked in `deserialiseScript` assertBool "in l3,Vasil" $ isLeft $ uplcToScriptForEvaluation PlutusV3 vasilPV v110script -- `PlutusCoreLanguageNotAvailableError` is checked in `mkTermToEvaluate` - assertBool "in l2,future" $ isLeft $ mkTermToEvaluate PlutusV2 conwayPV (either (Prelude.error . show) id (V2.deserialiseScript conwayPV $ serialiseUPLC v110script)) [] + assertBool "in l2,future" $ isLeft $ mkTermToEvaluate PlutusV2 changPV (either (Prelude.error . show) id (V2.deserialiseScript changPV $ serialiseUPLC v110script)) [] -- Both `deserialiseScript` and `mkTermToEvaluate` should succeed - assertBool "not in l3,future" $ isRight $ mkTermToEvaluate PlutusV3 conwayPV (either (Prelude.error . show) id (V3.deserialiseScript conwayPV $ serialiseUPLC v110script)) [] + assertBool "not in l3,future" $ isRight $ mkTermToEvaluate PlutusV3 changPV (either (Prelude.error . show) id (V3.deserialiseScript changPV $ serialiseUPLC v110script)) [] -- The availability of `case` and `constr` is checked in `deserialise` - , testCase "constr is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 conwayPV badConstrScript - , testCase "case is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 conwayPV badCaseScript + , testCase "constr is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 changPV badConstrScript + , testCase "case is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 changPV badCaseScript ] -- * UPLC written examples to test diff --git a/plutus-ledger-api/test/Spec/ScriptDecodeError.hs b/plutus-ledger-api/test/Spec/ScriptDecodeError.hs index c02c62961ff..c8d1212f491 100644 --- a/plutus-ledger-api/test/Spec/ScriptDecodeError.hs +++ b/plutus-ledger-api/test/Spec/ScriptDecodeError.hs @@ -5,7 +5,7 @@ module Spec.ScriptDecodeError where import Codec.Extras.SerialiseViaFlat (DeserialiseFailureInfo (..), DeserialiseFailureReason (..)) import PlutusCore.Version (plcVersion100) import PlutusLedgerApi.Common (ScriptDecodeError (..)) -import PlutusLedgerApi.Common.Versions (PlutusLedgerLanguage (..), conwayPV, vasilPV) +import PlutusLedgerApi.Common.Versions (PlutusLedgerLanguage (..), changPV, vasilPV) import Prettyprinter (Pretty (pretty)) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (Assertion, testCase, (@?=)) @@ -56,7 +56,7 @@ prettyLedgerLanguageNotAvailableError = err = LedgerLanguageNotAvailableError { sdeAffectedLang = PlutusV2 - , sdeIntroPv = conwayPV + , sdeIntroPv = changPV , sdeThisPv = vasilPV } diff --git a/plutus-ledger-api/test/Spec/Versions.hs b/plutus-ledger-api/test/Spec/Versions.hs index 61b180ea852..093247a4e69 100644 --- a/plutus-ledger-api/test/Spec/Versions.hs +++ b/plutus-ledger-api/test/Spec/Versions.hs @@ -39,7 +39,7 @@ testLedgerLanguages :: TestTree testLedgerLanguages = testGroup "ledger languages" [ testProperty "v1 not before but after" $ prop_notBeforeButAfter V1.deserialiseScript alonzoPV , testProperty "v2 not before but after" $ prop_notBeforeButAfter V2.deserialiseScript vasilPV - , testProperty "v3 not before but after" $ prop_notBeforeButAfter V3.deserialiseScript conwayPV + , testProperty "v3 not before but after" $ prop_notBeforeButAfter V3.deserialiseScript changPV , testProperty "protocol-versions can add but not remove ledger languages" $ \pvA pvB -> pvA < pvB ==> ledgerLanguagesAvailableIn pvA `Set.isSubsetOf` ledgerLanguagesAvailableIn pvB ] @@ -90,13 +90,13 @@ testRmdr = testGroup "rmdr" [ testCase "remdr" $ do assertBool "remdr1" $ isRight $ V1.deserialiseScript valentinePV $ errorScript <> "remdr1" assertBool "remdr2" $ isRight $ V2.deserialiseScript valentinePV $ errorScript <> "remdr2" - assertBool "remdr1c" $ isRight $ V1.deserialiseScript conwayPV $ errorScript <> "remdr1" - assertBool "remdr2c" $ isRight $ V2.deserialiseScript conwayPV $ errorScript <> "remdr2" - assertEqual "remdr3" (RemainderError "remdr3") $ fromLeft (Prelude.error "Expected Reft, got Right") $ V3.deserialiseScript conwayPV $ errorScript <> "remdr3" + assertBool "remdr1c" $ isRight $ V1.deserialiseScript changPV $ errorScript <> "remdr1" + assertBool "remdr2c" $ isRight $ V2.deserialiseScript changPV $ errorScript <> "remdr2" + assertEqual "remdr3" (RemainderError "remdr3") $ fromLeft (Prelude.error "Expected Reft, got Right") $ V3.deserialiseScript changPV $ errorScript <> "remdr3" , testProperty "remdr1gen"$ \remdr -> isRight $ V1.deserialiseScript valentinePV $ errorScript <> BSS.pack remdr , testProperty "remdr2gen"$ \remdr -> isRight $ V2.deserialiseScript valentinePV $ errorScript <> BSS.pack remdr - , testProperty "remdr1genc"$ \remdr -> isRight $ V1.deserialiseScript conwayPV $ errorScript <> BSS.pack remdr - , testProperty "remdr2genc"$ \remdr -> isRight $ V2.deserialiseScript conwayPV $ errorScript <> BSS.pack remdr + , testProperty "remdr1genc"$ \remdr -> isRight $ V1.deserialiseScript changPV $ errorScript <> BSS.pack remdr + , testProperty "remdr2genc"$ \remdr -> isRight $ V2.deserialiseScript changPV $ errorScript <> BSS.pack remdr -- we cannot make the same property as above for remdr3gen because it may generate valid bytestring append extensions to the original script -- a more sophisticated one could work though ] @@ -108,12 +108,12 @@ testLanguageVersions = testGroup "Plutus Core language versions" -- `LedgerLanguageNotAvailableError` is checked in `deserialiseScript` assertBool "in l3,Vasil" $ isLeft $ uplcToScriptForEvaluation PlutusV3 vasilPV v110script -- `PlutusCoreLanguageNotAvailableError` is checked in `mkTermToEvaluate` - assertBool "in l2,future" $ isLeft $ mkTermToEvaluate PlutusV2 conwayPV (either (Prelude.error . show) id (V2.deserialiseScript conwayPV $ serialiseUPLC v110script)) [] + assertBool "in l2,future" $ isLeft $ mkTermToEvaluate PlutusV2 changPV (either (Prelude.error . show) id (V2.deserialiseScript changPV $ serialiseUPLC v110script)) [] -- Both `deserialiseScript` and `mkTermToEvaluate` should succeed - assertBool "not in l3,future" $ isRight $ mkTermToEvaluate PlutusV3 conwayPV (either (Prelude.error . show) id (V3.deserialiseScript conwayPV $ serialiseUPLC v110script)) [] + assertBool "not in l3,future" $ isRight $ mkTermToEvaluate PlutusV3 changPV (either (Prelude.error . show) id (V3.deserialiseScript changPV $ serialiseUPLC v110script)) [] -- The availability of `case` and `constr` is checked in `deserialise` - , testCase "constr is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 conwayPV badConstrScript - , testCase "case is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 conwayPV badCaseScript + , testCase "constr is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 changPV badConstrScript + , testCase "case is not available with v1.0.0 ever" $ assertBool "in l3,future" $ isLeft $ uplcToScriptForEvaluation PlutusV3 changPV badCaseScript ] -- * UPLC written examples to test