From 6074a581b614c7ee6b287cca80fdc04d23add1a5 Mon Sep 17 00:00:00 2001 From: Ziyang Liu Date: Thu, 18 Apr 2024 14:35:13 -0700 Subject: [PATCH 1/3] Change CMTooFewParamsError to a warning --- .../Evaluation/Machine/CostModelInterface.hs | 44 ++++++++++++------- .../src/PlutusLedgerApi/Common/ParamName.hs | 7 ++- 2 files changed, 32 insertions(+), 19 deletions(-) diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs index 39072b91a5a..4e51f79602d 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs @@ -119,24 +119,37 @@ one plutus runtime a.k.a. `plutus-ledger-api.EvaluationContext` per plutus-versi 4) The node software will always pass the array in its entirety to each plutus-runtime, and not partially just the updated-parameter values (in case of (b)) or just the new-parameter values (in case of (c)). -There is one complication when (c) happens and some running nodes are not updated: -these nodes are only aware of the old set of builtins, thus they expect a specific (fixed in software) -number of cost model parameters. -To guarantee smooth,continuous operation of the entire network (and not cause any splits) -we allow the old nodes to continue operating when receiving more cost model parameters -than they expected, and only issue a warning to them. When the nodes restart and update to the new node software -these warnings will go away. The overall logic for the expected number of cost model paremeters is as follows: +To make (c) work, we must allow a node to continue operating when receiving either more or +fewer cost model parameters than it expects. As an example, suppose at the beginning of +major protocol version 9 (PV9), PlutusV3 has 100 cost model parameters. During PV9, we add +some more builtins to Plutus V3 (to be enabled after the hard fork, at PV10), requiring 20 +additional cost model parameters. Then, one submits a proposal updating the number of PlutusV3 +cost model parameters to 120. + +During PV9, both node-9.x and node-10.x must operate normally and agree on everything. This means +node-9.x must allow receiving more cost model parameters than it expects (since it may receive +120), and node-10.x must allow receiving fewer than it expects (since it may receive 100). +Node-10.x should fill in the missing parameters with a large enough number to prevent the new +builtins from being used, in case the hard fork to PV10 happens without first updating the number +of PlutusV3 cost model parameters to 120 (which is unlikely to happen, but just in case). + +During PV10, node-9.x stops working. + +The overall logic for the expected number of cost model paremeters is as follows: (expected number in node software == received number by ledger) => NOWARNING & NOERROR (expected number in node software < received number by ledger) => WARNING -(expected number in node software > received number by ledger) => ERROR +(expected number in node software > received number by ledger) => WARNING -If the received number is EQ or GT the expected (WARNING), the plutus software +If the received number is EQ or GT the expected (WARNING), we will take the first n from the received cost model parameters (n==expected number), and create the internal (nameful) representation of cost model parameters, by assigning a parameter name to its value: see `PlutusLedgerApi.Common.ParamName.tagWithParamNames` and the `ParamName` datatypes in plutus-ledger-api. +If the received number is LT the expected (WARNING), we will fill in the missing parameters +with maxBound :: Int64. + See https://github.com/IntersectMBO/cardano-ledger/issues/2902 for a discussion of these issues and the rationale for adopting the system described above. @@ -173,31 +186,28 @@ data CostModelApplyError = -- ^ internal error when we are transforming the applyParams' input to json (should not happen) | CMInternalWriteError !String -- ^ internal error when we are transforming the applied params from json with given jsonstring error (should not happen) - | CMTooFewParamsError { cmTooFewExpected :: !Int, cmTooFewActual :: !Int } - -- ^ See Note [Cost model parameters from the ledger's point of view] deriving stock (Eq, Show, Generic, Data) deriving anyclass (Exception, NFData, NoThunks) -- | A non-fatal warning when trying to create a cost given some plain costmodel parameters. data CostModelApplyWarn = - CMTooManyParamsWarn { cmTooManyExpected :: !Int, cmTooManyActual :: !Int } - {- ^ More costmodel parameters given, than expected - - See Note [Cost model parameters from the ledger's point of view] - -} + CMTooManyParamsWarn { cmTooManyExpected :: !Int, cmTooManyActual :: !Int } + -- ^ See Note [Cost model parameters from the ledger's point of view] + | CMTooFewParamsWarn { cmTooFewExpected :: !Int, cmTooFewActual :: !Int } + -- ^ See Note [Cost model parameters from the ledger's point of view] instance Pretty CostModelApplyError where pretty = (preamble <+>) . \case CMUnknownParamError k -> "Unknown cost model parameter:" <+> pretty k CMInternalReadError -> "Internal problem occurred upon reading the given cost model parameteres" CMInternalWriteError str -> "Internal problem occurred upon generating the applied cost model parameters with JSON error:" <+> pretty str - CMTooFewParamsError{..} -> "Too few cost model parameters passed, expected" <+> pretty cmTooFewExpected <+> "but got" <+> pretty cmTooFewActual where preamble = "applyParams error:" instance Pretty CostModelApplyWarn where pretty = (preamble <+>) . \case CMTooManyParamsWarn{..} -> "Too many cost model parameters passed, expected" <+> pretty cmTooManyExpected <+> "but got" <+> pretty cmTooManyActual + CMTooFewParamsWarn{..} -> "Too few cost model parameters passed, expected" <+> pretty cmTooFewExpected <+> "but got" <+> pretty cmTooFewActual where preamble = "applyParams warn:" diff --git a/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs b/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs index 1ee1da2a3b8..dbc302fc0b2 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs @@ -17,6 +17,7 @@ import PlutusCore.Evaluation.Machine.CostModelInterface import Control.Monad.Except import Control.Monad.Writer.Strict import Data.Char (toLower) +import Data.Int (Int64) import Data.List as List (lookup) import Data.Map qualified as Map import Data.Text qualified as Text @@ -99,9 +100,11 @@ tagWithParamNames ledgerParams = tell [CMTooManyParamsWarn {cmTooManyExpected = lenExpected, cmTooManyActual = lenActual}] -- zip will truncate/ignore any extraneous parameter values pure $ zip paramNames ledgerParams - GT -> + GT -> do + -- Too few parameters - substitute a large number for the missing parameters -- See Note [Cost model parameters from the ledger's point of view] - throwError $ CMTooFewParamsError {cmTooFewExpected = lenExpected, cmTooFewActual = lenActual } + tell [CMTooFewParamsWarn {cmTooFewExpected = lenExpected, cmTooFewActual = lenActual}] + pure $ zip paramNames (ledgerParams ++ repeat (toInteger (maxBound :: Int64))) -- | Untags the plutus version from the typed cost model parameters and returns their raw textual form -- (internally used by CostModelInterface). From 691b1e12c696cf25c021d0ed4a616b0cd0a51eb3 Mon Sep 17 00:00:00 2001 From: Ziyang Liu Date: Fri, 19 Apr 2024 02:53:06 -0700 Subject: [PATCH 2/3] Add a test --- plutus-ledger-api/test/Spec.hs | 28 +++++++++++++++---- .../testlib/PlutusLedgerApi/Test/Examples.hs | 13 ++++++++- 2 files changed, 35 insertions(+), 6 deletions(-) diff --git a/plutus-ledger-api/test/Spec.hs b/plutus-ledger-api/test/Spec.hs index 2380a62711b..f0854d4af92 100644 --- a/plutus-ledger-api/test/Spec.hs +++ b/plutus-ledger-api/test/Spec.hs @@ -4,7 +4,9 @@ module Main where import PlutusLedgerApi.Common.Versions import PlutusLedgerApi.Test.Examples import PlutusLedgerApi.Test.V1.EvaluationContext qualified as V1 +import PlutusLedgerApi.Test.V3.EvaluationContext qualified as V3 import PlutusLedgerApi.V1 as V1 +import PlutusLedgerApi.V3 as V3 import PlutusPrelude import Spec.CBOR.DeserialiseFailureInfo qualified import Spec.ContextDecoding qualified @@ -21,23 +23,30 @@ import Test.Tasty.HUnit import Test.Tasty.QuickCheck import Control.Monad.Writer +import Data.Int (Int64) main :: IO () main = defaultMain tests -v1_evalCtxForTesting :: EvaluationContext +v1_evalCtxForTesting :: V1.EvaluationContext v1_evalCtxForTesting = fst $ unsafeFromRight $ runWriterT $ V1.mkEvaluationContext (fmap snd V1.costModelParamsForTesting) +-- | Constructing a V3 context with the first 223 parameters. +-- As a result, the cost model parameters for `integerToByteString` and `byteStringToInteger` +-- should be set to large numbers, preventing them from being used. +v3_evalCtxTooFewParams :: V3.EvaluationContext +v3_evalCtxTooFewParams = fst $ unsafeFromRight $ runWriterT $ V3.mkEvaluationContext (take 223 $ fmap snd V3.costModelParamsForTesting) + alwaysTrue :: TestTree alwaysTrue = testCase "always true script returns true" $ let script = either (error . show) id $ V1.deserialiseScript alonzoPV (alwaysSucceedingNAryFunction 2) - (_, res) = evaluateScriptCounting alonzoPV Quiet v1_evalCtxForTesting script [I 1, I 2] + (_, res) = V1.evaluateScriptCounting alonzoPV V1.Quiet v1_evalCtxForTesting script [I 1, I 2] in assertBool "succeeds" (isRight res) alwaysFalse :: TestTree alwaysFalse = testCase "always false script returns false" $ let script = either (error . show) id $ V1.deserialiseScript alonzoPV (alwaysFailingNAryFunction 2) - (_, res) = evaluateScriptCounting alonzoPV Quiet v1_evalCtxForTesting script [I 1, I 2] + (_, res) = V1.evaluateScriptCounting alonzoPV V1.Quiet v1_evalCtxForTesting script [I 1, I 2] in assertBool "fails" (isLeft res) unavailableBuiltins :: TestTree @@ -50,13 +59,21 @@ availableBuiltins = testCase "builtins are available after Alonzo" $ let res = V1.deserialiseScript alonzoPV summingFunction in assertBool "succeeds" (isRight res) +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 [] + in case res of + Left _ -> assertFailure "fails" + Right (ExBudget cpu _mem) -> assertBool "did not exceed budget" (cpu >= fromIntegral (maxBound :: Int64)) + saltedFunction :: TestTree saltedFunction = let evaluate ss ss' args = let s = either (error . show) id $ V1.deserialiseScript alonzoPV ss s' = either (error . show) id $ V1.deserialiseScript alonzoPV ss' - in ( evaluateScriptCounting alonzoPV Quiet v1_evalCtxForTesting s args - , evaluateScriptCounting alonzoPV Quiet v1_evalCtxForTesting s' args + in ( V1.evaluateScriptCounting alonzoPV V1.Quiet v1_evalCtxForTesting s args + , V1.evaluateScriptCounting alonzoPV V1.Quiet v1_evalCtxForTesting s' args ) in testGroup "salted function" [ testProperty "saturated" $ \(n :: Word8) salt fWhich -> @@ -100,6 +117,7 @@ tests = testGroup "plutus-ledger-api"[ , saltedFunction , unavailableBuiltins , availableBuiltins + , integerToByteStringExceedsBudget ] , Spec.Interval.tests , Spec.Eval.tests diff --git a/plutus-ledger-api/testlib/PlutusLedgerApi/Test/Examples.hs b/plutus-ledger-api/testlib/PlutusLedgerApi/Test/Examples.hs index fc941fde855..c0174ebddc2 100644 --- a/plutus-ledger-api/testlib/PlutusLedgerApi/Test/Examples.hs +++ b/plutus-ledger-api/testlib/PlutusLedgerApi/Test/Examples.hs @@ -1,7 +1,7 @@ -- editorconfig-checker-disable-file {-# LANGUAGE TypeApplications #-} -- | This module contains example values to be used for testing. These should NOT be used in non-test code! -module PlutusLedgerApi.Test.Examples (alwaysSucceedingNAryFunction, alwaysFailingNAryFunction, summingFunction, saltFunction) where +module PlutusLedgerApi.Test.Examples where import PlutusCore qualified as PLC import PlutusCore.MkPlc qualified as PLC @@ -50,3 +50,14 @@ saltFunction salt b0 = serialiseUPLC $ UPLC.Program () version body body = UPLC.Apply () (UPLC.LamAbs () (UPLC.DeBruijn 0) b1) (UPLC.Constant () $ Some $ PLC.ValueOf PLC.DefaultUniInteger salt) + +integerToByteStringFunction :: SerialisedScript +integerToByteStringFunction = serialiseUPLC $ UPLC.Program () PLC.plcVersion110 body + where + body = + PLC.mkIterAppNoAnn + (UPLC.Builtin () PLC.IntegerToByteString) + [ PLC.mkConstant @Bool () False + , PLC.mkConstant @Integer () 5 + , PLC.mkConstant @Integer () 1 + ] From 6cbaac4bc76122dafcc58895b1c8f9899443a0ba Mon Sep 17 00:00:00 2001 From: Ziyang Liu Date: Mon, 22 Apr 2024 03:14:41 +0200 Subject: [PATCH 3/3] Rename record fields --- .../PlutusCore/Evaluation/Machine/CostModelInterface.hs | 8 ++++---- plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs | 4 ++-- plutus-ledger-api/test/Spec/CostModelParams.hs | 2 +- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs index 4e51f79602d..146e8f2ec3f 100644 --- a/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs +++ b/plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/CostModelInterface.hs @@ -191,9 +191,9 @@ data CostModelApplyError = -- | A non-fatal warning when trying to create a cost given some plain costmodel parameters. data CostModelApplyWarn = - CMTooManyParamsWarn { cmTooManyExpected :: !Int, cmTooManyActual :: !Int } + CMTooManyParamsWarn { cmExpected :: !Int, cmActual :: !Int } -- ^ See Note [Cost model parameters from the ledger's point of view] - | CMTooFewParamsWarn { cmTooFewExpected :: !Int, cmTooFewActual :: !Int } + | CMTooFewParamsWarn { cmExpected :: !Int, cmActual :: !Int } -- ^ See Note [Cost model parameters from the ledger's point of view] instance Pretty CostModelApplyError where @@ -206,8 +206,8 @@ instance Pretty CostModelApplyError where instance Pretty CostModelApplyWarn where pretty = (preamble <+>) . \case - CMTooManyParamsWarn{..} -> "Too many cost model parameters passed, expected" <+> pretty cmTooManyExpected <+> "but got" <+> pretty cmTooManyActual - CMTooFewParamsWarn{..} -> "Too few cost model parameters passed, expected" <+> pretty cmTooFewExpected <+> "but got" <+> pretty cmTooFewActual + CMTooManyParamsWarn{..} -> "Too many cost model parameters passed, expected" <+> pretty cmExpected <+> "but got" <+> pretty cmActual + CMTooFewParamsWarn{..} -> "Too few cost model parameters passed, expected" <+> pretty cmExpected <+> "but got" <+> pretty cmActual where preamble = "applyParams warn:" diff --git a/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs b/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs index dbc302fc0b2..7c6ee429a67 100644 --- a/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs +++ b/plutus-ledger-api/src/PlutusLedgerApi/Common/ParamName.hs @@ -97,13 +97,13 @@ tagWithParamNames ledgerParams = pure $ zip paramNames ledgerParams LT -> do -- See Note [Cost model parameters from the ledger's point of view] - tell [CMTooManyParamsWarn {cmTooManyExpected = lenExpected, cmTooManyActual = lenActual}] + tell [CMTooManyParamsWarn {cmExpected = lenExpected, cmActual = lenActual}] -- zip will truncate/ignore any extraneous parameter values pure $ zip paramNames ledgerParams GT -> do -- Too few parameters - substitute a large number for the missing parameters -- See Note [Cost model parameters from the ledger's point of view] - tell [CMTooFewParamsWarn {cmTooFewExpected = lenExpected, cmTooFewActual = lenActual}] + tell [CMTooFewParamsWarn {cmExpected = lenExpected, cmActual = lenActual}] pure $ zip paramNames (ledgerParams ++ repeat (toInteger (maxBound :: Int64))) -- | Untags the plutus version from the typed cost model parameters and returns their raw textual form diff --git a/plutus-ledger-api/test/Spec/CostModelParams.hs b/plutus-ledger-api/test/Spec/CostModelParams.hs index 57726968f53..6cff19826ac 100644 --- a/plutus-ledger-api/test/Spec/CostModelParams.hs +++ b/plutus-ledger-api/test/Spec/CostModelParams.hs @@ -60,7 +60,7 @@ tests = where hasWarnMoreParams :: Int -> Int -> Either a (b, [CostModelApplyWarn]) -> Bool hasWarnMoreParams testExpected testActual (Right (_,[CMTooManyParamsWarn{..}])) - | testExpected==cmTooManyExpected && testActual==cmTooManyActual = True + | testExpected==cmExpected && testActual==cmActual = True hasWarnMoreParams _ _ _ = False paramProperSubset pA pB =