Skip to content

Commit 52eba47

Browse files
Lucsanszkylehins
authored andcommittedDec 13, 2024
Create CLI for plutus-debug
1 parent 3bdb373 commit 52eba47

File tree

7 files changed

+166
-16
lines changed

7 files changed

+166
-16
lines changed
 

‎hie.yaml

+3
Original file line numberDiff line numberDiff line change
@@ -231,6 +231,9 @@ cradle:
231231
- path: "libs/cardano-ledger-core/app/PlutusDebug.hs"
232232
component: "cardano-ledger-core:exe:plutus-debug"
233233

234+
- path: "libs/cardano-ledger-core/app/CLI.hs"
235+
component: "cardano-ledger-core:exe:plutus-debug"
236+
234237
- path: "libs/cardano-ledger-core/test"
235238
component: "cardano-ledger-core:test:tests"
236239

‎libs/cardano-ledger-core/CHANGELOG.md

+3
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,9 @@
22

33
## 1.16.0.0
44

5+
* Add `PlutusDebugOverrides` argument to `debugPlutus`
6+
* Add `PlutusDebugOverrides` data type
7+
* Add `Read` instance for `Language`
58
* Add `toVRFVerKeyHash` and `fromVRFVerKeyHash`
69
* Change lens type of `hkdNOptL`, `ppNOptL`, and `ppuNOptL` to `Word16`
710
* Add `epochFromSlot`

‎libs/cardano-ledger-core/app/CLI.hs

+62
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,62 @@
1+
module CLI (
2+
Opts (..),
3+
optsParser,
4+
) where
5+
6+
import Cardano.Ledger.Binary (mkVersion64)
7+
import Cardano.Ledger.Plutus.Evaluate
8+
import Options.Applicative
9+
10+
data Opts = Opts
11+
{ optsScriptWithContext :: !String
12+
, optsOverrides :: !PlutusDebugOverrides
13+
}
14+
deriving (Show)
15+
16+
overridesParser :: Parser PlutusDebugOverrides
17+
overridesParser =
18+
PlutusDebugOverrides
19+
<$> option
20+
(Just <$> str)
21+
( long "script"
22+
<> value Nothing
23+
<> help "Plutus script hex without context"
24+
)
25+
<*> option
26+
(mkVersion64 <$> auto)
27+
( long "protocol-version"
28+
<> short 'v'
29+
<> value Nothing
30+
<> help "Major protocol version"
31+
)
32+
<*> option
33+
(Just <$> auto)
34+
( long "language"
35+
<> value Nothing
36+
<> help "Plutus language version"
37+
)
38+
<*> option
39+
(str >>= pure . Just . map read . words)
40+
( long "cost-model-values"
41+
<> value Nothing
42+
<> help ""
43+
)
44+
<*> option
45+
(Just <$> auto)
46+
( long "execution-units-memory"
47+
<> value Nothing
48+
<> help ""
49+
)
50+
<*> option
51+
(Just <$> auto)
52+
( long "execution-units-steps"
53+
<> value Nothing
54+
<> help ""
55+
)
56+
57+
optsParser :: Parser Opts
58+
optsParser =
59+
Opts
60+
<$> strArgument
61+
(metavar "SCRIPT_WITH_CONTEXT(BASE64)")
62+
<*> overridesParser
+24-4
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,31 @@
1+
{-# LANGUAGE RecordWildCards #-}
12
{-# LANGUAGE TypeApplications #-}
23

34
module Main where
45

6+
import CLI
57
import Cardano.Ledger.Crypto (StandardCrypto)
6-
import Cardano.Ledger.Plutus.Evaluate (debugPlutus)
7-
import Control.Monad ((<=<))
8-
import System.Environment (getArgs)
8+
import Cardano.Ledger.Plutus.Evaluate
9+
import Options.Applicative
910

1011
main :: IO ()
11-
main = mapM_ (print <=< debugPlutus @StandardCrypto) =<< getArgs
12+
main = do
13+
Opts {..} <-
14+
execParser $
15+
info
16+
(optsParser <* abortOption (ShowHelpText Nothing) (long "help"))
17+
( header "plutus-debug - A Plutus script debugger"
18+
<> progDesc
19+
( "The purpose of this tool is to troubleshoot failing Plutus scripts. "
20+
<> "When you encounter a `PlutusFailure`, you can pass the `Base64-encoded script bytes` "
21+
<> "to `plutus-debug` for debugging purposes and override the context of the failed script "
22+
<> "and the script itself with the available command line options."
23+
)
24+
<> footer
25+
( "EXAMPLE: plutus-debug \"hgmCAVksj...\" --script \"5906ab010...\" "
26+
<> "Note when rewriting the script with the `--script` option "
27+
<> "you will have to provide the hex of the Plutus script as seen in "
28+
<> "`Test.Cardano.Ledger.Plutus.Examples`."
29+
)
30+
)
31+
debugPlutus @StandardCrypto optsScriptWithContext optsOverrides >>= print

‎libs/cardano-ledger-core/cardano-ledger-core.cabal

+5
Original file line numberDiff line numberDiff line change
@@ -219,6 +219,9 @@ library testlib
219219
executable plutus-debug
220220
main-is: PlutusDebug.hs
221221
hs-source-dirs: app
222+
other-modules:
223+
CLI
224+
222225
default-language: Haskell2010
223226
ghc-options:
224227
-Wall
@@ -234,7 +237,9 @@ executable plutus-debug
234237

235238
build-depends:
236239
base >=4.14 && <5,
240+
cardano-ledger-binary,
237241
cardano-ledger-core,
242+
optparse-applicative,
238243

239244
test-suite tests
240245
type: exitcode-stdio-1.0

‎libs/cardano-ledger-core/src/Cardano/Ledger/Plutus/Evaluate.hs

+68-11
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@
1818
{-# LANGUAGE UndecidableSuperClasses #-}
1919

2020
module Cardano.Ledger.Plutus.Evaluate (
21+
PlutusDebugOverrides (..),
2122
PlutusWithContext (..),
2223
ScriptFailure (..),
2324
ScriptResult (..),
@@ -48,11 +49,16 @@ import Cardano.Ledger.Plutus.CostModels (
4849
CostModel,
4950
decodeCostModel,
5051
encodeCostModel,
52+
getCostModelLanguage,
53+
getCostModelParams,
5154
getEvaluationContext,
55+
mkCostModel,
5256
)
53-
import Cardano.Ledger.Plutus.ExUnits (ExUnits)
57+
import Cardano.Ledger.Plutus.ExUnits (ExUnits (..))
5458
import Cardano.Ledger.Plutus.Language (
59+
Language,
5560
Plutus (..),
61+
PlutusBinary (..),
5662
PlutusLanguage (..),
5763
PlutusRunnable (..),
5864
decodeWithPlutus,
@@ -65,13 +71,24 @@ import Cardano.Ledger.Plutus.TxInfo
6571
import Control.DeepSeq (NFData (..), force)
6672
import Control.Exception (evaluate)
6773
import Control.Monad (join, unless)
74+
import Data.ByteString (ByteString)
75+
import qualified Data.ByteString.Base16 as B16
6876
import qualified Data.ByteString.Base64 as B64
77+
import qualified Data.ByteString.Char8 as BSC
78+
import qualified Data.ByteString.Short as SBS
6979
import qualified Data.ByteString.UTF8 as BSU
80+
import Data.Either (fromRight)
81+
import Data.Int (Int64)
7082
import Data.List.NonEmpty (NonEmpty (..))
7183
import Data.Maybe (fromMaybe)
7284
import Data.Text (Text, pack)
7385
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+
)
7592
import Prettyprinter (Pretty (..))
7693
import System.Timeout (timeout)
7794

@@ -80,7 +97,7 @@ data PlutusWithContext c where
8097
PlutusWithContext ::
8198
PlutusLanguage l =>
8299
{ pwcProtocolVersion :: !Version
83-
-- ^ Mayjor protocol version that is necessary for [de]serialization
100+
-- ^ Major protocol version that is necessary for [de]serialization
84101
, pwcScript :: !(Either (Plutus l) (PlutusRunnable l))
85102
-- ^ Actual plutus script that will be evaluated. Script is allowed to be in two forms:
86103
-- serialized and deserialized. This is necesary for implementing the opptimization
@@ -218,16 +235,56 @@ data PlutusDebugInfo c
218235
(Maybe P.ExBudget)
219236
deriving (Show)
220237

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
224280
Left e -> pure $ DebugBadHex (show e)
225281
Right bs ->
226282
case Plain.decodeFull' bs of
227283
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
231288
onDecoderError err = pure $ DebugFailure [] err pwc Nothing
232289
in withRunnablePlutusWithContext pwc onDecoderError $ \plutusRunnable args ->
233290
let toDebugInfo = \case
@@ -236,14 +293,14 @@ debugPlutus db =
236293
mExpectedExUnits <-
237294
timeout 5_000_000 $ do
238295
let res =
239-
evaluatePlutusRunnableBudget pwcProtocolVersion P.Verbose cm plutusRunnable args
296+
evaluatePlutusRunnableBudget (pwcProtocolVersion pwc) P.Verbose cm plutusRunnable args
240297
case snd res of
241298
Left {} -> pure Nothing
242299
Right exUnits -> Just <$> evaluate (force exUnits)
243300
pure $ DebugFailure logs err pwc (join mExpectedExUnits)
244301
(logs, Right ex) -> pure $ DebugSuccess logs ex
245302
in toDebugInfo $
246-
evaluatePlutusRunnable pwcProtocolVersion P.Verbose cm eu plutusRunnable args
303+
evaluatePlutusRunnable (pwcProtocolVersion pwc) P.Verbose cm eu plutusRunnable args
247304

248305
runPlutusScript :: PlutusWithContext c -> ScriptResult c
249306
runPlutusScript = snd . runPlutusScriptWithLogs

‎libs/cardano-ledger-core/src/Cardano/Ledger/Plutus/Language.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -226,7 +226,7 @@ data Language
226226
= PlutusV1
227227
| PlutusV2
228228
| PlutusV3
229-
deriving (Eq, Generic, Show, Ord, Enum, Bounded, Ix)
229+
deriving (Eq, Generic, Show, Ord, Enum, Bounded, Ix, Read)
230230

231231
instance NoThunks Language
232232

0 commit comments

Comments
 (0)
Please sign in to comment.