Skip to content

Commit

Permalink
PlutusV3 ScriptContext (IntersectMBO#5449)
Browse files Browse the repository at this point in the history
  • Loading branch information
zliu41 authored Aug 8, 2023
1 parent 998db79 commit 68c180d
Show file tree
Hide file tree
Showing 14 changed files with 685 additions and 92 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,11 @@

module PlutusBenchmark.ScriptContexts where

import PlutusLedgerApi.V1
import PlutusLedgerApi.V1.Address
import PlutusLedgerApi.V1.Value
import PlutusLedgerApi.V3
import PlutusTx qualified as PlutusTx
import PlutusTx.AssocMap qualified as Map
import PlutusTx.Builtins qualified as PlutusTx
import PlutusTx.Prelude qualified as PlutusTx

Expand All @@ -20,22 +21,29 @@ mkScriptContext i = ScriptContext (mkTxInfo i) (Spending (TxOutRef (TxId "") 0))
mkTxInfo :: Int -> TxInfo
mkTxInfo i = TxInfo {
txInfoInputs=mempty,
txInfoReferenceInputs=mempty,
txInfoOutputs=fmap mkTxOut [1..i],
txInfoFee=mempty,
txInfoMint=mempty,
txInfoDCert=mempty,
txInfoWdrl=mempty,
txInfoTxCerts=mempty,
txInfoWdrl=Map.empty,
txInfoValidRange=always,
txInfoSignatories=mempty,
txInfoData=mempty,
txInfoId=TxId ""
txInfoRedeemers=Map.empty,
txInfoData=Map.empty,
txInfoId=TxId "",
txInfoVotingProcedures=Map.empty,
txInfoProposalProcedures=mempty,
txInfoCurrentTreasuryAmount=Nothing,
txInfoTreasuryDonation=Nothing
}

mkTxOut :: Int -> TxOut
mkTxOut i = TxOut {
txOutAddress=pubKeyHashAddress (PubKeyHash ""),
txOutValue=mkValue i,
txOutDatumHash=Nothing
txOutDatum=NoOutputDatum,
txOutReferenceScript=Nothing
}

mkValue :: Int -> Value
Expand Down
4 changes: 2 additions & 2 deletions plutus-benchmark/script-contexts/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ testCheckSc1 = testGroup "checkScriptContext1"
compiledCodeToTerm $ mkCheckScriptContext1Code (mkScriptContext 4)
, testCase "fails on 5" . assertFailed $
compiledCodeToTerm $ mkCheckScriptContext1Code (mkScriptContext 5)
, Tx.fitsInto "checkScriptContext1 (size)" (mkCheckScriptContext1Code (mkScriptContext 1)) 1910
, Tx.fitsInto "checkScriptContext1 (size)" (mkCheckScriptContext1Code (mkScriptContext 1)) 3721
, runTestNested $ Tx.goldenBudget "checkScriptContext1-4" $
mkCheckScriptContext1Code (mkScriptContext 4)
, runTestNested $ Tx.goldenBudget "checkScriptContext1-20" $
Expand All @@ -54,7 +54,7 @@ testCheckSc2 = testGroup "checkScriptContext2"
compiledCodeToTerm $ mkCheckScriptContext2Code (mkScriptContext 4)
, testCase "succeed on 5" . assertSucceeded $
compiledCodeToTerm $ mkCheckScriptContext2Code (mkScriptContext 5)
, Tx.fitsInto "checkScriptContext2 (size)" (mkCheckScriptContext2Code (mkScriptContext 1)) 1847
, Tx.fitsInto "checkScriptContext2 (size)" (mkCheckScriptContext2Code (mkScriptContext 1)) 3652
, runTestNested $ Tx.goldenBudget "checkScriptContext2-4" $
mkCheckScriptContext2Code (mkScriptContext 4)
, runTestNested $ Tx.goldenBudget "checkScriptContext2-20" $
Expand Down
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 60538597
| mem: 200402})
({cpu: 65159541
| mem: 214802})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 404224911
| mem: 1263209})
({cpu: 471649967
| mem: 1452669})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 111747759
| mem: 350281})
({cpu: 136356335
| mem: 425597})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 385069422
| mem: 1201066})
({cpu: 452356478
| mem: 1389926})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 106199902
| mem: 332970})
({cpu: 130670478
| mem: 407686})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 45770100
| mem: 199100})
({cpu: 49082100
| mem: 213500})
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
({cpu: 588804251
| mem: 2402046})
({cpu: 603616251
| mem: 2466446})
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
### Added

- `ScriptContext` type for PlutusV3.
1 change: 1 addition & 0 deletions plutus-ledger-api/plutus-ledger-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ library
PlutusLedgerApi.V2.ParamName
PlutusLedgerApi.V2.Tx
PlutusLedgerApi.V3
PlutusLedgerApi.V3.Contexts
PlutusLedgerApi.V3.EvaluationContext
PlutusLedgerApi.V3.ParamName

Expand Down
153 changes: 83 additions & 70 deletions plutus-ledger-api/src/PlutusLedgerApi/V3.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,16 +12,33 @@ module PlutusLedgerApi.V3 (
-- * Running scripts
, evaluateScriptRestricting
, evaluateScriptCounting
-- ** CIP-1694
, ColdCommitteeCredential (..)
, HotCommitteeCredential (..)
, DRepCredential (..)
, DRep (..)
, Delegatee (..)
, AnchorDataHash (..)
, Anchor (..)
, TxCert (..)
, Voter (..)
, Vote (..)
, GovernanceActionId (..)
, VotingProcedure (..)
, Committee (..)
, Constitution (..)
, GovernanceAction (..)
, ProposalProcedure (..)
-- ** Protocol version
, ProtocolVersion (..)
-- ** Verbose mode and log output
, VerboseMode (..)
, LogOutput
-- * Costing-related types
, ExBudget (..)
, ExCPU (..)
, ExMemory (..)
, SatInt
, V2.ExCPU (..)
, V2.ExMemory (..)
, V2.SatInt
-- ** Cost model
, EvaluationContext
, mkEvaluationContext
Expand All @@ -34,90 +51,86 @@ module PlutusLedgerApi.V3 (
, ScriptPurpose(..)
-- ** Supporting types used in the context types
-- *** ByteStrings
, BuiltinByteString
, toBuiltin
, fromBuiltin
, V2.BuiltinByteString
, V2.toBuiltin
, V2.fromBuiltin
-- *** Bytes
, LedgerBytes (..)
, fromBytes
-- *** Certificates
, DCert(..)
, V2.LedgerBytes (..)
, V2.fromBytes
-- *** Credentials
, StakingCredential(..)
, Credential(..)
, V2.StakingCredential(..)
, V2.Credential(..)
-- *** Value
, Value (..)
, CurrencySymbol (..)
, TokenName (..)
, singleton
, unionWith
, adaSymbol
, adaToken
, V2.Value (..)
, V2.CurrencySymbol (..)
, V2.TokenName (..)
, V2.singleton
, V2.unionWith
, V2.adaSymbol
, V2.adaToken
-- *** Time
, POSIXTime (..)
, POSIXTimeRange
, V2.POSIXTime (..)
, V2.POSIXTimeRange
-- *** Types for representing transactions
, Address (..)
, PubKeyHash (..)
, TxId (..)
, V2.Address (..)
, V2.PubKeyHash (..)
, V2.TxId (..)
, TxInfo (..)
, TxOut(..)
, TxOutRef(..)
, TxInInfo(..)
, OutputDatum (..)
, V2.TxOut(..)
, V2.TxOutRef(..)
, V2.TxInInfo(..)
, V2.OutputDatum (..)
-- *** Intervals
, Interval (..)
, Extended (..)
, Closure
, UpperBound (..)
, LowerBound (..)
, always
, from
, to
, lowerBound
, upperBound
, strictLowerBound
, strictUpperBound
, V2.Interval (..)
, V2.Extended (..)
, V2.Closure
, V2.UpperBound (..)
, V2.LowerBound (..)
, V2.always
, V2.from
, V2.to
, V2.lowerBound
, V2.upperBound
, V2.strictLowerBound
, V2.strictUpperBound
-- *** Association maps
, Map
, fromList
, V2.Map
, V2.fromList
-- *** Newtypes and hash types
, ScriptHash (..)
, Redeemer (..)
, RedeemerHash (..)
, Datum (..)
, DatumHash (..)
, V2.ScriptHash (..)
, V2.Redeemer (..)
, V2.RedeemerHash (..)
, V2.Datum (..)
, V2.DatumHash (..)
-- * Data
, Data (..)
, BuiltinData (..)
, ToData (..)
, FromData (..)
, UnsafeFromData (..)
, toData
, fromData
, dataToBuiltinData
, builtinDataToData
, V2.Data (..)
, V2.BuiltinData (..)
, V2.ToData (..)
, V2.FromData (..)
, V2.UnsafeFromData (..)
, V2.toData
, V2.fromData
, V2.dataToBuiltinData
, V2.builtinDataToData
-- * Errors
, EvaluationError (..)
, ScriptDecodeError (..)
, V2.EvaluationError (..)
, V2.ScriptDecodeError (..)
) where

import Control.Monad.Except (MonadError)

import PlutusLedgerApi.Common as Common hiding (assertScriptWellFormed, evaluateScriptCounting,
evaluateScriptRestricting)
import PlutusLedgerApi.Common qualified as Common (assertScriptWellFormed, evaluateScriptCounting,
import PlutusLedgerApi.Common as Common hiding (ProtocolVersion (..), assertScriptWellFormed,
evaluateScriptCounting, evaluateScriptRestricting)
import PlutusLedgerApi.Common qualified as Common (ProtocolVersion (..), assertScriptWellFormed,
evaluateScriptCounting,
evaluateScriptRestricting)
import PlutusLedgerApi.V1 hiding (ParamName, ScriptContext (..), TxInInfo (..), TxInfo (..),
TxOut (..), assertScriptWellFormed, evaluateScriptCounting,
evaluateScriptRestricting, mkEvaluationContext)
import PlutusLedgerApi.V2.Contexts
import PlutusLedgerApi.V2.Tx (OutputDatum (..))
import PlutusLedgerApi.V2 qualified as V2 hiding (ScriptContext (..), ScriptPurpose (..),
TxInfo (..))
import PlutusLedgerApi.V3.Contexts
import PlutusLedgerApi.V3.EvaluationContext
import PlutusLedgerApi.V3.ParamName

import PlutusCore.Data qualified as PLC
import PlutusTx.AssocMap (Map, fromList)

-- | An alias to the Plutus ledger language this module exposes at runtime.
-- MAYBE: Use CPP '__FILE__' + some TH to automate this.
Expand All @@ -127,7 +140,7 @@ thisLedgerLanguage = PlutusV3
-- | Check if a 'Script' is "valid" according to a protocol version. At the moment this means "deserialises correctly", which in particular
-- implies that it is (almost certainly) an encoded script and the script does not mention any builtins unavailable in the given protocol version.
assertScriptWellFormed :: MonadError ScriptDecodeError m
=> ProtocolVersion -- ^ which protocol version to run the operation in
=> Common.ProtocolVersion -- ^ which protocol version to run the operation in
-> SerialisedScript -- ^ the script to check for well-formedness
-> m ()
assertScriptWellFormed = Common.assertScriptWellFormed thisLedgerLanguage
Expand All @@ -137,7 +150,7 @@ assertScriptWellFormed = Common.assertScriptWellFormed thisLedgerLanguage
-- limit the execution time of the script also, you can use 'evaluateScriptRestricting', which
-- also returns the used budget.
evaluateScriptCounting
:: ProtocolVersion -- ^ which protocol version to run the operation in
:: Common.ProtocolVersion -- ^ which protocol version to run the operation in
-> VerboseMode -- ^ Whether to produce log output
-> EvaluationContext -- ^ Includes the cost model to use for tallying up the execution costs
-> SerialisedScript -- ^ The script to evaluate
Expand All @@ -152,7 +165,7 @@ evaluateScriptCounting = Common.evaluateScriptCounting thisLedgerLanguage
-- Can be used to calculate budgets for scripts, but even in this case you must give
-- a limit to guard against scripts that run for a long time or loop.
evaluateScriptRestricting
:: ProtocolVersion -- ^ which protocol version to run the operation in
:: Common.ProtocolVersion -- ^ which protocol version to run the operation in
-> VerboseMode -- ^ Whether to produce log output
-> EvaluationContext -- ^ Includes the cost model to use for tallying up the execution costs
-> ExBudget -- ^ The resource budget which must not be exceeded during evaluation
Expand Down
Loading

0 comments on commit 68c180d

Please sign in to comment.