18
18
{-# LANGUAGE UndecidableSuperClasses #-}
19
19
20
20
module Cardano.Ledger.Plutus.Evaluate (
21
+ PlutusDebugOverrides (.. ),
21
22
PlutusWithContext (.. ),
22
23
ScriptFailure (.. ),
23
24
ScriptResult (.. ),
@@ -48,11 +49,16 @@ import Cardano.Ledger.Plutus.CostModels (
48
49
CostModel ,
49
50
decodeCostModel ,
50
51
encodeCostModel ,
52
+ getCostModelLanguage ,
53
+ getCostModelParams ,
51
54
getEvaluationContext ,
55
+ mkCostModel ,
52
56
)
53
- import Cardano.Ledger.Plutus.ExUnits (ExUnits )
57
+ import Cardano.Ledger.Plutus.ExUnits (ExUnits ( .. ) )
54
58
import Cardano.Ledger.Plutus.Language (
59
+ Language ,
55
60
Plutus (.. ),
61
+ PlutusBinary (.. ),
56
62
PlutusLanguage (.. ),
57
63
PlutusRunnable (.. ),
58
64
decodeWithPlutus ,
@@ -65,13 +71,24 @@ import Cardano.Ledger.Plutus.TxInfo
65
71
import Control.DeepSeq (NFData (.. ), force )
66
72
import Control.Exception (evaluate )
67
73
import Control.Monad (join , unless )
74
+ import Data.ByteString (ByteString )
75
+ import qualified Data.ByteString.Base16 as B16
68
76
import qualified Data.ByteString.Base64 as B64
77
+ import qualified Data.ByteString.Char8 as BSC
78
+ import qualified Data.ByteString.Short as SBS
69
79
import qualified Data.ByteString.UTF8 as BSU
80
+ import Data.Either (fromRight )
81
+ import Data.Int (Int64 )
70
82
import Data.List.NonEmpty (NonEmpty (.. ))
71
83
import Data.Maybe (fromMaybe )
72
84
import Data.Text (Text , pack )
73
85
import GHC.Generics (Generic )
74
- import PlutusLedgerApi.Common as P (EvaluationError (CodecError ), ExBudget , VerboseMode (.. ))
86
+ import Numeric.Natural (Natural )
87
+ import qualified PlutusLedgerApi.Common as P (
88
+ EvaluationError (CodecError ),
89
+ ExBudget ,
90
+ VerboseMode (.. ),
91
+ )
75
92
import Prettyprinter (Pretty (.. ))
76
93
import System.Timeout (timeout )
77
94
@@ -80,7 +97,7 @@ data PlutusWithContext c where
80
97
PlutusWithContext ::
81
98
PlutusLanguage l =>
82
99
{ pwcProtocolVersion :: ! Version
83
- -- ^ Mayjor protocol version that is necessary for [de]serialization
100
+ -- ^ Major protocol version that is necessary for [de]serialization
84
101
, pwcScript :: ! (Either (Plutus l ) (PlutusRunnable l ))
85
102
-- ^ Actual plutus script that will be evaluated. Script is allowed to be in two forms:
86
103
-- serialized and deserialized. This is necesary for implementing the opptimization
@@ -218,16 +235,56 @@ data PlutusDebugInfo c
218
235
(Maybe P. ExBudget )
219
236
deriving (Show )
220
237
221
- debugPlutus :: Crypto c => String -> IO (PlutusDebugInfo c )
222
- debugPlutus db =
223
- case B64. decode (BSU. fromString db) of
238
+ data PlutusDebugOverrides = PlutusDebugOverrides
239
+ { pdoScript :: ! (Maybe ByteString )
240
+ , pdoProtocolVersion :: ! (Maybe Version )
241
+ , pdoLanguage :: ! (Maybe Language )
242
+ , pdoCostModelValues :: ! (Maybe [Int64 ])
243
+ , pdoExUnitsMem :: ! (Maybe Natural )
244
+ , pdoExUnitsSteps :: ! (Maybe Natural )
245
+ }
246
+ deriving (Show )
247
+
248
+ -- TODO: Add support for overriding arguments.
249
+ overrideContext :: PlutusWithContext c -> PlutusDebugOverrides -> PlutusWithContext c
250
+ overrideContext PlutusWithContext {.. } PlutusDebugOverrides {.. } =
251
+ -- NOTE: due to GADTs, we can't do a record update here and need to
252
+ -- copy all the fields. Otherwise GHC will greet us with
253
+ -- `Record update for insufficiently polymorphic field...` error
254
+ PlutusWithContext
255
+ { pwcProtocolVersion = fromMaybe pwcProtocolVersion pdoProtocolVersion
256
+ , pwcScript = overrideScript
257
+ , pwcExUnits = overrideExUnits
258
+ , pwcCostModel = overrideCostModel
259
+ , ..
260
+ }
261
+ where
262
+ overrideExUnits =
263
+ ExUnits
264
+ (fromMaybe (exUnitsMem pwcExUnits) pdoExUnitsMem)
265
+ (fromMaybe (exUnitsSteps pwcExUnits) pdoExUnitsSteps)
266
+ overrideCostModel =
267
+ fromRight pwcCostModel $
268
+ mkCostModel
269
+ (fromMaybe (getCostModelLanguage pwcCostModel) pdoLanguage)
270
+ (fromMaybe (getCostModelParams pwcCostModel) pdoCostModelValues)
271
+ overrideScript =
272
+ case pdoScript of
273
+ Nothing -> pwcScript
274
+ Just script ->
275
+ either error (Left . Plutus . PlutusBinary . SBS. toShort) . B16. decode $ BSC. filter (/= ' \n ' ) script
276
+
277
+ debugPlutus :: Crypto c => String -> PlutusDebugOverrides -> IO (PlutusDebugInfo c )
278
+ debugPlutus scriptsWithContext opts =
279
+ case B64. decode (BSU. fromString scriptsWithContext) of
224
280
Left e -> pure $ DebugBadHex (show e)
225
281
Right bs ->
226
282
case Plain. decodeFull' bs of
227
283
Left e -> pure $ DebugCannotDecode $ show e
228
- Right pwc@ (PlutusWithContext {.. }) ->
229
- let cm = getEvaluationContext pwcCostModel
230
- eu = transExUnits pwcExUnits
284
+ Right pwcOriginal ->
285
+ let pwc = overrideContext pwcOriginal opts
286
+ cm = getEvaluationContext $ pwcCostModel pwc
287
+ eu = transExUnits $ pwcExUnits pwc
231
288
onDecoderError err = pure $ DebugFailure [] err pwc Nothing
232
289
in withRunnablePlutusWithContext pwc onDecoderError $ \ plutusRunnable args ->
233
290
let toDebugInfo = \ case
@@ -236,14 +293,14 @@ debugPlutus db =
236
293
mExpectedExUnits <-
237
294
timeout 5_000_000 $ do
238
295
let res =
239
- evaluatePlutusRunnableBudget pwcProtocolVersion P. Verbose cm plutusRunnable args
296
+ evaluatePlutusRunnableBudget ( pwcProtocolVersion pwc) P. Verbose cm plutusRunnable args
240
297
case snd res of
241
298
Left {} -> pure Nothing
242
299
Right exUnits -> Just <$> evaluate (force exUnits)
243
300
pure $ DebugFailure logs err pwc (join mExpectedExUnits)
244
301
(logs, Right ex) -> pure $ DebugSuccess logs ex
245
302
in toDebugInfo $
246
- evaluatePlutusRunnable pwcProtocolVersion P. Verbose cm eu plutusRunnable args
303
+ evaluatePlutusRunnable ( pwcProtocolVersion pwc) P. Verbose cm eu plutusRunnable args
247
304
248
305
runPlutusScript :: PlutusWithContext c -> ScriptResult c
249
306
runPlutusScript = snd . runPlutusScriptWithLogs
0 commit comments