Skip to content

Commit 9ab93f4

Browse files
Benchmark the production code rather than some arbitrary thing (#5200)
* Benchmark the production code rather than some arbitrary thing * Apply suggestions from code review Co-authored-by: Michael Peyton Jones <[email protected]> * Address comments --------- Co-authored-by: Michael Peyton Jones <[email protected]>
1 parent 4497b2f commit 9ab93f4

File tree

6 files changed

+73
-26
lines changed

6 files changed

+73
-26
lines changed
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
Fixed
2+
-----
3+
4+
- Made the `validation` benchmarks use the actual production evaluator (#5200)

plutus-benchmark/plutus-benchmark.cabal

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -271,6 +271,8 @@ benchmark validation
271271
, optparse-applicative
272272
, plutus-benchmark-common
273273
, plutus-core ^>=1.3
274+
, plutus-ledger-api ^>=1.3
275+
, transformers
274276

275277
---------------- validation-decode ----------------
276278

@@ -291,6 +293,7 @@ benchmark validation-decode
291293
, plutus-benchmark-common
292294
, plutus-core ^>=1.3
293295
, plutus-ledger-api ^>=1.3
296+
, transformers
294297

295298
---------------- validation-full ----------------
296299

@@ -311,6 +314,7 @@ benchmark validation-full
311314
, plutus-benchmark-common
312315
, plutus-core ^>=1.3
313316
, plutus-ledger-api:{plutus-ledger-api, plutus-ledger-api-testlib} ^>=1.3
317+
, transformers
314318

315319
---------------- Cek cost model calibration ----------------
316320

plutus-benchmark/validation/BenchCek.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Main where
33

44
import Common
55
import Control.DeepSeq (force)
6+
import Control.Exception
67
import Criterion
78
import PlutusBenchmark.Common
89
import UntypedPlutusCore as UPLC
@@ -16,11 +17,10 @@ import UntypedPlutusCore as UPLC
1617
`cabal bench -- plutus-benchmark:validation --benchmark-options crowdfunding`.
1718
-}
1819
main :: IO ()
19-
main = benchWith mkCekBM
20+
main = evaluate (force getEvalCtx) *> benchWith mkCekBM
2021
where
2122
mkCekBM file program =
2223
-- don't count the undebruijn . unflat cost
2324
-- `force` to try to ensure that deserialiation is not included in benchmarking time.
2425
let !nterm = force (toNamedDeBruijnTerm $ UPLC._progTerm $ unsafeUnflat file program)
25-
in whnf unsafeEvaluateCekNoEmit' nterm
26-
26+
in whnf evaluateCekLikeInProd nterm

plutus-benchmark/validation/Common.hs

Lines changed: 36 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -3,19 +3,25 @@
33
module Common (
44
benchWith
55
, unsafeUnflat
6-
, unsafeEvaluateCekNoEmit'
6+
, getEvalCtx
7+
, evaluateCekLikeInProd
78
, peelDataArguments
89
, Term
910
) where
1011

12+
import PlutusPrelude
13+
1114
import PlutusBenchmark.Common (getConfig, getDataDir)
1215
import PlutusBenchmark.NaturalSort
1316

1417
import PlutusCore qualified as PLC
1518
import PlutusCore.Builtin qualified as PLC
1619
import PlutusCore.Data qualified as PLC
1720
import PlutusCore.Evaluation.Machine.ExBudgetingDefaults qualified as PLC
18-
import PlutusCore.Evaluation.Machine.Exception
21+
import PlutusCore.Evaluation.Result
22+
import PlutusLedgerApi.Common (LedgerPlutusVersion (PlutusV1), evaluateTerm)
23+
import PlutusLedgerApi.Common.Versions (languageIntroducedIn)
24+
import PlutusLedgerApi.V3 (EvaluationContext, ParamName, VerboseMode (..), mkEvaluationContext)
1925
import UntypedPlutusCore qualified as UPLC
2026
import UntypedPlutusCore.Evaluation.Machine.Cek qualified as UPLC
2127

@@ -24,6 +30,8 @@ import Criterion.Main.Options (Mode, parseWith)
2430
import Criterion.Types (Config (..))
2531
import Options.Applicative
2632

33+
import Control.Monad.Trans.Except
34+
import Control.Monad.Trans.Writer.Strict
2735
import Data.ByteString qualified as BS
2836
import Data.List (isPrefixOf)
2937
import Flat
@@ -128,13 +136,32 @@ benchWith act = do
128136
env (BS.readFile $ dir </> file) $ \scriptBS ->
129137
bench (dropExtension file) $ act file scriptBS
130138

131-
unsafeEvaluateCekNoEmit' :: UPLC.Term PLC.NamedDeBruijn PLC.DefaultUni PLC.DefaultFun () -> PLC.EvaluationResult (UPLC.Term PLC.NamedDeBruijn PLC.DefaultUni PLC.DefaultFun ())
132-
unsafeEvaluateCekNoEmit' =
133-
(\(e, _, _) -> unsafeExtractEvaluationResult e) .
134-
UPLC.runCekDeBruijn
135-
PLC.defaultCekParameters
136-
UPLC.restrictingEnormous
137-
UPLC.noEmitter
139+
getEvalCtx
140+
:: Either
141+
(UPLC.CekEvaluationException UPLC.NamedDeBruijn UPLC.DefaultUni UPLC.DefaultFun)
142+
EvaluationContext
143+
getEvalCtx = do
144+
costParams <-
145+
maybe
146+
(Left evaluationFailure)
147+
(Right . take (length $ enumerate @ParamName) . toList)
148+
PLC.defaultCostModelParams
149+
either (const $ Left evaluationFailure) (Right . fst) . runExcept . runWriterT $
150+
mkEvaluationContext costParams
151+
{-# NOINLINE getEvalCtx #-}
152+
153+
-- | Evaluate a term as it would be evaluated using the on-chain evaluator.
154+
evaluateCekLikeInProd
155+
:: UPLC.Term PLC.NamedDeBruijn PLC.DefaultUni PLC.DefaultFun ()
156+
-> Either
157+
(UPLC.CekEvaluationException UPLC.NamedDeBruijn UPLC.DefaultUni UPLC.DefaultFun)
158+
(UPLC.Term UPLC.NamedDeBruijn UPLC.DefaultUni UPLC.DefaultFun ())
159+
evaluateCekLikeInProd term = do
160+
evalCtx <- getEvalCtx
161+
let (getRes, _, _) =
162+
-- The validation benchmarks were all created from PlutusV1 scripts
163+
evaluateTerm UPLC.restrictingEnormous (languageIntroducedIn PlutusV1) Quiet evalCtx term
164+
getRes
138165

139166
type Term = UPLC.Term UPLC.DeBruijn UPLC.DefaultUni UPLC.DefaultFun ()
140167

plutus-ledger-api/src/PlutusLedgerApi/Common.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module PlutusLedgerApi.Common
1111
-- * Script evaluation
1212
, evaluateScriptCounting
1313
, evaluateScriptRestricting
14+
, evaluateTerm
1415
, VerboseMode (..)
1516
, LogOutput
1617
, EvaluationError (..)

plutus-ledger-api/src/PlutusLedgerApi/Common/Eval.hs

Lines changed: 25 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module PlutusLedgerApi.Common.Eval
1313
, VerboseMode (..)
1414
, evaluateScriptRestricting
1515
, evaluateScriptCounting
16+
, evaluateTerm
1617
, mkDynEvaluationContext
1718
, toMachineParameters
1819
, mkTermToEvaluate
@@ -133,6 +134,28 @@ mkDynEvaluationContext ver newCMP =
133134
assertWellFormedCostModelParams :: MonadError CostModelApplyError m => Plutus.CostModelParams -> m ()
134135
assertWellFormedCostModelParams = void . Plutus.applyCostModelParams Plutus.defaultCekCostModel
135136

137+
-- | Evaluate a fully-applied term using the CEK machine. Useful for mimicking the behaviour of the
138+
-- on-chain evaluator.
139+
evaluateTerm
140+
:: UPLC.ExBudgetMode cost DefaultUni DefaultFun
141+
-> ProtocolVersion
142+
-> VerboseMode
143+
-> EvaluationContext
144+
-> UPLC.Term UPLC.NamedDeBruijn DefaultUni DefaultFun ()
145+
-> ( Either
146+
(UPLC.CekEvaluationException NamedDeBruijn DefaultUni DefaultFun)
147+
(UPLC.Term UPLC.NamedDeBruijn DefaultUni DefaultFun ())
148+
, cost
149+
, [Text]
150+
)
151+
evaluateTerm budgetMode pv verbose ectx =
152+
UPLC.runCekDeBruijn
153+
(toMachineParameters pv ectx)
154+
budgetMode
155+
(if verbose == Verbose then UPLC.logEmitter else UPLC.noEmitter)
156+
-- Just replicating the old behavior, probably doesn't matter.
157+
{-# INLINE evaluateTerm #-}
158+
136159
{-| Evaluates a script, with a cost model and a budget that restricts how many
137160
resources it can use according to the cost model. Also returns the budget that
138161
was actually used.
@@ -155,14 +178,8 @@ evaluateScriptRestricting
155178
-> (LogOutput, Either EvaluationError ExBudget)
156179
evaluateScriptRestricting lv pv verbose ectx budget p args = swap $ runWriter @LogOutput $ runExceptT $ do
157180
appliedTerm <- mkTermToEvaluate lv pv p args
158-
159181
let (res, UPLC.RestrictingSt (ExRestrictingBudget final), logs) =
160-
UPLC.runCekDeBruijn
161-
(toMachineParameters pv ectx)
162-
(UPLC.restricting $ ExRestrictingBudget budget)
163-
(if verbose == Verbose then UPLC.logEmitter else UPLC.noEmitter)
164-
appliedTerm
165-
182+
evaluateTerm (UPLC.restricting $ ExRestrictingBudget budget) pv verbose ectx appliedTerm
166183
tell logs
167184
liftEither $ first CekError $ void res
168185
pure (budget `minusExBudget` final)
@@ -184,14 +201,8 @@ evaluateScriptCounting
184201
-> (LogOutput, Either EvaluationError ExBudget)
185202
evaluateScriptCounting lv pv verbose ectx p args = swap $ runWriter @LogOutput $ runExceptT $ do
186203
appliedTerm <- mkTermToEvaluate lv pv p args
187-
188204
let (res, UPLC.CountingSt final, logs) =
189-
UPLC.runCekDeBruijn
190-
(toMachineParameters pv ectx)
191-
UPLC.counting
192-
(if verbose == Verbose then UPLC.logEmitter else UPLC.noEmitter)
193-
appliedTerm
194-
205+
evaluateTerm UPLC.counting pv verbose ectx appliedTerm
195206
tell logs
196207
liftEither $ first CekError $ void res
197208
pure final

0 commit comments

Comments
 (0)