Skip to content

Commit fefa367

Browse files
committed
SCP-2772: Teach evaluateScriptRestricting to return the used budget
This enables the ledger to compute budgets while still setting an overall limit, to guard against scripts that run for a very long time, or loop. I decided to roll this into `evaluateScriptRestricting` rather than giving `evaluteScriptCounting` a bound, since having the bound-less version of `evaluateScriptCounting` is still handy for casual usage. Possibly it's actually just a trap and we should delete it, though.
1 parent 913c867 commit fefa367

File tree

2 files changed

+16
-7
lines changed
  • plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine
  • plutus-ledger-api/src/Plutus/V1/Ledger

2 files changed

+16
-7
lines changed

plutus-core/plutus-core/src/PlutusCore/Evaluation/Machine/ExBudget.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -137,6 +137,7 @@ possible to adjust them at runtime.
137137

138138
module PlutusCore.Evaluation.Machine.ExBudget
139139
( ExBudget(..)
140+
, minusExBudget
140141
, ExBudgetBuiltin(..)
141142
, ExRestrictingBudget(..)
142143
, LowerIntialCharacter
@@ -178,6 +179,10 @@ data ExBudget = ExBudget { exBudgetCPU :: ExCPU, exBudgetMemory :: ExMemory }
178179
deriving (FromJSON, ToJSON) via CustomJSON '[FieldLabelModifier LowerIntialCharacter] ExBudget
179180
-- LowerIntialCharacter won't actually do anything here, but let's have it in case we change the field names.
180181

182+
-- | Subract one 'ExBudget' from another. Does not guarantee that the result is positive.
183+
minusExBudget :: ExBudget -> ExBudget -> ExBudget
184+
minusExBudget (ExBudget c1 m1) (ExBudget c2 m2) = ExBudget (c1-c2) (m1-m2)
185+
181186
-- These functions are performance critical, so we can't use GenericSemigroupMonoid, and we insist that they be inlined.
182187
instance Semigroup ExBudget where
183188
{-# INLINE (<>) #-}

plutus-ledger-api/src/Plutus/V1/Ledger/Api.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -220,24 +220,25 @@ mkTermToEvaluate bs args = do
220220
pure t
221221

222222
-- | Evaluates a script, with a cost model and a budget that restricts how many
223-
-- resources it can use according to the cost model. There's a default cost
224-
-- model in 'UPLC.defaultBuiltinCostModel' and a budget called 'enormousBudget' in
225-
-- 'UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode' which should be large
226-
-- enough to evaluate any sensible program.
223+
-- resources it can use according to the cost model. Also returns the budget that
224+
-- was actually used.
225+
--
226+
-- Can be used to calculate budgets for scripts, but even in this case you must give
227+
-- a limit to guard against scripts that run for a long time or loop.
227228
evaluateScriptRestricting
228229
:: VerboseMode -- ^ Whether to produce log output
229230
-> CostModelParams -- ^ The cost model to use
230231
-> ExBudget -- ^ The resource budget which must not be exceeded during evaluation
231232
-> SerializedScript -- ^ The script to evaluate
232233
-> [PLC.Data] -- ^ The arguments to the script
233-
-> (LogOutput, Either EvaluationError ())
234+
-> (LogOutput, Either EvaluationError ExBudget)
234235
evaluateScriptRestricting verbose cmdata budget p args = swap $ runWriter @LogOutput $ runExceptT $ do
235236
appliedTerm <- mkTermToEvaluate p args
236237
model <- case applyCostModelParams PLC.defaultCekCostModel cmdata of
237238
Just model -> pure model
238239
Nothing -> throwError CostModelParameterMismatch
239240

240-
let (res, _, logs) =
241+
let (res, UPLC.RestrictingSt (PLC.ExRestrictingBudget final), logs) =
241242
UPLC.runCek
242243
(toMachineParameters model)
243244
(UPLC.restricting $ PLC.ExRestrictingBudget budget)
@@ -246,9 +247,12 @@ evaluateScriptRestricting verbose cmdata budget p args = swap $ runWriter @LogOu
246247

247248
tell logs
248249
liftEither $ first CekError $ void res
250+
pure (budget `PLC.minusExBudget` final)
249251

250252
-- | Evaluates a script, returning the minimum budget that the script would need
251-
-- to evaluate successfully.
253+
-- to evaluate successfully. This will take as long as the script takes, if you need to
254+
-- limit the execution time of the script also, you can use 'evaluateScriptRestricting', which
255+
-- also returns the used budget.
252256
evaluateScriptCounting
253257
:: VerboseMode -- ^ Whether to produce log output
254258
-> CostModelParams -- ^ The cost model to use

0 commit comments

Comments
 (0)